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

📄 llcgrp.asm

📁 [随书类]Dos6.0源代码
💻 ASM
📖 第 1 页 / 共 3 页
字号:
;
;Purpose:
;	This routine stores the internal form of the current tile
;	attribute for a specific plane.  This routine is called
;	N times for each line to be tiled, where N is the number
;	of planes (actually the value returned by B$TILEMOD).	If
;	not all the bytes for multiple plane systems are specified
;	by the BASIC programmer [b$SetTile] will be called with
;	a value of 0 for the remaining planes.
;
;	The tile attribute should be aligned to the current graphics
;	cursor before actually setting pixels in [b$ScanR] or [b$ScanL].
;
;	NOTE: b$SetTile is a variable through which the routine is
;	      indirectly called.
;
;Entry:
;	[BL] = internal form of the tile attribute
;	[BH] = which plane the attribute is for
;
;Exit:
;	b$AttrC set to tile attribute
;
;Uses:
;	Per Convention
;
;Exceptions:
;	None
;******************************************************************************

;***
;  b$ScanL - Paint pixels from cursor to the left
;OEM-interface routine
;
;Purpose:
;	Scan left beginning with the pixel to the left of cursor,
;	and paint pixels with the current attribute until:
;		(1) the viewport edge is encountered (edge painted)
;	     or (2) a border pixel is encountered (border not painted)
;
;	The border value is set in the call to B$PaintInit.  The viewport
;	edges are set when B$MapVWC is called.  Since this routine
;	is called multiple times for a single PAINT statement, it is
;	important that this routine be optimized for speed.  Any values
;	that can be precomputed should be done so in the routines
;	B$PaintInit and [b$PaintBound].
;
;	NOTE: b$ScanL is a variable through which the routine is
;	      indirectly called.
;
;Entry:
;	Graphics Cursor    = pixel to right of starting pixel
;Exit:
;	BX		   = number of pixels scanned
;	CL		   = 0 iff no pixels changed color
;	Graphics Cursor    = the last non-border pixel examined/painted
;
;Uses:
;	per convention
;
;Exceptions:
;	None
;******************************************************************************
;Our Entry Conditions:
;	b$PaintBorder	   = attribute of paint region border
;	b$AttrC	   = attribute to paint
;	B$LEOFST, B$VLMASK   = left viewport edge
;

;***
;  b$ScanR - Paint pixels from cursor to the right
;OEM-interface routine
;
;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 count   = 0
;		CL = pixels modified flag     = 0
;		BX = number of pixels painted = 0
;		Graphics Cursor returned to starting point.
;		Returned Cursor = Last cursor returned by [b$ScanR]
;
;	If (1) terminated the scan, start a new scan and paint non-border
;	pixels until:
;		(1) the viewport edge is encountered (edge painted)
;		(2) a border pixel is encountered (border not painted)
;
;	Return with:
;		DX = entry DX - # pixels searched before non-border found
;		CL = pixels modified flag
;		BX = number of pixels painted (even if no color change)
;		Graphics Cursor is at the last pixel examined
;			(either border or viewport edge)
;		Returned Cursor = Cursor Position at which the original
;				  scan was terminated.
;
;	NOTE: b$ScanR is a variable through which the routine is
;	      indirectly called.
;
;Entry:
;	DX		   = count of border pixels which may be skipped
;	Graphics Cursor    = starting pixel
;
;Exit:
;	BX		   = number of pixels painted
;				(whether or not they changed color)
;	CL		   = 0 iff no pixels changed color
;	DX		   = remaining border pixel count
;	Graphics Cursor    = the last non-border pixel examined/painted
;	AX, SI, DI	   = the first non-border pixel encountered
;			      AX = first byte of cursor
;			      SI = second byte of cursor
;			      DI = third byte of cursor
;Uses:
;	SI and DI are used for return values.
;
;Exceptions:
;	None
;******************************************************************************
;Our Entry Conditions:
;	b$PaintBorder	   = attribute of paint region border
;	b$AttrC	   = attribute to paint
;	B$REOFST, B$VRMASK   = right viewport edge
;

;***
; b$PutVector
;
;Purpose:
;	PUT action vectors. The PUT code vectors through this routine
;	to write bytes to the screen with the specified PUT action.
;	This vector is generally set up by the b$PutAction routine.
;
;	NOTE: b$PutVector is a variable through which the routine is
;	      indirectly called.
;
;Entry:
;	AH =	byte to write to screen.
;	DH =	mask
;	ES:DI = pointer to video memory
;
;Exit:
;	DI =	updated to point to next video byte
;
;Uses:
;Exceptions:
;******************************************************************************

sEnd	_DATA			

sBegin	GR_TEXT 		
	ASSUMES CS,GR_TEXT	

externNP B$GETDS		
externNP B$ErrorReturn 	

;*** 
; B$InitModeData
;
;Purpose:
;	Initialize mode-dependent data from a table.
;
;Entry:
;	CS:BX = pointer to table to match b$ModeData.
;	CX    = table length
;
;Exit:
;Uses:
;Exceptions:
;******************************************************************************

cProc	B$InitModeData,<PUBLIC,NEAR>,<SI,DI,DS,ES>
cBegin
	push	ds		;to DS:ModeData
	pop	es
	cmp	cx,TextDataLen	;a text entry?
	jne	InitTable	;go if not
	
	;when only the text data is initialized, set all of the graphics
	;function vectors to B$ErrorReturn which will just set carry
	;and return
	
	push	cx		
	mov	di,OFFSET DGROUP:GraphVectStart 
	mov	cx,GraphVectCnt 		
	mov	ax,GR_TEXTOFFSET B$ErrorReturn 
    rep stosw			
	pop	cx		
InitTable:
	mov	di,OFFSET DGROUP:b$ModeData
	push	cs		;from CS:BX
	pop	ds
	mov	si,bx
	cld
    rep movsb			;move it
; initialize foreground attribute to default
	push	es		
	pop	ds		;set DS=DGROUP for SetAttr
	mov	al,b$ForeColor ;get default foreground attribute
	call	[b$SetAttr]	;set attribute
	mov	b$BorderColor,0 ;clear border
cEnd


;***
; B$MapVWC - Change OEM viewport
;OEM-interface routine
;
;Purpose:
;	This routine is called each time the viewport is changed
;	to notify OEM dependent code of the current viewport
;	boundaries. Whenever B$MapVWC is called constants are
;	calculated and these constants will be used in other
;	OEM dependent routines to help speed up the PAINT routine.
;
;Entry:
;	[AX] = Minimum horizontal co-ordinate of viewport. (left edge)
;	[BX] = Maximum horizontal co-ordinate of viewport. (right edge)
;	[CX] = Minimum vertical co-ordinate of viewport. (top edge)
;	[DX] = Maximum vertical co-ordinate of viewport. (bottom edge)
;
;Exit:
;	None.
;
;Uses:
;	Per Convention
;
;Exceptions:
;	None.
;****
cProc	B$MapVWC,<PUBLIC,NEAR>,<DI>
cBegin
	PUSH	b$OffC 	;SAVE CURSOR OFFSET
	push	bx		;save viewport_right
	PUSH	AX
	XOR	AH,AH
	MOV	AL,b$MaskC	;SAVE CURSOR MASK
	MOV	DI,AX		;IN [DI]
	PUSH	DX		;SAVE DX, BCOS MAPXYC USES DX
	MOV	DX,CX		;get offset of (o,viewport-topedge)
	XOR	CX,CX
	CALL	[b$MapXYC]
	MOV	CX,b$OffC	;add b$BytesPerRow to this offset
	ADD	CX,b$BytesPerRow 
	MOV	B$VTOFST,CX	;and save in VTOFST (used in b$ChkUpC)
	POP	DX		;RESTORE DX
	XOR	CX,CX
	CALL	[b$MapXYC]	;get offset of (0,viewport-bottomedge)
	MOV	CX,b$OffC	;and svae it in VBOFST
	MOV	B$VBOFST,CX	;used in $TDOWNC
	POP	AX		;restore viewport_left
	MOV	CX,AX		;GET OFFSET AND MASK FOR THE
	XOR	DX,DX		;POINT (VIEWPORT_LEFT,0)
	CALL	[b$MapXYC]
	MOV	CX,b$OffC	;TRANSFER OFFSET AND MASK TO
	MOV	B$VLOFST,CX	;VLOFST AND VLMASK
	MOV	CL,b$MaskC
	MOV	B$VLMASK,CL
	pop	bx		;restore viewport_right
	MOV	CX,BX		;GET OFFSET AND MASK FOR THE
	XOR	DX,DX		;POINT (VIEWPORT_RIGHT,0)
	CALL	[b$MapXYC]
	MOV	CX,b$OffC	;TRANSFER OFFSET AND MASK TO
	MOV	B$VROFST,CX	;VROFST AND VRMASK
	MOV	CL,b$MaskC
	MOV	B$VRMASK,CL
	MOV	AX,DI		;RESTOR OLD CURSOR MASK
	MOV	b$MaskC,AL	;AND STORE IT BACK IN b$MaskC
	POP	b$OffC 	;RESTORE OLD OFFSET
cEnd

;***
; B$GetAspect - Get screen aspect ratio
;OEM-interface routine
;
;Purpose:
;	Return the screen aspect ratio.  Aspect ratio is used by CIRCLE
;	and DRAW to compensate for the possibility that pixels are of
;	unequal dimensions.  The ratio is returned as a fraction of 256.
;
;Entry:
;	None.
;
;Exit:
;	BX = 256 * aspect ratio
;	DX = 256 / aspect ratio
;
;Uses:
;	Per Convention
;
;Preserves:
;	AX, CX
;
;Exceptions:
;	None.
;****
cProc	B$GetAspect,<PUBLIC,NEAR>
cBegin
	MOV	BX,b$Aspect	;get aspect ratio
	MOV	DX,b$AspectInv ;get inverse aspect ratio
cEnd

;***
;B$BumpDS - Advances array segment in DS to next valid segment
;
;Purpose:
;	This routine is called by the low level PUT code when it is
;	detected that an indexed PUT has crossed a segment boundary
;	This routine knows that the Low Levels access the array through
;	DS.  It will advance the selector to the next legal 64K chunk.
;
;Entry:
;	DS = Array segment
;
;Exit:
;	DS = Next 64K Array segment
;
;Uses:
;	None!
;
;Exceptions:
;	None.
;****
cProc	B$BumpDS,<PUBLIC,NEAR>,<AX>	
cBegin
	MOV	AX,DS		;save array selector
.erre	ID_SSEQDS		;assumes ss = ds
	add	ax,ss:b$HugeDelta ;add in HUGE segment delta
	MOV	DS,AX		;update DS
cEnd

;***
;B$BumpES - Advances array segment in ES to next valid segment
;
;Purpose:
;	This routine is called by the low level GET code when it is
;	detected that an indexed GET has crossed a segment boundary
;	This routine knows that the Low Levels access the array through
;	ES.  It will advance the selector to the next legal 64K chunk.
;	Added with [10].
;
;Entry:
;	ES = Array segment
;
;Exit:
;	ES = Next 64K Array segment
;
;Uses:
;	None!
;
;Exceptions:
;	None.
;****
cProc	B$BumpES,<PUBLIC,NEAR>,<AX>
cBegin
	MOV	AX,ES		;save array selector
.erre	ID_SSEQDS		;assumes ss = ds
	add	ax,ss:b$HugeDelta ;add in HUGE segment delta
	MOV	ES,AX		;update ES
cEnd

;***
;B$DecDS - Decrements array segment in DS to prev valid segment
;
;Purpose:
;	This routine has the opposite effect of B$BumpDS.
;	Added with [10].
;
;Entry:
;	DS = Array segment
;
;Exit:
;	DS = Prev 64K Array segment
;
;Uses:
;	None!
;
;Exceptions:
;	None.
;****
cProc	B$DecDS,<PUBLIC,NEAR>,<AX>
cBegin
	MOV	AX,DS		;save array selector
.erre	ID_SSEQDS		;assumes ss = ds
	sub	ax,ss:b$HugeDelta ;sub HUGE segment delta
	MOV	DS,AX		;update DS
cEnd

;***
; B$OutWord
;
;Purpose:
;	Output the word in AX to the port at DX.  This is equivalent
;	to "OUT DX,AX" except that AH and AL are swapped when done.
;	This routine exists to support machines (specifically the
;	ATT 6300+) whose word output capability malfunctions.
;
;Entry:
;	[DX] = address of output port
;	[AX] = output data
;
;Exit:
;Uses:
;Exceptions:
;****
cProc	B$OutWord,<PUBLIC,NEAR>
cBegin
	OUT	DX,AL		;set index register
	XCHG	AL,AH		;set up data in AL
	INC	DX		;data port is one byte above index register
	OUT	DX,AL		;set up data in relevant register
	DEC	DX		;restore address of index register
cEnd

;***
; B$ResetEGA
;
;Purpose:
;	To reset EGA Registers to values expected by the BIOS.
;
;Entry:
;Exit:
;
;Uses:
;	none
;
;Exceptions:
;****
cProc	B$ResetEGA,<PUBLIC,NEAR>,<AX,DX>
cBegin
	MOV	DX,SEQADD
	
	;converted OutWord macros to in-line byte outs here for speed
	
	MOV	AL,MMREG	;enables all planes for 32-bit write
	OUT	DX,AL
	INC	DX
	MOV	AL,0FH
	OUT	DX,AL
	MOV	DX,GRPADD	;address of graphics index register
	MOV	AL,ENBREG	;make sure Set/Reset is NOT enabled
	OUT	DX,AL
	INC	DX
	XOR	AL,AL
	OUT	DX,AL
	DEC	DX
	MOV	AL,CLCREG	;select color compare register, and set color 0
	OUT	DX,AL
	INC	DX
	XOR	AL,AL
	OUT	DX,AL
	DEC	DX
	MOV	AX,DTRREG	;reset logical operations
	OUT	DX,AL
	INC	DX
	XOR	AL,AL
	OUT	DX,AL
	DEC	DX
	MOV	AL,BMKREG	;activate all bits in the mask
	OUT	DX,AL
	INC	DX
	MOV	AL,0FFH
	OUT	DX,AL
	DEC	DX
	MOV	AL,CDCREG	;Color Don't Care Register
	OUT	DX,AL
	INC	DX
	MOV	AL,0FH
	OUT	DX,AL
	DEC	DX
	MOV	AL,RWMREG	;index to Mode Register
	OUT	DX,AL
	INC	DX
	MOV	AL,b$EgaWrMd	;then set bit 4 for odd/even addressing
	AND	AL,10H		;use only odd/even bit
	OUT	DX,AL
cEnd

sEnd	GR_TEXT 		

	END

⌨️ 快捷键说明

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