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

📄 llega.asm

📁 [随书类]Dos6.0源代码
💻 ASM
📖 第 1 页 / 共 4 页
字号:
	JZ	COLCM7
	CALL	B$EgaTILLFT
	JMP	SHORT COLCM8
COLCM7:
	CALL	B$EgaSETCMP	;set color compare register to paint attribute
	CALL	PIXLF3		;see whether any pixels in range will change
COLCM8:
	POP	SI		;restore leftmost address to SI
	POP	DI		;restore rightmost address to DI
	OR	CL,CL		;returns CL non-zero if changes needed
	JZ	BRDEX2

;	we found at least 1 pixel to change, so set entire range
;	set pixels-changed flag, set up write mode 2

	XOR	CH,CH
	NOT	CH		;set to FF as decrement flag
	STD			;for SCANL, decrement from DI
	CALL	B$EgaPAINPX
	CLD
BRDEX2:
	CALL	B$EgaPIXCNT	;returns # pixels "painted" in BX
BRDEX3:
	CALL	B$ResetEGA
cEnd

;***
; ScanRX
;Purpose:
;	Starting with the current pixel, search right until:
;		(1) a non-border pixel is found
;		(2) [DX] pixels have been tested
;		(3) the viewport edge is encountered
;
;	If (2) or (3) terminated the scan, exit with:
;		DX = remaining border bount = 0
;
;	If (1) terminated the scan, scan and paint non-border pixels until:
;		(1) the viewport edge is encountered (edge painted)
;		(2) a border pixel is encountered (border not painted)
;
;	This version supports PAINT for the odd/even EGA modes (bios mode
;	10H with 64K of memory, and monochrome bios mode F).  It differs
;	from SCANR2 in its use of the Color Don't Care register in
;	conjunction with screen reads.	This is necessary because if the
;	planes representing the even bytes and those representing the odd
;	bytes are not disabled during color compares for odd and even bytes,
;	respectively, the color compare is made as the sum of the bits set
;	for each even byte and its odd successor, all four planes at one
;	address.
;Entry:
;	DX		   = count of border pixels which may be skipped
;	b$AddrC, b$MaskC = starting pixel
;	b$PaintBorder	   = attribute of paint region border
;	b$AttrC	   = attribute to paint
;	B$REOFST, B$VRMASK   = right viewport edge
;Exit:
;	BX		   = number of pixels painted
;				(whether or not they changed color)
;	CL		   = 0 iff no pixels changed color
;	DX		   = remaining border pixel count
;	b$OffC, b$MaskC  = the last non-border pixel examined/painted
;	SI, AL		   = the first non-border pixel encountered
;Uses:
;	per conv.
;Exceptions:
;
;****************************************************************************
DbPub	ScanRX
cProc	ScanRX,<NEAR>,<ES>
cBegin
;	set up EGA registers for color compare read
;	point ES:[SI] to screen memory, b$MaskC in CH
;	CL = 0 (pixels changed flag)

	CALL	B$EgaScanInit	;setup

;	Initial task is to set up a mask for specifying which planes
;	we want to read when doing color compare reads.	For even bytes,
;	we need to specify 0's in bits 1 and 3 (color don't care planes
;	1 and 3), vice versa for odd bytes.  For convenience in coding,
;	we set up an 8-bit mask in CL and rotate right as we move across
;	the screen.

	MOV	BX,DX		;decrement BX instead of DX (needed for OUTs)
	MOV	CL,10101010B	;assume start mask 10101010
	TEST	SI,1		;check whether odd or even byte
	JNZ	COLCOM		;if odd, we're in business
	ROR	CL,1		;else 010101
COLCOM:
	MOV	DX,GRPADD	;address of index port
	MOV	AL,LOW CDCREG	;Color Don't Care register

	OUT	DX,AL
	INC	DX		;data port address
	MOV	AL,CL		;mask indicating planes to ignore (=0)
	OUT	DX,AL		;set up initial Color Don't Care planes

;	perform color compare on first byte

	MOV	AL,ES:[SI]	;bits set where border found
	EGAINT10STI		;read is done, reenable ints if EGAINT10

;	Starting at entry cursor, search right looking for non-border,
;	viewport edge, or end-of-byte as long as DX does not decrement to 0.

	XOR	AH,AH		;initialize viewport mask to 0
SRCRT3:
	CMP	SI,B$REOFST	;check whether we are in viewport edge byte
	JNZ	NOTVP3
	MOV	AH,B$VRMASK	;if so, get viewport edge mask
NOTVP3:

;	While border...

	TEST	AL,CH		;compare color compare mask with b$MaskC
	JZ	ENDRT3		;if pixel not border, exit loop

;	and not viewport edge...

	TEST	AH,CH		;compare viewport edge mask with b$MaskC
	JNZ	ENDRT3		;if edge found, exit

;	and BX is greater than 0...

	DEC	BX		;contains # pixels which can be skipped
	JZ	ENDRT3		;in search for non-border pixel

;	and not off the edge of the byte...

	ROR	CH,1		;shift bit mask right

;	repeat the search

	JNB	NOTVP3

;	end of first byte.

	INC	SI		;next byte address
	ROR	CL,1		;rotate mask for next Color Don't Care
	MOV	AL,CL
	OUT	DX,AL		;next compare with alternate planes disabled
	MOV	AL,ES:[SI]
	EGAINT10STI		;reenable ints between bytes if EGAINT10
	MOV	CH,80H		;mask now 1000/0000 for next search
	JMP	SHORT SRCRT3

;	either (not border) OR (viewport edge) OR (DX = 0)

ENDRT3:
	MOV	DX,BX		;return decremented value to proper register
	TEST	AL,CH		;border?
	JZ	NTBRD3		;if so, we are either at viewport edge
	XOR	DX,DX		;or have skipped DX pixels and therefore
	MOV	BX,DX		;should exit with info as initialized
	XOR	CL,CL		;restore old value to flag
	JMP	SHORT SCNEX3	

;	Look for viewport edge to determine how many bytes to look
;	through for border pixel.

NTBRD3:
	PUSH	DX		;store skipcount for later
	XOR	DX,DX		;use to count pixels painted
	MOV	b$SaveCa,SI	;we have a new CSAVE
	PUSH	SI		;store copy of first byte address
	MOV	b$SaveCm,CH
	CALL	B$EgaCHKBTR	;set up byte for write, and count some pixels
				;(AH = viewport edge mask if any)
	MOV	BL,BH		;store first bit mask in BL
	XOR	BH,BH		;zero BH until last byte bit mask if any
	XOR	BP,BP		;start whole byte count at 0
	MOV	DI,B$REOFST
	SUB	DI,SI		;viewport edge address - first byte address
	TEST	BL,1		;if last bit not set, we found border for sure
	JZ	WRTPX3		;if just one byte, we're done
	OR	DI,DI		;check also if we hit viewport edge
	JZ	WRTPX3		;if so, also done

;	else look through DI bytes for border (this includes viewport
;	edge byte)

	DEC	BP		;start increment at -1
	MOV	CH,80H		;start each byte at left edge
	PUSH	DX		;save accumulating bit count
	MOV	DX,GRPADD+1	;prepare to send Color Don't Care data
SCANM3:
	INC	BP		;whole byte count
	INC	SI		;point to byte
	ROR	CL,1		;rotate plane mask
	MOV	AL,CL
	OUT	DX,AL
	MOV	AL,ES:[SI]	;read each byte for color compare
	EGAINT10STI		;read is done, reenable ints if EGAINT10
	OR	AL,AL		;check for occurrence of border pixel(s)
	JNZ	BRDPX3		;set up last byte
	DEC	DI		;decrement to 0 to include last byte
	JNZ	SCANM3		;go check out this byte
;	MOV	AH,B$VRMASK	;if edge of viewport, get viewport mask
				;and proceed to set up byte for write
BRDPX3:
				;may have found border, viewport
				; edge, or have both in same byte
	CMP	SI,B$REOFST	;heck if this is edge byte
	JNZ	BRDFD3
	MOV	AH,B$VRMASK	;if found, install viewport edge mask
BRDFD3:
	POP	DX		;restore pixel count
	CALL	B$EgaCHKBTR	;set up byte for write

;	most recent call to CHKBTR has generated new cursor location and mask

WRTPX3:
	MOV	b$OffC,SI
	MOV	b$MaskC,CH
	POP	DI		;restore leftmost byte address
	PUSH	DI		;save a copy for leftmost add. for painting
	PUSH	SI		;save copy of rightmost address also
	MOV	SI,DI		;leftmost byte address in SI for PIXRGT
	MOV	DI,BP		;PIXRGT will use DI to count whole bytes
	CMP	b$Tiling,0	;see whether tiling is on
	JZ	COLCM3
	CALL	B$EgaTILRGT
	JMP	SHORT COLCM4
COLCM3:
	CALL	B$EgaSETCMP	;set color compare register to paint attribute
	CALL	PIXRT3		;routine to determine whether any pixels change
COLCM4:
	POP	SI		;restore rightmost
	POP	DI		;and leftmost byte addresses
	OR	CL,CL		;non-zero indicates at least one must change
	JZ	NPNTR3
	XOR	CH,CH		;zero as increment flag
	CLD			;for SCANR, paint routine should increment REP
	CALL	B$EgaPAINPX	;set line
NPNTR3:
	CALL	B$EgaPIXCNT	;return # pixels "painted" in BX
	POP	DX		;skipcount in DX
SCNEX3:
	CALL	B$ResetEGA	;reset EGA registers for BIOS write mode 0
	MOV	SI,b$SaveCa	;return CSAVE
	MOV	AL,b$SaveCm
cEnd

	ASSUME	DS:NOTHING

;***
; Read_64K
;
;Purpose:
;	Support routine for NReadL_64K, reads one byte from screen
;	memory into AL.  Read from even plane even address, from
;	odd plane if odd address.
;Entry:
;	DS:SI = screen address
;Exit:
;	AL    = screen contents from address at ES:DI
;	DI    = incremented to next screen byte
;Uses:
;	per conv.
;Exceptions:
;******************************************************************************
DbPub	Read_64K
cProc	Read_64K,<NEAR>
cBegin
	EGAINT10CLI		;disable ints if using EGAINT10
	mov	al,RMPREG	;select read map select register
	out	dx,al
	inc	dx
	xor	al,al		;for plane computation
	ror	di,1		;carry = 1 if odd address
	adc	al,BasePlane	;base plane +1 iff odd address
	rol	di,1		;restore address
	out	dx,al		;set plane to read
	dec	dx
	lodsb			;read it (finally!!)
	EGAINT10STI		;reenable ints if using EGAINT10
cEnd

;***
; NReadL_64K
;
;Purpose:
;	Read a line of pixels from a specified plane to an array for
;	64K Screen mode 9 (odd/even color mode).
;Entry:
;	DS:SI = screen address
;	ES:DI = array address
;	CL    = array align shift count
;	CH    = mask for last partial byte
;	BP    = count of bits to read
;	BH    = plane to read from
;Exit:
;	ES:DI = updated to array byte past point used
;Uses:
;	per conv.
;Exceptions:
;******************************************************************************
DbPub	NReadL_64K
cProc	NReadL_64K,<NEAR>
cBegin
	MOV	DX,GRPADD	;address graphics controller
;the next 2 statements appear to be unnecessary, but I'm not totally sure.
;	MOV	AX,RWMREG	;r/w mode, [ah] = 0
;	OutWord 		;non color compare read
	shl	bh,1		;plane 0 = maps 0/1, plane 1 = maps 2/3
	mov	BasePlane,bh
	call	Read_64K	;preload hi byte
	mov	ah,al		;  to ah
NRdLoopX:
	call	Read_64K	;fill ax word with video bytes
	mov	bh,al		;this lo byte will become next hi byte
	rol	ax,cl		;align to array
	sub	bp,8		;8 bits done
	jbe	NRdLastX	;go if bit count exhausted
	mov	es:[di],ah	;save full byte
	inc	di		
	mov	ah,bh		;move lo byte (BH) to hi byte (AH)
	jnz	NRdLoopX	;loop if no offset overflow
	call	B$BumpES	;move array pointer over segment boundary
	jmp	short NRdLoopX	;go do another
NRdLastX:
	and	ah,ch		;strip unused bits from last byte
	mov	es:[di],ah	;save last byte
	inc	di		
	jnz	NRdDoneX	
	call	B$BumpES	;move array pointer over segment boundary
NRdDoneX:
cEnd

;***
; Write_64K
;
;Purpose:
;	Support routine for NWriteL_64K, writes one byte to screen
;	memory from AL.  Initializes EGA regs to appropriate plane and
;	vectors through [b$PutVector] which writes the byte after
;	applying any bitwise logic necessary.
;Entry:
;	ES:DI = screen address
;Exit:
;	None
;Uses:
;	per conv.
;Exceptions:
;******************************************************************************
DbPub	Write_64K
cProc	Write_64K,<NEAR>,<AX,DX>
cBegin
	push	ax
	MOV	DX,GRPADD	;address graphics controller
	mov	al,RMPREG	;select read map select register
	out	dx,al
	inc	dx
	xor	al,al		;for plane computation
	ror	di,1		;carry = 1 if odd address
	adc	al,BasePlane	;base plane +1 iff odd address
	rol	di,1		;restore address
	out	dx,al		;set plane to read
	MOV	DX,SEQADD	;address the sequencer
	MOV	AL,MMREG	;  map mask register
	out	dx,al
	inc	dx
	mov	al,b$PlaneMask ;get base plane mask
	and	al,MapMask	;with even/odd map mask
	and	al,0FH		;strip to nibble
	out	dx,al		;set plane to write
	rol	MapMask,1	;rotate even/odd mask for next byte
	pop	ax
.erre	ID_SSEQDS		;assumes ss = ds
	call	ss:[b$PutVector]   ;put the byte (finally!!)
cEnd

;***
; NWriteL_64K
;
;Purpose:
;	Write a line of pixels from an array to a specified plane for
;	64K Screen mode 9 (odd/even color mode).
;Entry:
;	ES:DI = screen address
;	DS:SI = array address
;	CX    = array align shift count
;	BP    = count of bits to write
;	BH    = plane to write to
;	DL    = last partial byte mask
;	DH    = first partial byte mask
;Exit:
;	DS:SI = updated to array byte past point used
;Uses:
;	per conv.
;Exceptions:
;******************************************************************************
DbPub	NWriteL_64K
cProc	NWriteL_64K,<NEAR>
cBegin
	rol	b$PlaneMask,1	;shift to next plane
	rol	b$PlaneMask,1
	mov	MapMask,01010101B	;setup map mask for even access
	test	di,1		;is it even?
	jz	IsEvenX 	;go if so
	rol	MapMask,1
IsEvenX:
	shl	bh,1		;plane 0 = maps 0/1, plane 1 = maps 2/3
	mov	BasePlane,bh
	push	dx
	mov	ah,dh		;first byte bit mask
	MOV	DX,GRPADD	;address graphics controller
	mov	al,BMKREG	;  bit mask register
	EGAINT10CLI		;disable ints if using EGAINT10 interface
	OutWord 		;set first partial byte mask
	pop	dx

	mov	ah,[si] 	;preload byte from array
	inc	si
	jnz	NWrOvfl1X	
	call	B$BumpDS	;move array pointer over segment boundary
NWrOvfl1X:
	ror	ax,cl		;align to video
	add	bp,cx
	sub	bp,8		;account for first partial byte
	jbe	NWrLastX	;go if last byte
	call	Write_64K
	mov	dh,0FFH 	;mask for whole bytes in the middle
	push	ax
	push	dx
	mov	ah,dh		;middle byte bit mask
	MOV	DX,GRPADD	;address graphics controller
	mov	al,BMKREG	;  bit mask register
	OutWord 		;set full byte mask for middle bytes
	EGAINT10STI		;reenable ints if using EGAINT10 interface
	pop	dx
	pop	ax
	jmp	short NWrLoopX2
NWrLoopX:
.erre	ID_SSEQDS		;assumes ss = ds
	EGAINT10CLI		;disable ints if using EGAINT10 interface
	call	Write_64K	;put the byte
	EGAINT10STI		;reenable ints if using EGAINT10 interface
NWrLoopX2:
	rol	ax,cl		;re-align to array
	xchg	ah,al
	cmp	cx,bp		;enough bits in this byte to finish
	jae	NWrOvfl2X	;go if so, don't load another
	mov	ah,[si] 	;fill ax word with array bytes
	inc	si
	jnz	NWrOvfl2X	
	call	B$BumpDS	;move array pointer over segment boundary
NWrOvfl2X:
	ror	ax,cl		;align to video
	sub	bp,8		;8 bits done
	ja	NWrLoopX	;go if bit count not exhausted
NWrLastX:
	push	ax
	and	dh,dl		;combine first|middle mask with end mask
	mov	ah,dh		;last byte bit mask
	MOV	DX,GRPADD	;address graphics controller
	mov	al,BMKREG	;  bit mask register
	EGAINT10CLI		;disable ints if using EGAINT10 interface
	OutWord 		;set first partial byte mask
	pop	ax
.erre	ID_SSEQDS		;assumes ss = ds
	call	Write_64K	;put the last byte
	EGAINT10STI		;reenable ints if using EGAINT10 interface
cEnd

	ASSUME	DS:DGROUP

;***
; B$xINITEGA - initialize EGA modes
;
;Purpose:
;	Added with revision [26].
;	Put the addresses of EGA screen mode support routines into the
;	dispatch table used by the screen statement.
;
;Entry:
;	None
;Exit:
;	ScreenTab updated
;Uses:
;	None
;Exceptions:
;******************************************************************************
cProc	B$xINITEGA,<FAR,PUBLIC> 
cBegin
	MOV	WORD PTR [b$ScreenTab + (7*2) + 1],OFFSET B$Screen7
	MOV	WORD PTR [b$ScreenTab + (8*2) + 1],OFFSET B$Screen8
	MOV	WORD PTR [b$ScreenTab + (9*2) + 1],OFFSET B$Screen9
	MOV	WORD PTR [b$ScreenTab + (10*2)+ 1],OFFSET B$Screen10
cEnd

sEnd	GR_TEXT

	END

⌨️ 快捷键说明

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