⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 screen.asm

📁 Dos6.0
💻 ASM
📖 第 1 页 / 共 3 页
字号:
;*
;*	COW : Character Oriented Windows
;*
;*	screen.asm : installable screen drivers

	title	screen - Screen control code for CW

.xlist
	include	user.inc
	include uisa.inc		;* for isa's
	include	screen.inc		;* screen stuff

	include	inscr.inc
	include	indrv.inc

ifdef	KANJI
	include kanji.inc
endif	;KANJI

.list

;----------------------------------------------------------------------------
;
;	* Video Support Macros *

;********** PrepareDraw **********
;*	entry : axPos = ax position
;*		ayPos = ay position
;*	* Calculate the screen position of the character specified
;*	* set ayDrawing to the row being drawn, clear fMouseLockedOut first
;*	* set axDrawFirst
;*	exit : ES:DI = address of character (lpch)
;*	* TRASHES AX,BX

PrepareDraw MACRO axPos,ayPos
	mov	al,ayPos
	mov	ayDrawing,al			;* set drawing location
	mul	axMac
	mov	bl,axPos
	mov	axDrawFirst,bl
	xor	bh,bh
	add	ax,bx
	shl	ax,1		; ax = (ayPos * axMac + ayPos) * 2
ifdef	DEBUG
	cmp	instCur.psPrimInst,0	;* no buffer! (FAllocInstBuffers)
	jne	@F
	cCall	CowAssertFailed
	DB	"no primary buffer for current mode$"
@@:
endif	;DEBUG
	mov	es,instCur.psPrimInst
	mov	di,ax		;* ES:DI => primary buffer
ENDM

;*****************************************************************************

ifdef	DEBPUB	;* Debugging Publics
	PUBLIC	DoDraw
endif

;*****************************************************************************

sBegin	DATA
	assumes DS,DGROUP

;* PUBLIC
externW <rgsa>			;* array of SA's
externB <inch, insj>

IFNDEF	CBOX
externB	<boxSingle, boxDouble, chShadow>
endif	; !CBOX

ifdef	WINDOW_OVERLAP
externW <psOverlap>		;* windows for overlap check
externW <pwndCur>		;* current drawing window
externB <boxActiveWindowOut>
externB <boxInactiveWindowOut>
externB <boxActiveWindowIn>
externB <boxInactiveWindowIn>
endif	;WINDOW_OVERLAP

;* PRIVATE
externB <ayMouse>		;* current mouse position


globalB	ayDrawing,ayNil		;* current drawing ay
globalB	axDrawFirst,ayNil	;* start drawing ax

ifdef	SCREEN_FFONT
externW	<mpisaffont>		;* ffont values
endif	;SCREEN_FFONT

ifdef	BUILTIN_SNOW
globalB fWaitRetrace,0		;* snow protect for twin compatibility,QC only
endif	;BUILTIN_SNOW

sEnd	DATA

;----------------------------------------------------------------------------

sBegin	BSS
	assumes DS,DGROUP

globalB instCur,<cbInstMin DUP (?)>	; data for installable drivers.

globalW	fRestoreDbcs,0		;* => restore DBCS characters
				;* stays 0 for non-KANJI

ifdef	SCREEN_FFONT
globalW	fFontAvailable,0	;* => ffont support allowed
endif	;SCREEN_FFONT

globalB	axMac,0			; Maximum column number
globalB	ayMac,0			; Maximum row number (start at 0)
globalW	axMacTimes2,0		; for row modulus - WORD !!!

globalB	fMonochrome,0		;* Is b/w display

;*	* Variable for implementing mouse lockout (see kernel/mouse.asm)
globalB	fMouseLockedOut,0	;* set by mouse handler

globalB cHoldUpdate,0		;* used by BeginDraw EndDraw

;* PRIVATE *
globalW	fColorModeOld,0		;* last color mode

globalW	offDrawFirst,0		;* offset where drawing started
staticW	ffontCur,0		;* current ffont value

;*	* KLUDGE for clear screen !!
globalB	caOld,0			;* old screen attribute
	DB	0

sEnd	BSS

;*****************************************************************************


sBegin	SCREEN
	assumes CS,SCREEN
	assumes DS,DGROUP
	assumes SS,DGROUP

;*	* High level routines

;********** FillArc **********
;*	entry : axLeft, ayTop, axRight, ayBottom : rectangle to fill
;*		chFill	: fill character (CHAR -- may be DBCS character)
;*		diCur	: draw info (HIBYTE = dm, LOBYTE = isa).
;*	* apply draw mode & data to specified rectangle
;*		D flag MUST BE CLEARED !!!
;*	exit : n/a

cPrivate FillArc,<ATOMIC>,<SI,DI>		;* PRIVATE
	parmB  axLeft
	parmB  ayTop 
	parmB  axRight 
	parmB  ayBottom			;* also day
ifdef	KANJI
	parmW  chFill			;* CHAR type
ELSE
	parmB  chFill
endif	;!KANJI
	parmW  diCur			;* draw info

	LocalW daxMax			;* line wrap value

cBegin	FillArc

	StartPublic
	AssertUp

;*	* Find row count
	mov	al,ayTop
	sub	ayBottom,al		;* day
ifdef	KANJI
	jz	J_fill_end
else	; KANJI
	jz	fill_end		;* no rows to fill
endif	; KANJI

;*	* Find character count
	mov	cl,axRight
	sub	cl,axLeft
ifdef	KANJI
	jnz	@F
J_fill_end:
	jmp	fill_end
@@:
else	; KANJI
	jz	fill_end		;* no width to fill
endif	; KANJI
	xor	ch,ch

;*	* Prepare for the fill
	PrepareDraw axLeft,ayTop	;* sets ES:DI
	mov	dx,screenOffset mpdmnpfnDrawFR	;* normal fill row
ifdef	KANJI
	mov	ax,chFill		;* fill character
	JmpNotDbc fill_normal
;*	* fill as double byte character
	and	cx,not 1		;* force even
	mov	dx,screenOffset mpdmnpfnDrawFR_DBCS	;* DBCS fill row
fill_normal:
ELSE
	mov	al,chFill		;* fill character
endif
	mov	si,ax			;* SI = char save value

;*	* SI = character (AL for non KANJI), DX = dispatch table, CX = count
fill_row_loop:
;*	* Perform Draw
	mov	bx,diCur
	Save	<dx,cx,di>			;* cx = dax, di + start
	cCall	DoDraw			;* fill it in
	inc	ayDrawing		;* next row
	add	di,axMacTimes2		;* to next row
	dec	ayBottom		;* day
	jnz	fill_row_loop

	cCall	FinishDraw

fill_end:
	AssertUp
	StopPublic

cEnd	FillArc



;********** TextOutAbs **********
;*	entry : axLeft, ayTop : start position
;*		pch	: pointer to string data
;*		cch	: # of characters
;*		diCur	: draw info (HIBYTE = dm, LOBYTE = isa).
;*	* apply draw mode & string data to 1 row of text
;*		D flag MUST BE CLEARED !!!
;*	exit : n/a

cPrivate TextOutAbs,<ATOMIC>,<SI,DI>
	parmB  axLeft
	parmB  ayTop
	parmDP pch  
	parmW  cch
	parmW  diCur			;* draw mode + isa
  
cBegin	TextOutAbs

	StartPublic

	AssertUp

;*	* Prepare for the fill
	PrepareDraw axLeft,ayTop	;* sets ES:DI
	mov	si,pch			;* array

	mov	cx,cch

	mov	dx,screenOffset mpdmnpfnDrawTO
	mov	bx,diCur
	cCall	DoDraw			;* perform Text Out

	cCall	FinishDraw

textout_end:
	AssertUp

	StopPublic

cEnd	TextOutAbs



;********** CharOutAbs **********
;*	entry : axCur, ayCur : start position
;*		chPut	: character to put (CHAR)
;*		diCur	: draw info (HIBYTE = dm, LOBYTE = isa).
;*	* TextOutAbs for a single character
;*		D flag MUST BE CLEARED !!!
;*	exit : n/a

cPrivate CharOutAbs,<ATOMIC>,<SI,DI>
	parmB axCur
	parmB ayCur
	parmW chPut		;* could be double byte
	parmW diCur
cBegin	CharOutAbs

	StartPublic

	AssertUp

	PrepareDraw axCur,ayCur		;* sets ES:DI
	lea	si,chPut

	mov	cx,1			;* 1 character TextOut
ifdef	KANJI
	mov	al,ds:[si]		;* get first byte
	JmpNotDbc single_char_out
	inc	cx
single_char_out:
endif	;KANJI

	mov	dx,screenOffset mpdmnpfnDrawTO
	mov	bx,diCur
	cCall	DoDraw			;* perform Text Out

	cCall	FinishDraw

put_ch_end:
	AssertUp

	StopPublic

cEnd	CharOutAbs


ifdef	DRAW_MODE_MINIMIZE

;*****************************************************************************

;*	* * * Drawing info tables * * *
;*	* Drawing routine table for TextOut
mpdmnpfnDrawTO:
	DW	TO_dmTFB		;* Normal
	DW	TO_dmT			;* Text only
	DW	InvalidMode		;* attribute only for TextOut => bogus
	DW	InvalidMode		;* foreground only
	DW	InvalidMode		;* background only
	DW	InvalidMode		;* text & foreground
	DW	InvalidMode		;* text & background
	DW	InvalidMode		;* Text Map background
	DW	InvalidMode		;* Text Map foreground
	DW	InvalidMode		;* Map background
	DW	InvalidMode		;* Map foreground
	DW	InvalidMode		;* Map attr: back 2 back, fore 2 fore
	DW	InvalidMode		;* Map attribute to attribute

;*	* Drawing routine table for FillRectangle
mpdmnpfnDrawFR:
	DW	FR_dmTFB		;* Normal
	DW	InvalidMode		;* Text only
	DW	FR_dmFB			;* ca only
	DW	InvalidMode		;* foreground only
	DW	InvalidMode		;* background only
	DW	InvalidMode		;* text & foreground
	DW	InvalidMode		;* text & background
	DW	InvalidMode		;* Text Map background
	DW	InvalidMode		;* Text Map foreground
	DW	InvalidMode		;* Map background
	DW	InvalidMode		;* Map foreground
	DW	InvalidMode		;* Map attr: back 2 back, fore 2 fore
	DW	InvalidMode		;* Map attribute to attribute

ifdef	KANJI
;*	* Drawing routine table for FillRectangle for DBCS fill
;*	* (attribute only functions stay the same)
mpdmnpfnDrawFR_DBCS:
	DW	FR_dmTFB_DBCS		;* Normal
	DW	InvalidMOde		;* Text only
	DW	FR_dmFB			;* ca only (same as normal)
	DW	InvalidMode		;* foreground only
	DW	InvalidMode		;* background only
	DW	InvalidMode		;* text & foreground
	DW	InvalidMode		;* text & background
	DW	InvalidMode		;* Text Map background
	DW	InvalidMode		;* Text Map foreground
	DW	InvalidMode		;* Map background
	DW	InvalidMode		;* Map foreground
	DW	InvalidMode		;* Map attr: back 2 back, fore 2 fore
	DW	InvalidMode		;* Map attribute to attribute
endif	;KANJI

else	; !DRAW_MODE_MINIMIZE

;*****************************************************************************

;*	* * * Drawing info tables * * *
;*	* Drawing routine table for TextOut
mpdmnpfnDrawTO:
	DW	TO_dmTFB		;* Normal
	DW	TO_dmT			;* Text only
	DW	InvalidMode		;* attribute only for TextOut => bogus
	DW	TO_dmF			;* foreground only
	DW	TO_dmB			;* background only
	DW	TO_dmTF			;* text & foreground
	DW	TO_dmTB			;* text & background
	DW	TO_dmTMb		;* Text Map background
	DW	TO_dmTMf		;* Text Map foreground
	DW	TO_dmMb			;* Map background
	DW	TO_dmMf			;* Map foreground
	DW	TO_dmMfb		;* Map attr: back 2 back, fore 2 fore
	DW	TO_dmMAttr		;* Map attribute to attribute

;*	* Drawing routine table for FillRectangle
mpdmnpfnDrawFR:
	DW	FR_dmTFB		;* Normal
	DW	FR_dmT			;* Text only
	DW	FR_dmFB			;* ca only
	DW	FR_dmF			;* foreground only
	DW	FR_dmB			;* background only
	DW	FR_dmTF			;* text & foreground
	DW	FR_dmTB			;* text & background
	DW	FR_dmTMb		;* Text Map background
	DW	FR_dmTMf		;* Text Map foreground
	DW	FR_dmMb			;* Map background
	DW	FR_dmMf			;* Map foreground
	DW	FR_dmMfb		;* Map attr: back 2 back, fore 2 fore
	DW	FR_dmMAttr		;* Map attribute to attribute

ifdef	KANJI
;*	* Drawing routine table for FillRectangle for DBCS fill
;*	* (attribute only functions stay the same)
mpdmnpfnDrawFR_DBCS:
	DW	FR_dmTFB_DBCS		;* Normal
	DW	FR_dmT_DBCS		;* Text only
	DW	FR_dmFB			;* ca only (same as normal)
	DW	FR_dmF			;* foreground only
	DW	FR_dmB			;* background only
	DW	FR_dmTF_DBCS		;* text & foreground
	DW	FR_dmTB_DBCS		;* text & background
	DW	FR_dmTMb_DBCS		;* Text Map background
	DW	FR_dmTMf_DBCS		;* Text Map foreground
	DW	FR_dmMb			;* Map background
	DW	FR_dmMf			;* Map foreground
	DW	FR_dmMfb		;* Map attr: back 2 back, fore 2 fore
	DW	FR_dmMAttr		;* Map attribute to attribute.
endif	;KANJI

endif	; !DRAW_MODE_MINIMIZE

;*****************************************************************************

;********** DoDraw **********
;*	entry : ES:DI => screen location
;*		DX = pointer to table (mpdmnpfnDrawXX)
;*		CX = # of screen locations
;*		BX = di (drawing info) : BH = dm, BL = isa
;*		DS:SI => string (Text Out variant)
;*		 (DS => default DS (==SS))
;*		non-kanji LOBYTE(SI) = fill character (Fill Rectangle variant)
;*		kanji SI = fill double byte character (double byte Fill variant)
;*		D flag cleared !!
;*		ayDrawing and axDrawFirst set up !
;*		for overlap pwndCur is the current window (0=>draw always)
;*	* Prepare & call draw routine
;*	exit : ES:DI => after last character/attrib munged over
;*	TRASHES SI !!!!

do_draw_end1:
	jmp	do_draw_end

cProc	DoDraw,<NEAR,ATOMIC>,<BP>
cBegin	DoDraw

	AssertUp
	Assert <caSa EQ rgcaFill+1>		;* caSa MUST be in high byte

	Save	<es, bx, cx, dx>
	cCall	insj.lpfnPrepUpdateCsdInsj, <ayDrawing, axDrawFirst, cx, di, fRestoreDbcs>

	jcxz	do_draw_end1			;* trivial case

ifdef	MOUSE_TEXT
;*	* If ayDrawing == ayMouse{new} then kill mouse
	mov	al,ayMouse
	cmp	al,ayDrawing
	jne	not_drawing_over_mouse
else	; MOUSE_TEXT
;*	* If ABS(ayDrawing - ayMouse{new}) = FE,FF,0,1,2 then kill mouse
	mov	al,ayMouse
	sub	al,ayDrawing
	add	al,2				;* 0, 1, 2, 3, 4 => kill it
	cmp	al,5
	jae	not_drawing_over_mouse
endif	; MOUSE_TEXT
;*	* We may be drawing over mouse
	mov	al,0ffh				;* set value
	xchg	fMouseLockedOut,al		;* set flag, get old contents
	or	al,al
	jnz	already_locked_out
;*	* Turn mouse off
	xor	ax,ax				;* turn off
	Save	<bx,cx,dx>
	cCall	FEnableMouse,<ax>
	mov	fMouseLockedOut,al		;* save old state
already_locked_out:

not_drawing_over_mouse:

	Assert	<SIZE SA EQ 2>
	mov	ah,bh				;* ah = dm
	xor	bh,bh
	shl	bx,1				;* bx = isa * sizeof(SA)
ifdef	SCREEN_FFONT
	Assert	<SIZE SA EQ 2>			;* sizeof(SA) == sizeof(FFONT)
	mov	bp,[bx]+dataOffset mpisaffont
	mov	ffontCur,bp
endif	;SCREEN_FFONT
	mov	bp,[bx].rgcaFill+dataOffset rgsa;* bp = rgcaFill, bp(high) = caSa
	mov	bl,ah				;* ah = bl = dm
	shl	bx,1				;* bl = dm * sizeof(PROC NEAR)
						;*  lose the fdmKeepFfont bit
	xor	bh,bh
	add	bx,dx				;* bx = &mpdmnpfnDrawXX[dm]
	mov	bx,cs:[bx]			;* table look up procedure

ifdef	SCREEN_FFONT
;*	* ah = dm
	or	ah,ah				;* fdmKeepFfont bit set ?
	js	no_draw_ffont			;* keep the old FFONT
	cmp	fFontAvailable,0
	jz	no_draw_ffont
;*	* DI => start offset, CX = # of chars
	push	es
	push	di
	push	cx
	AssertNE instCur.psSecInst,0
	mov	es,instCur.psSecInst
	mov	ax,ffontCur
	rep stosw				;* fill in FFONT values
	pop	cx
	pop	di
	pop	es
no_draw_ffont:
endif	;SCREEN_FFONT

	push	di				;* start buffer offset
	push	cx				;* dax
	call	bx				;* call routine
	pop	cx
	pop	bx

;*	* inform driver that the line is done
	Save	<es>
	cCall	insj.lpfnDoUpdateCsdInsj, <ayDrawing, axDrawFirst, cx, bx, fRestoreDbcs>
					;* (ay, axFirst, dax, offFirst)
					;* note -- offset in primary!
do_draw_end:

cEnd	DoDraw


ifdef	KANJI
;*********** FlushDraw **********
;*	entry: n/a
;*	* update must be drawn NOW
;*	*  calls FinishDraw, sets hold update counter to zero
;*	exit: n/a

cPrivate FlushDraw, <ATOMIC>
cBegin	nogen

	mov	cHoldUpdate,0
	jmp	short finished_drawing

cEnd	nogen
endif	; KANJI


;*********** EndDraw **********
;*	entry: n/a
;*	* decrements the hold update counter which defers the call
;*	*  to DoUpdate.  If necessary, calls FinishDraw.
;*	exit: n/a

cPrivate EndDraw, <ATOMIC>
cBegin	EndDraw

ifdef	KANJI
	cmp	cHoldUpdate,0		;* FlushDraw may occur at any level of
	je	finished_drawing	;*  nesting, stop cHoldUpdate < 0
endif	; KANJI

	dec	cHoldUpdate
	jnz	not_finished_drawing
finished_drawing:			;* from FlushDraw aswell!!
	cCall	FinishDraw
not_finished_drawing:

cEnd	EndDraw

;*********** FinishDraw **********
;*	entry: n/a
;*	* drawing is done for now
;*	* inform the screen driver
;*	*  then turn mouse back on (if it was turned off)
;*	exit: n/a

cProc	FinishDraw, <NEAR, ATOMIC>
cBegin	FinishDraw

	test	cHoldUpdate,0ffh
	jnz	mouse_ok

	cCall	insj.lpfnDoneUpdateCsdInsj		;* ()

	mov	ayDrawing,ayNil			;* clear ayDrawing first
	test	fMouseLockedOut,0ffh
	jz	mouse_ok			;* it was not turned off
	cCall	FEnableMouse,<sp>

ifdef	DEBUG
	or	ax,ax				;* MUST have been turned off
	jz	clear_locked_out_flag
	cCall	CowAssertFailed
	DB	"mouse$"
endif	;DEBUG

clear_locked_out_flag:
	mov	fMouseLockedOut,al

mouse_ok:

cEnd	FinishDraw

;*****************************************************************************

;********** Draw Routines **********
;*	entry : ES:DI => screen (character, attribute at +1)
;*		CX = # of operations
;*		AL = new character (Fill Only)
;*		DS:SI => string (TextOut Only)
;*		DX = CGA video status port (3DAh)
;*		BP = rgcaFill (for map modes only) or high byte = caSa
;*		D flag cleared

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -