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

📄 ega.asm

📁 Dos6.0
💻 ASM
📖 第 1 页 / 共 5 页
字号:

	assume	cs:CODE, ds:INTVEC, es:nothing, ss:nothing

ChangeRegs	proc	near

	push	cx			; Save environment
	push	di			; Save environment
	PUSH	BX			; Save environment

ifdef	OS2
	mov	cx,cs			; DS = Code segment
	mov	ds,cx			; Two instructions needed
	assume	ds:CODE
	EGAChooseMonoColorDisplay	; Validate CRTC address
endif	; OS2

	CMP	[fVga],FALSE		; Do we have a VGA Card?
	JE	HandleEGA		; No - skip
	PUSH	DX			; Save environment

ifndef	OS2
	mov	cx,cs			; DS = Code segment
	mov	ds,cx			; Two instructions needed
	assume	ds:CODE
	VGAChooseMonoColorDisplay	; Validate CRTC address
endif	; NOT OS2

	mov	si,1			; Change default save maps
	call	ReadVGARegs
	POP	DX			; Restore environment
	JMP	SHORT FinishChangeRegs

HandleEGA:

ifdef	OS2
	PUSH	ES			; Save environment
	xor	si,si			; DS = Segment 0
	mov	ds,si			; Two instructions needed
	assume	ds:INTVEC
else	; NOT OS2
	assume	ds:INTVEC
	PUSH	ES			; Save environment
	EGAChooseMonoColorDisplay	; Validate CRTC address
endif	; NOT OS2

	call	MakeBase		; ES:SI -> correct table on exit
	assume	es:nothing
	mov	ax,es
	mov	ds,ax			; DS = ES
	assume	ds:nothing
	mov	ax,cs
	mov	es,ax			; ES = CS
	assume	es:CODE
	add	si,5			; Bump past BIOS misc junk
	mov	di,offset StartShadowMaps
	mov	al,3			; Always stash 3 in seq reset reg
	stosb
	mov	cx,(VGAPatch - 2) / 2	; Move data up to extra VGA reg

if	(VGAPatch - 2) AND 1
	movsb				; Odd count adjust
endif	; (VGAPatch - 2) AND 1

rep	movsw
	inc	di			; Bump past VGA reg
	mov	cl,NumGraphicsRegs / 2	; Finish up grph ctrlr regs

if	NumGraphicsRegs AND 1
	movsb				; Odd count adjust
endif	; NumGraphicsRegs AND 1

rep	movsw

	sub	si,(SizeShadowMaps - 2) ; Drop back to beginning
	stosb				; Always stash 3 in seq reset reg
	mov	cl,(VGAPatch - 2) / 2	; Move data up extra VGA reg

if	(VGAPatch - 2) AND 1
	movsb				; Odd count adjust
endif	; (VGAPatch - 2) AND 1

rep	movsw
	inc	di			; Bump past VGA reg
	mov	cl,NumGraphicsRegs / 2	; Finish up grph ctrlr regs

if	NumGraphicsRegs AND 1
	movsb				; Odd count adjust
endif	; NumGraphicsRegs AND 1

rep	movsw
	mov	ax,cs
	mov	ds,ax
	assume	ds:CODE 		; DS = CS
	mov	[PortTable][3 * SIZE PortRec].prNumRegs,NumAttrRegs - 1
					; Adjust size for EGA
	xor	ax,ax			; Get a zero value
	mov	[Gr1PosReg],al		; AX = 0, init Gr1PosRegs
	mov	[DefGr1PosReg],al
	inc	ax
	mov	[Gr2PosReg],al		; AX = 1, init Gr2PosRegs
	mov	[DefGr2PosReg],al
	POP	ES			; Restore environment
	assume	es:nothing

FinishChangeRegs:
	assume	ds:CODE
	xor	ax,ax
	mov	di,ax			; Now clear all dirty flags
	mov	cl,NumPtrData
	mov	bx,offset PortTable	; Start at beginning

@@:
	mov	code:[bx][di].prModFlag,al
	add	di,SIZE PortRec
	loop	@B
	mov	[SingleRegMod],al
	POP	BX			; Restore environment
	pop	di			; Restore environment
	pop	cx			; Restore environment
	ret

ChangeRegs	endp

	subttl	SetMode
	page

;
; SetMode - shadow int 10h SetMode functionality (subfunction 00h)
;
;	This code is executed when a BIOS setmode call is made.  It must
;	predict which mode table the BIOS will use, so the BIOS decision
;	logic is duplicated here.
;
; ENTRY
;	SaveAX		=  original ax on entry with mode in al
;	ds		=  cs
; EXIT
;	none
; DESTROYS
;	ax, si, ds, flags
;

	assume	cs:CODE, ds:CODE, es:nothing, ss:nothing

SetMode 	proc	near

	xor	ax,ax
	mov	ds,ax
	assume	ds:INTVEC
	mov	al,byte ptr [EquipFlag]	; Get planar switch setting
	mov	ah,byte ptr [SaveAX]	; AH = mode
	and	ah,01111111b		; Reset noclear bit
	test	[Info],00000010b	; If EGA has color monitor
	jz	smNoMonochrome		;  skip mono tests
	test	al,030h 		; If default video is color,
	jnz	smNoChange		;  get out now
	mov	al,0B4h 		; IO addr = 3Bx
	cmp	ah,00Fh 		; If mono hi-res graphics,
	je	@F			;  do it
	mov	ah,007h 		; Else force mono alpha
	jmp	short @F		;  do it

smNoMonochrome:
	test	al,030h 		; If default video mono,
	jz	smNoChange		;  get out now
	mov	al,0D4h 		; IO addr = 3Dx

@@:
	push	ax			; Save video mode
	call	ChangeRegs		; Initialize shadow maps
	assume	ds:CODE
	pop	ax			; Recover mode
	push	bx			; We need it
	mov	bx,0FF01h		; Assume mono 8x14 font
	cmp	[fVga],FALSE		; Do we have a VGA Card?
	je	@F			; No - skip
	mov	bl,4			; Assume mono 8x16 font

@@:
	cmp	ah,7			; If mode is mono alpha,
	je	smDoFonts		;  do it
	mov	bl,0FFh 		; Assume no fonts (graphics)
	cmp	ah,3			; If mode is graphics,
	ja	smDoFonts		;  do it
	mov	bl,001h 		; Assume 8x14 font
	cmp	[fVga],FALSE		; Do we have a VGA Card?
	je	@F			; No - skip
	mov	bl,004h 		; Assume 8x16 font

@@:
	call	BrstDet 		; If 350 scanlines,
	jnc	smDoFonts		;  do it
	mov	bl,2			; Else show 8x8 font

smDoFonts:
	mov	word ptr [FontBank][0],bx ; Stash bl:bh
	mov	word ptr [FontBank][2],0FFFFh ; Stash 0FFh:0FFh
	pop	bx

smNoChange:
	assume	ds:nothing
	ret

SetMode 	endp

if	CallTableNeeded

	subttl	SetCursorType
	page

;
; SetCursorType - shadow int 10h SetCursorType functionality (subfunction 01h)
;
; ENTRY
;	ch	=  bits 0-4: start scanline for cursor
;		   bits 5-6: visibility attributes
;	cl	=  bits 0-4: stop scanline for cursor
;	ds	=  cs
; EXIT
;	none
; DESTROYS
;	ax, flags
;

	assume	cs:CODE, ds:CODE, es:nothing, ss:nothing

SetCursorType	proc	near

	push	bx			; Save environment
	push	ds			; Save environment
	xor	ax,ax
	mov	ds,ax
	assume	ds:INTVEC
	mov	bx,cx			; BX = cursor type
	test	[Info],00001000b	; If EGA not active,
	jnz	sctStash		;  just stash the raw values
	mov	al,bh			; AL = raw start
	and	al,01100000b		; Extract visibility attributes
	cmp	al,00100000b		; If cursor-off flag not set,
	jne	@F			;  continue
	mov	bx,01E00h		; Else emulate cursor off
	jmp	short sctStash

@@:
	test	[Info],00000001b	; If not emulating cursor,
	jnz	sctStash		;  just stash the raw values
	cmp	[CrtMode],3		; If not alpha mode,
	ja	sctNoBump2		;  avoid special alpha tests
	call	BrstDet 		; If 200 lines,
	jc	sctNoBump2		;  avoid 350 line heuristics
	mov	al,005h 		; Magic number
	cmp	bh,al			; If start < 5,
	jb	@F			;  leave it alone
	add	bh,al			; Else bump it up

@@:
	cmp	bl,al			; If stop < 5,
	jb	sctNoBump2		;  leave it alone
	add	bl,al			; Else bump it up

sctNoBump2:
	inc	bl			; Bump stop
	or	bh,bh			; If start = 0,
	jz	@F			;  check for wraparound
	cmp	bl,byte ptr [Points]	; If stop < char cell height,
	jb	@F			;  proceed to final test
	xor	bl,bl			; Else stop = 0

@@:
	mov	ax,bx			; Get copy into ax
	sub	al,ah
	cmp	al,16			; If stop - start != magic
	jne	sctStash		;  continue
	inc	bl			; Else bump stop

sctStash:
	pop	ds			; Restore environment
	assume	ds:CODE
	xchg	bh,bl			; Flip start/stop
	mov	word ptr [CRTCRegs][10],bx ; Stash computed value
	pop	bx			; Restore environment

if2	; Pass 2 of the assembler
.ERRNZ		($ - Ignore)		; Drop into Ignore
endif	; Pass 2 of the assembler

SetCursorType	endp

;
; Ignore - Unsupported device driver calls enter here
;
; ENTRY
;	none
; EXIT
;	none
; DESTROYS
;	none
; NOTE:
;	We are using the RET instruction from SetMode above
;

	assume	cs:CODE, ds:nothing, es:nothing, ss:nothing

Ignore		proc	near		; Enter here just to use the ret

	ret

Ignore		endp

	subttl	ScrollUpDown
	page

;
; ScrollUpDown - shadow int 10h Scroll functionality (subfunctions 06h, 07h)
;
; ENTRY
;	al  =	current video mode
;	ah  =	static copy of ega info byte
;
; EXIT
;	none
; DESTROYS
;	ax, flags
;

	assume	cs:CODE, ds:CODE, es:nothing, ss:nothing

ScrollUpDown	proc	near

	push	bp
	mov	bp,sp			; Watch out for stack!
	push	bx
	mov	bh,byte ptr [bp].userAX ; BH = num lines to scroll
	or	bh,bh			; If bh = 0,
	jz	sudSetSeq		;  only change sequencer
	mov	bl,dh			; BL = lower row of window
	sub	bl,ch			; BL = lower row - upper row
	inc	bx			; Make 1-based
	cmp	bl,bh			; If size window = num lines,
	je	sudSetSeq		;  treat as blank whole window
	mov	bl,010h 		; Assume odd/even addressing
	cmp	al,00Fh 		; If mode < 0Fh,
	jb	@F			;  assumption is correct
	test	ah,01100000b		; If EGA memory is 64K,
	jz	@F			;  assumption is correct
	xor	bl,bl			; Else use enhanced default

@@:
	mov	[GraphicsRegs][005h],bl	; Stash the default

sudSetSeq:
	mov	[SeqRegs][002h],00Fh	; Stash another default
	pop	bx
	pop	bp
	ret

ScrollUpDown	endp

	subttl	ReadChar
	page

;
; ReadChar - shadow int 10h ReadChar functionality (subfunction 08h)
;
; ENTRY
;	al  =	current video mode
;	ah  =	static copy of ega info byte
;
; EXIT
;	none
; DESTROYS
;	ax, flags
;

	assume	cs:CODE, ds:CODE, es:nothing, ss:nothing

ReadChar	proc	near

	cmp	al,00Fh 		; If mode <  0Fh,
	mov	al,0			; (reuse al and assume default)
	jb	@F			;  no more processing needed
	test	ah,0110000b		; If EGA memory >64K
	jnz	@F			;  no more processing needed
	mov	al,010h 		; Else use crippled default

@@:
	mov	[GraphicsRegs][005h],al	; Put al in r/w mode reg
	ret

ReadChar	endp

	subttl	WriteChar
	page

;
; WriteChar - shadow int 10h WriteChar functionality (subfunctions 09h, 0Ah)
;
; ENTRY
;	al  =	current video mode
;	ah  =	static copy of ega info byte
;
; EXIT
;	none
; DESTROYS
;	ax, flags
;

	assume	cs:CODE, ds:CODE, es:nothing, ss:nothing

WriteChar	proc	near

	mov	[GraphicsRegs][003h],0	; Put 000h in data rotate reg
	mov	[SeqRegs][002h],00Fh	; Put 00Fh in map mask reg

scpGetOut:				; Mind if we use your ret?  Thanks.
	assume	ds:nothing
	ret

WriteChar	endp

	subttl	SetCGAPalette
	page

;
; SetCGAPalette - shadow int 10h SetCGAPalette functionality (subfunction 0Bh)
;
;	SetCGAPalette is a quirky function, even on a CGA system.  Note the
;	following points carefully:
;
;	1.  When using bh = 0 to set background/overscan, the call will fall
;	    through to the bh = 1 code because bit 4 is the palette intensity
;	    which must be combined with the current palette selection.	Thus
;	    when making a set background call, you are also implicitly making
;	    a set palette intensity call (subject to constraints that follow).
;
;	2.  In alpha modes, you may only set the overscan color if you are in
;	    a CGA compatible (200 lines, 15KHz) sweep mode.  Attempting to do
;	    this in 350 line alpha will cause display problems and therefore is
;	    a nop in this function.  It is also meaningless to set the palette
;	    and the background color in either alpha sweep mode, and thus is a
;	    nop.
;
; ENTRY
;	bh	=  0: set background/overscan color
;		bl	=  bits 0-3: irgb color for background/overscan
;			   bit	  4: palette intensity
;			   bits 5-7: unused
;	bh	=  1: set foreground palette
;		bl	=  0: set palette 0 (green/red/brown)
;			   1: set palette 1 (cyan/magenta/white)
;	ds	=  cs
; EXIT
;	none
; DESTROYS
;	ax, si, ds, flags
;

	assume	cs:CODE, ds:CODE, es:nothing, ss:nothing

SetCgaPalette	proc	near

	xor	ax,ax
	mov	ds,ax
	assume	ds:INTVEC
	cmp	byte ptr [Addr6845],0B4h; If mono active,
	je	scpGetOut		;  get out
	test	[Info],00000010b	; If EGA has no color monitor,
	jnz	scpGetOut		;  get out
	mov	ah,[CrtMode]		; AH = video mode
	mov	al,[CrtPalette] 	; AL = CGA palette byte
	mov	si,cs			; DS = Code segment
	mov	ds,si			; Two instructions needed
	assume	ds:CODE
	push	bx
	or	bh,bh			; If bh != 0,
	jnz	scpPal			;  go set CGA palette colors
	and	al,11100000b		; Clear old backgnd, pal intense
	and	bl,00011111b		; Isolate new backgnd, pal int
	or	al,bl			; AL = new palette byte
	mov	bh,bl			; Get a copy into bh
	shl	bl,1			; Shift intensity into position
	and	bx,0000011100010000b	; And isolate it
					; Isolate rgb in bh
	or	bh,bl			; BH = EGA compatible background
	cmp	ah,3			; If in graphics mode,
	ja	@F			;  do background and overscan
	call	BrstDet 		; If 200 lines,
	jc	scpOverScan		;  do overscan only
	jmp	short scpX		; Else nothing left to do

@@:
	mov	[AttrRegs][000h],bh	; Stash background

scpOverScan:
	mov	[AttrRegs][011h],bh	; Stash overscan
	mov	bl,al			; Recover new palette byte
	and	bl,00100000b		; Isolate palette bit

ifdef	OS2
	rol	bl,3			; And get into bit 0
else	; NOT OS2
	rol	bl,1			; And get into bit 0
	rol	bl,1
	rol	bl,1
endif	; NOT OS2

scpPal:
	cmp	ah,3			; If in alpha mode,
	jbe	scpX			;  don't bother with palettes
	and	bl,00000001b		; Only allow palettes 0 and 1
	and	al,00010000b		; Isolate palette intensity bit

⌨️ 快捷键说明

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