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

📄 paint.asm

📁 DOS 6.22 的源代码
💻 ASM
📖 第 1 页 / 共 2 页
字号:
	JMP	SHORT MAT3LP	;Loop
MATC3X:
	RET

CMPST:
	PUSH	SI		;Save tile string pointer
	MOV	BX,3
	PUSH	ES		
	PUSH	DS		
	POP	ES		
CMPST2:
	MOV	CL,DL		;Look for 3 in a row matches of B$GRPLAN bytes
	XOR	CH,CH
CMPST0: CMPSB			;Compare [SI],[DI]
	JNE	CMPST1		;Different already, exit with Z clear
	CALL	WRAPSI
	LOOP	CMPST0		;Matched B$GRPLAN in a row yet?
	MOV	DI,WORD PTR B$BGTLOC ;Yes: reset background pointer
	DEC	BX		;Matched 3 sets of B$GRPLAN in a row?
	JNZ	CMPST2		;No:
				;Yes: exit with Z set
CMPST1:
	POP	ES		
	POP	SI
	RET

WRAPSI:
	CMP	SI,AX		;Wrap around to beginning of tile string yet?
	JBE	NoWrap		;No:
	MOV	SI,WORD PTR B$TILLOC ;Yes: back to go
NoWrap: RET

;***
; TILATR
;	Set ATRBYT from tile and set B$TIPROG if current tile
;	attribute equals BG tile attribute.
; USES BX,DI
;****

TILATR:
	CMP	B$TILFLG,0
	MOV	BL,B$TILPTR
	JNZ	B$TILAT1	;Update ATRBYT
	RET			;do nothing if not tile

;***
; TILNDD
;	Decrement Tile index
;	and store tile in ATRBYT if B$TILFLG True...
; USES AX,BX
;****

TILNDD:
	CMP	B$TILFLG,0
	JNZ	TILNDD1 	;do nothing if not tile
	RET
TILNDD1:
	DEC	B$TILNDX 	;index is one less
	MOV	BL,B$TILPTR	;get offset to fground tile string
	OR	BL,BL		;At beginning of tile string?
	JNZ	TILDN1		;Brif not underflowing
	MOV	BL,B$TILHGT	;get tile height
	DEC	BL		;make 0-relative
	MOV	B$TILNDX,BL	;put into index
	MOV	BL,B$TILLEN	;else wrap to top end
	INC	BL		;make 1 based
TILDN1:
	SUB	BL,B$GRPLAN	;Decrement index to beginning of prev tile
	JMP	SHORT TILND2	;Update index, ATRBYT


PNTERR:
	MOV	B$TILFLG,0	;Turn Tiling off
	JMP	B$ERR_FC


;***
; TILNDI
;	Increment Tile index (called after DOWNC)
;	and store tile in ATRBYT if B$TILFLG True...
; USES AX,BX
;****
TILNDI:
	CMP	B$TILFLG,0
	JNZ	TILNDI1 	;do nothing if not tile
	RET
TILNDI1:
	INC	B$TILNDX 	;increment tile pixel index
	MOV	BL,B$TILPTR	;get fground tile byte offset
	ADD	BL,B$GRPLAN	;Increment index to beginning of next tile
	CMP	BL,B$TILLEN
	JBE	TILND2		;Brif not overflowing
	XOR	BL,BL		;else wrap to bottom end
	MOV	B$TILNDX,BL	;also clear tile pixel index
TILND2:
	MOV	B$TILPTR,BL	;update tile byte offset pointer

;***
; B$TILAT1
;
;****

cProc	B$TILAT1,<NEAR>,<SI>	
cBegin				
	MOV	BH,0		;[BL]=[BL]*GRPLAN, [BH]=0
	ADD	BX,WORD PTR B$TILLOC
	MOV	SI,BX		;SI points into tile string
	MOV	DI,WORD PTR B$BGTLOC ;DI points into background string
	MOV	B$TIPROG,0	;Clear progress flag
	XOR	BH,BH
TILAT2: INC	BH
	CMP	BH,B$GRPLAN
	JA	TILAT4		;For BH = 1 to gplanes
	MOV	BL,[SI] 	;Get curr tile attr
	PUSH	BX
	CALL	[b$SetTile]	;Set OEM's 'ATRBYT' to tile attr
	POP	BX
	CMP	BL,[DI] 	;Compare FG attr to BG attr
	JNZ	TILAT3		;Brif not equal
	INC	B$TIPROG 	;Count matches
TILAT3:
	INC	SI		;Check next planes bytes
	INC	DI
	JMP	SHORT TILAT2	;next BH
TILAT4:
	MOV	BL,B$TIPROG
	MOV	B$TIPROG,0
	CMP	BL,B$GRPLAN	;Did all FG match BG?
	JNE	TILAT6		;No:  not all matched so say none did.
	MOV	B$TIPROG,1	;Yes: flag all matched
TILAT6:
cEnd				


	PAGE
	SUBTTL	PAINT QUEUE ROUTINES

cProc	B$INTQNOCPCT,<PUBLIC,NEAR>,<BX,DX>	
cBegin						

;	PUSH	BX		;save registers...
;	PUSH	DX		
;	cCALL	B$STGETFRESIZ	;get size of free string
;	OR	BX,BX		;test if no free string
;	JZ	PQOMER		;if not, give out of memory error
;	cCALL	B$STALCTMP	; Allocate all string space as temporary

	cCALL	B$STALCMAXTMPNC	; Allocate max-string w/o compaction
	JMP	SHORT INTQUE_COMMON ;jump to common code point

cEnd	<nogen>			; End of B$INTQNOCPCT

	PUBLIC	B$INTQUE

B$INTQUE:
	PUSH	BX		;Save x coord
	PUSH	DX		;SAVE Y COORD
	CALL	B$STALCMAXTMP	;allocate maximum temporary string
INTQUE_COMMON:			
	MOV	AX,0[BX]	;AX:=size of free string space
	MOV	CX,2[BX]	;CX:=location of free string space
	CMP	AX,9		;is temp string too small?
	JB	TEMP_TOO_SMALL	;if so, do not subtract
	SUB	AX,9		;give string room for test
TEMP_TOO_SMALL:

;Note: B$GY_OLD is the previous x coord accumulator.  Since this variable is
;never used in the PAINT statement, it is used here to save the location
;of the temporary string being used for the paint queue.
	MOV	B$GY_OLD,CX	;save string location in B$GY_OLD
	ADD	CX,AX		;CX points just past end of free string
	DEC	CX		;CX=highest byte of in-use string space
				;omit check for overflow
;Note: B$GX_OLD is the previous y coord accumulator.  Since this variable is
;never used in the PAINT statement, it is used here to save the pointer to
;the end of the temporary string being used for the paint queue.
	MOV	B$GX_OLD,CX	;Save this value in B$GX_OLD
	CALL	B$STDALCTMP	;mark temp string as deallocated
	CMP	AX,18d
	JNB	INTQU3		;Ok if at least 18 bytes (2 entries)
PQOMER:
	JMP	B$ERR_OM	  ; else Out of Memory
INTQU3:
	MOV	WORD PTR B$PQLEN,AX ;len is free size
	MOV	WORD PTR B$PQNUM,0 ;present number is 0
	XCHG	AX,DX		;AX:=beginning of usable free space
	MOV	WORD PTR B$PQGET,AX ;Init head
	MOV	WORD PTR B$PQPUT,AX ; and tail
	POP	DX		;Restore y coord
	POP	BX		;Restore X coord
	RET

; PUTQ - Enqueue entry in paint queue
; Entry - AX,BX,CX = OEM's graphics cursor
;	  SI = B$SKPCNT
;	  DL = Direction (and tiling) flag
; Exit	- B$PQNUM,B$PQPUT updated
; AX,DI Used
DbPub	PUTQ			
PUTQ:
	PUSH	ES		
	PUSH	DS		
	POP	ES		
	PUSH	DX
;added 1 line
	PUSH	SI
	PUSH	CX
	PUSH	BX
;added 1 line
	PUSH	AX
	ADD	WORD PTR B$PQNUM,9d ;len= len+9
	MOV	AX,WORD PTR B$PQLEN
	CMP	WORD PTR B$PQNUM,AX
	JNB	PQOMER		;Out of Memory if at end or higher
	MOV	AX,WORD PTR B$PQPUT ;[AX]= queue ptr
	CALL	WRAP		;check wrap
	MOV	DI,AX		;[DI]= queue ptr
	POP	AX
	CLD
	STOS	WORD PTR [SI]	;Graphics cursor
	POP	AX
	STOS	WORD PTR [SI]	;Graphics cursor
	POP	AX
	STOS	WORD PTR [SI]	;Graphics cursor
	POP	AX
	STOS	WORD PTR [SI]	;B$SKPCNT
;added 2 lines
	POP	AX
	STOSB			;Direction flag
	MOV	WORD PTR B$PQPUT,DI
	POP	ES		
	RET

WRAP:
	PUSH	AX


	ADD	AX,9
;Note: B$GX_OLD is the previous x coord accumulator.  Since this variable is
;never used in the PAINT statement, it is used here to save the location
;of the temporary string being used for the paint queue.
	CMP	AX,WORD PTR B$GX_OLD ;Are we at end of free space?

	POP	AX		;Restore AX
	JB	WRAPX		;Brif not off end of queue


;Note: B$GY_OLD is the previous y coord accumulator.  Since this variable is
;never used in the PAINT statement, it is used here to save the pointer to
;the end of the temporary string being used for the paint queue.  This
;value is set at the beginning of B$INTQUE.
	MOV	AX,B$GY_OLD	;else set to beginning of queue

WRAPX:
	RET

; GETQ - Dequeue entry from paint queue
; Entry - none
; Exit	- AX,BX,CX = OEM's graphics cursor
;	  SI = B$SKPCNT
;	  DL = Direction (and tiling) flag
;	  B$PQNUM,B$PQGET updated
; No other registers used.
DbPub	GETQ			
GETQ:
	MOV	DL,0		;preset "Direction=0" in case no entries
	CMP	WORD PTR B$PQNUM,0
	JZ	GETQX		;Brif empty
	SUB	WORD PTR B$PQNUM,9d ;len = len-9
	MOV	AX,WORD PTR B$PQGET ;[AX]= dequeue ptr
	CALL	WRAP		;check wrap
	MOV	SI,AX		;[SI]= dequeue ptr
;added 3 lines
	CLD
	LODS	WORD PTR [SI]	;Graphics cursor
	PUSH	AX
	LODS	WORD PTR [SI]	;Graphics cursor
	MOV	BX,AX
	LODS	WORD PTR [SI]	;Graphics cursor
	MOV	CX,AX
	LODS	WORD PTR [SI]	;B$SKPCNT
	PUSH	AX
;added 2 lines
	LODSB			;Direction flag
	MOV	DL,AL
	MOV	WORD PTR B$PQGET,SI
;added 2 lines
	POP	SI		;SI = B$SKPCNT
	POP	AX
GETQX:
	RET

	PAGE
	SUBTTL	COMPILER ENTRY POINTS FOR PAINT

; PAINT - FILL AN AREA WITH COLOR
;
; SYNTAX: PAINT [STEP](X,Y)[,<iexp>[,iexp]]|[,<sexp>[,<iexp>[,<sexp>]]]
;	where <iexp>=integer expression, <sexp>=string expression
;

;***
;B$PAIN - Process PAINT statement without tiling
;
;Purpose:
;	This routine will be called by the parsing routine PAINT in PRSG86
;	in the interpreter version or by the compiler in the compiler version
;	if the PAINT statement scanned does not contain a paint tile
;	attribute but uses a integer paint color instead.  The call to
;	BNDS_CHK tests the start coordinates of the PAINT against the current
;	viewport boundaries.  The paint and border colors are checked for
;	validity before the jump to B$PAINTBEG begins the actual painting.
;
;Entry:
;	Color	= paint color spec or -1 if default
;	Border	= border color spec or -1 if default
;Exit:
;	None.
;Uses:
;	Per convention
;Exceptions:
;	Control may be transfered to B$ERR_FC
;****
cProc	B$PAIN,<PUBLIC,FAR>,<SI,DI> 
parmW	Color			
parmW	Border			
cBegin				

	CALL	B$SCINIT	; init screen if not already done
	cCall	B$COORD1	;do any necessary translations
	MOV	BX,Color	;[BX] = paint color
	MOV	DX,Border	;[DX] = border color
	CALL	OLD_PA1 	; Perform
cEnd				


OLD_PA1:			; Entry point for PAINT with no tiling
	MOV	B$TILFLG,0	;tiling is not active
	MOV	B$TIPROG,0	
	CALL	B$INTQUE 	;Init the Queue
	PUSH	DX		;Save border color
	CALL	BNDS_CHK	;Check if coordinates are inside
				;screen or viewport
	JC	MAPIT		
	JMP	DONT_PAINT	;Don't PAINT if coordinates out of bounds
MAPIT:				
	push	bx		;preserve bx across call to MapXYC
	CALL	[b$MapXYC]	;Graphics Cursor:=(CX,DX)
	pop	ax		;restore paint color
	POP	DX		;Restore border color
	CALL	B$CLRATR 	;Returns paint color attribute in AL
	CMP	DX,-1		;Is border color defaulted?
	JZ	BRDCHK		;Yes: AL contains valid paint color which is
				;border color default when no tiling
	MOV	AX,DX		;AX:=border color
BRDCHK: 			;check for valid border color
	CALL	B$PaintInit	;OEM check for legal border color
	JC	ERR_PAINT	;carry set if invalid border color
	JMP	B$PAINTBEG	;Go begin painting

;***
;B$PNTC - Process PAINT statement with tiling option
;
;Purpose:
;	This routine will be called if the PAINT statement scanned contains
;	a paint tile attribute instead of an integer paint color.  The
;	call to BNDS_CHK checks to see if the PAINT coordinates are within
;	bounds of the current viewport (the screen if there is no viewport).
;	The call to FGSTRINI initializes a buffer area (b$Buf1) to the tile
;	specified in the PAINT statement or to the default value.  B$ClrBgStr
;	initializes the default background string.  TILEINIT checks for a
;	valid border color, initializes B$TILNDX to index the appropriate byte
;	of the tile string, initializes ATRBYT (variable containing tile
;	mask) and checks for three consecutive matches between the foreground
;	and background tiles.  If everything is ok the jump to B$PAINTBEG is
;	taken to begin the actual painting procedure.
;Entry:
;	sdTile = sd for tiling string
;	Border = border spec or -1 if default
;	sdBkgd = sd for background string or -1 if none
;Exit:
;	None.
;Uses:
;	None.
;Exceptions:
;	B$ERR_FC
;****
cProc	B$PNTC,<PUBLIC,FAR>,<ES,SI,DI>	
parmSD	sdTile			
parmW	Border			
parmSD	sdBkgd			
cBegin				

	CALL	B$SCINIT	; init screen if not already done

	cCall	B$COORD1	;do any necessary translations
	GetpSD	BX,sdTile	;[BX] = psdTile
	GetpSD	CX,sdBkgd	;[CX] = psdBkgd
	MOV	DX,Border	;[DX] = border color
	PUSH	DS		; set es=ds
	POP	ES		
	CALL	OLD_PA2 	; Perform

cEnd				

ERR_PAINT:
	MOV	B$TILFLG,0	;Turn Tiling off
	JMP	B$ERR_FC


OLD_PA2:			; Entry point for PAINT with tiling
	MOV	B$TILFLG,-1	;Tile is active
	PUSH	DX		;Save border color
	PUSH	CX		;Save ptr to backgrd string descriptor
	CALL	B$INTQUE 	;Init the Queue
	CALL	BNDS_CHK	;Check if coordinates are inside screen or viewport
	JNC	POPNRET 	;coords out of bounds: don't do PAINT
	push	bx		;preserve bx across mapxyc call
	CALL	[b$MapXYC]	;Graphics Cursor:=(CX,DX)
	pop	bx		;restore ptr to fg string desc
	CALL	FGSTRINI	;Initialize foreground paint string
	POP	BX		;Restore ptr to background string descriptor
	CALL	B$ClrBgStr	;initialize null string for background
	CMP	BX,-1		;is background string defaulted?
	JZ	TILEINIT	;yes: branch to tile ATRBYT initialization
	CALL	BGSTRINI	;initialize background string
	CALL	MATCH3		;check for three consecutive matching
				;bytes in paint tile and background
				;tile and abort if found
	JC	ERR_PAINT	;Three matches found: issue error
TILEINIT:			;Tile initialization
	POP	AX		;Restore border color attribute
	CMP	AX,-1		;Is border color defaulted?
	JNZ	BORDER_CHK	;NO: Go check for valid border color
	STC			;Set carry
	CALL	B$GETFBC 	;Get foreground color in AL
BORDER_CHK:
	CALL	B$PaintInit	;OEM routine to check for valid border color
	MOV	DX,WORD PTR B$GYPOS ;DX:=current y coord
	CALL	B$SetTileIndex ;set B$TILNDX to proper byte of tile string
	CALL	TILATR		;set up tiling mask in ATRBYT
	JMP	B$PAINTBEG	;Valid border: go begin painting
POPNRET:			;Pop stack and abort PAINT statement
	POP	CX		;pop backgrd string ptr
DONT_PAINT:
	POP	DX		;pop border color
	MOV	B$TILFLG,0	;clear tiling flag
	RET			;Return

;***
; BNDS_CHK - routine checks for valid PAINT coordinates,
; Purpose:
;	To see if the coordinates specified in the PAINT statement
;	are within the current viewport.  May be called from B$PAIN
;	or B$PNTC.
;
;	If clipping is supported:
;		If the coordinates are inside the viewport, then continue
;		to process the PAINT statement, otherwise, return with
;		carry clear to indicate that PAINT statement should be
;		aborted without issuing an error message.
;	If clipping is not supported:
;		If the coordinates are inside the viewport, then continue
;		to process the PAINT statement, otherwise, issue a
;		function call error.
;
; Entry:
;	None.
; Exit:
;	Graphics cursor updated if coordinates inside current viewport.
; Modifies:
;	AX,CX,DX.
;****

BNDS_CHK:
	MOV	CX,WORD PTR B$GXPOS ;CX:=Graphics accumulator x position
	MOV	DX,WORD PTR B$GYPOS ;DX:=Graphics accumulator y position
	PUSH	BX		;Save paint parameter
	CALL	B$INVIEW 	;Returns carry set if coords within
				;current viewport
	POP	BX		;Restore paint parameter
	RET			;return with carry flag


sEnd	GR_TEXT 		
	END

⌨️ 快捷键说明

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