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

📄 ega.asm

📁 Dos6.0
💻 ASM
📖 第 1 页 / 共 5 页
字号:
	page	56,132
	name	EGASYS
	title	EGA Screen Device Driver
	subttl	Header

IFDEF	OS2
	.286				; Oh goody, can use 80286 instructions
ELSE	; NOT OS2
	.8086				; Have to support everything
ENDIF	; NOT OS2

;
; I N C L U D E S
;

	include	ega.inc

;
; C O D E
;

IFDEF	OS2				; Start of OS/2 functions

;
; DoSave - Save state of EGA
;
; ENTRY
;	ds = cs
;
; EXIT
;	ax = 0, operation complete
;
; DESTROYS
;	bx, si
;

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

DoSave		proc	near

	mov	ax,cs
	mov	es,ax
	assume	es:CODE
	mov	ax,0F901h		; Select new context subfunction
	jmp	short DoCommon

DoSave		endp

;
; DoRestore - Restore state of EGA
;
; ENTRY
;	ds = cs
;
; EXIT
;	ax = 0, operation complete
;
; DESTROYS
;	bx, si, ds
;

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

DoRestore	proc	near

	mov	ax,cs
	mov	es,ax
	assume	es:CODE
	mov	ax,0F902h		; Select new context subfunction

DoCommon:
	mov	bx,offset ContextCopy
	int	10h			; Restore from ContextCopy

if2	; Pass 2 of the assembler
.errnz		($ - StatusComplete)	; Drop into StatusComplete
endif	; Pass 2 of the assembler

DoRestore	endp

ENDIF	; OS2

;
; StatusComplete - Set completion status
;
; ENTRY
;	none
;
; EXIT
;	ax = 0, request completed
;
; DESTROYS
;	None
;

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

StatusComplete	proc	near

	sub	ax,ax			; AX = 0, complete
	ret

StatusComplete	endp

ENDIF	; SYS

	subttl	Miscellaneous Code
	page

;
; UpdateCRTCMap - get the latest values for certain readable CRTC regs
;
;	Called by all routines that return register values to the user,
;	this function updates the current CRTC shadow map with the latest
;	values of the readable CRTC StartAddress (00Ch, 00Dh) and
;	CursorPosition (00Eh, 00Fh).
;
;	Of the numerous EGA regs that are write only, the CRTC contains a
;	handful of readable regs.  Normally, for readable regs like Input
;	Status 1, EGA.SYS requires the user keep track of its value.  But if
;	the goal is for the user of EGA.SYS to be able to rely 100% on the
;	shadow maps, we must properly update readables that we do return.
;	Note that the CRTC lightpen regs do not fall into this category,
;	since we shadow writes to that index, which is really the vertical
;	sync start/stop regs.
;
; ENTRY
;	none
; EXIT
;	none
; DESTROYS
;	AX, SI (if VGA)
;

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

UpdateCRTCMap	proc	near

	push	dx			; Save environment
	mov	dx,[PortTable][0].prPortAddr
	mov	ax,0C0Dh
	pushf				; Save interrupt flag state
	CLI				; Disable interrupts
	out	dx,al			; Address CRTCStart high
	IOdelay
	inc	dx
	in	al,dx			; Get CRTCStart high
	IOdelay
	dec	dx
	xchg	al,ah
	out	dx,al			; Address CRTCStart low
	IOdelay
	inc	dx
	in	al,dx			; Get CRTCStart low
	IOdelay
	mov	word ptr [CRTCRegs][00Ch],ax ; Stash low:high
	dec	dx
	mov	ax,00E0Fh
	out	dx,al			; Address CRTCCursor pos high
	IOdelay
	inc	dx
	in	al,dx			; Get CRTCCursor pos high
	IOdelay
	dec	dx
	xchg	al,ah
	out	dx,al			; Address CRTCCursor pos low
	IOdelay
	inc	dx
	in	al,dx			; Get CRTCCursor pos low
	popf				; Restore interrupt flag state
	mov	word ptr [CRTCRegs][00Eh],ax ; Stash low:high
	cmp	[fVga],false		; On VGA card?
	je	UpdateCRTCMapDone	; No - skip
	xor	si,si			; Don't change default save maps
	push	bx			; Save environment
	push	cx			; Save environment
	call	ReadVGARegs
	mov	[fPalette],cl		; fPalette = FALSE
	pop	cx			; Restore environment
	pop	bx			; Restore environment

UpdateCRTCMapDone:
	pop	dx			; Restore environment
	ret

UpdateCRTCMap	endp

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

ReadVGARegs	proc	near

;
; Save Miscellaneous Output Register
;

	MOV	DX,MiscOutputRegR	; Get Miscellaneous Output Register
	IN	AL,DX			; Get current state of the register
	IOdelay
	MOV	[MiscOutReg],AL		; value
	or	si,si			; Change default save map?
	jz	@F			; No - skip
	MOV	[DefMiscOutReg],AL	; Save initial

;
; Save Feature Control Register
;

@@:
	MOV	DL,FeatureCtrlReg AND 0FFH ; Get Feature Control Register
	IN	AL,DX			; Get current state of the register
	MOV	[FeatureReg],AL		; value
	or	si,si			; Change default save map?
	jz	@F			; No - skip
	MOV	[DefFeatureReg],AL	; Save initial

;
; Save Sequencer Registers
;

@@:
	MOV	CX,NumSeqRegs		; Initialize 5H registers
	MOV	DL,(EGA_BASE + SEQ_ADDR) AND 0FFH ; Get Sequencer Register
	XOR	BX,BX			; Code to select reset reg
	pushf				; Save interrupt flag state

SaveSequencerRegs:
	MOV	AL,BL			; Get index
	CLI				; Disable interrupts
	OUT	DX,AL			; Send index to the Address Register
	IOdelay
	INC	DX			; Choose read only register
	IN	AL,DX			; Get current state of the register
	STI				; Enable interrupts
	DEC	DX			; Choose index register
	MOV	[SeqRegs][BX],AL	; value
	or	si,si			; Change default save map?
	jz	@F			; No - skip
	MOV	[DefSeqRegs][BX],AL	; Save initial

@@:
	INC	BX			; Move to the next index register
	LOOP	SaveSequencerRegs	; Loop back and initialize another reg

;
; Save Graphics Controller Registers
;

	MOV	BX,CX			; Code to select enable set/reset reg
	MOV	CL,NumGraphicsRegs	; Initialize 9H registers
	MOV	DL,(EGA_BASE + GRAF_CONT) AND 0FFH
					; Get Graphics Control Addr Reg

SaveGraphicsContRegs:
	MOV	AL,BL			; Get index
	CLI				; Disable interrupts
	OUT	DX,AL			; Send index to the Address Register
	IOdelay
	INC	DX			; Choose read only register
	IN	AL,DX			; Get current state of the register
	STI				; Enable interrupts
	DEC	DX			; Choose index register
	MOV	[GraphicsRegs][BX],AL	; value
	or	si,si			; Change default save map?
	jz	@F			; No - skip
	MOV	[DefGraphicsRegs][BX],AL ; Save initial

@@:
	INC	BX			; Move to the next index register
	LOOP	SaveGraphicsContRegs	; Loop back and initialize another reg

;
; Save Attribute Controller Registers
;

	MOV	BX,CX			; Code to select Palette
					; Register and keep video disabled
	MOV	CL,NumAttrRegs		; Initialize 15H registers

SaveAttributeContRegs:
	MOV	DL,BYTE PTR [PortTable][5 * SIZE PortRec].PRPortAddr
	CLI				; Disable interrupts
	IN	AL,DX			; Initialize flip-flop to select address
	MOV	AL,BL			; Get index
	CMP	AL,10H			; Past palette registers?
	JB	PaletteCheckDone	; No - skip
	OR	AL,PaletteAddressSource	; Code to enable video
	jmp	short GetAttrReg

;
;	We are stuck.  In order to correctly read the Palette registers
;	on a VGA, the Palette address source bit (bit 5 of the Attribute
;	Address Register) needs to be 0, but making this 0 will disable
;	video.  Then after reading the Palette registers, we need to
;	re-enable video.  But this happens so often that the screen
;	flashes.  So, we can only read these registers at init time.
;	Only loss of functionality is if the palette registers get
;	out of sync with the shadow maps after init time.
;

PaletteCheckDone:
	cmp	[fPalette],ch		; Did user request the palette regs?
	jne	GetAttrReg		; Yes - skip
	or	si,si			; Init?
	jz	NextAttrReg		; No - skip

GetAttrReg:
	MOV	DL,AttCtrlAddrReg AND 0FFH ; Get Attribute Control Address Reg
	OUT	DX,AL			; Send index to the Address Register
	IOdelay
	INC	DX			; Choose read only register
	IN	AL,DX			; Get current state of the register
	MOV	[AttrRegs][BX],AL	; value
	or	si,si			; Change default save map?
	jz	NextAttrReg		; No - skip
	MOV	[DefAttrRegs][BX],AL	; Save initial

NextAttrReg:
	STI				; Enable interrupts
	INC	BX			; Move to the next index register
	LOOP	SaveAttributeContRegs	; Loop back and initialize another reg

;
; Save CRT Controller Registers
;

	MOV	BX,CX			; Code to select horizontal total reg
	MOV	CL,NumCRTCRegs		; Initialize 19H registers
	MOV	DL,BYTE PTR [PortTable][5 * SIZE PortRec].PRPortAddr
	CLI				; Disable interrupts
	IN	AL,DX			; So that we get back to index again
	IOdelay
	SUB	DL,6			; Get CRT Controller Address Reg

SaveCRTContRegs:
	CLI				; Disable interrupts
	MOV	AL,BL			; Get index
	OUT	DX,AL			; Send index to the Address Register
	IOdelay
	INC	DX			; Choose read only register
	IN	AL,DX			; Get current state of the register
	STI				; Enable interrupts
	DEC	DX			; Choose index register
	MOV	[CRTCRegs][BX],AL	; value
	or	si,si			; Change default save map?
	jz	@F			; No - skip
	MOV	[DefCRTCRegs][BX],AL	; Save initial

@@:
	INC	BX			; Move to the next index register
	LOOP	SaveCRTContRegs		; Loop back and initialize another reg
	popf				; Restore interrupt flag state
	ret

ReadVGARegs	endp

	page

;
; BrstDet - determine number of scan lines for raster
;
;	BrstDet, similar to the IBM function by the same name, determines
;	whether the current raster should be 200 or 350 scanlines based on
;	the switch settings on the rear of the EGA card.  In a nutshell,
;	switch settings 0011 or 1001 indicate 350 lines, otherwise 200 lines.
;
; EXIT
;	cy	=  200 scanlines
;	nc	=  350 scanlines
; DESTROYS
;	None
;

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

BrstDet 	proc	near

	push	ax
	mov	al,[biosinfo3]		; Get feature and switch info
	and	al,00001111b		; Mask for switches
	cmp	al,00001001b		; Most common config
	je	@F
	cmp	al,00000011b		; Less common
	je	@F
	stc				; Else set carry

@@:
	pop	ax
	ret

BrstDet 	endp

	page

;
; MakeBase - find proper video params for given mode
;
;	MakeBase, similar to the IBM function by the same name, will return
;	a pointer to the correct table of video parameters to use when
;	initializing the EGA for a given mode.	The root of the list of tables
;	is derived from the ParmPtr in the SavePtr table.
;
; ENTRY
;	ah	=  video mode
;	ds	=  0
; EXIT
;	es:si	-> base of correct parameter table
; DESTROYS
;	ax, flags
;

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

MakeBase	proc	near

	les	si,[lpSavePtr]		; Load up SavePtr
	assume	es:nothing
	les	si,es:[si]		; Load up ParmPtr
	assume	es:nothing
	test	[Info],01100000b	; If 64K video memory,
	jz	mb64K			;  skip special graphics tests
	add	si,440h			; Bump to alt 640x350x1
	cmp	ah,0Fh 			; If this is what we want,
	je	mbX			;  we are done
	add	si,40h			; Bump to alt 640x350x4
	cmp	ah,10h 			; If this is what we want,
	je	mbX			;  we are done

;
; I assume that the special VGA modes 11h, 12h, and 13h are
;	contiguous and lie after the last EGA table in memory, but
;	I don't know this for sure.
;

	add	si,140h			; Bump for VGA modes 11h, 12h, 13h
	cmp	ah,11h			; Is it a VGA mode 11h?
	je	mbx			; Yes - skip
	add	si,40h			; Bump for VGA mode 12h
	cmp	ah,12h			; Is it a VGA mode 12h?
	je	mbx			; Yes - skip
	add	si,40h			; Bump for VGA mode 13h
	cmp	ah,13h			; Is it a VGA mode 13h?
	je	mbx			; Yes - skip
	sub	si,640h			; Nope, not special graphics

mb64K:
	cmp	ah,3h 			; If not alpha,
	ja	@F			;  skip special alpha tests
	call	BrstDet 		; If not enhanced config,
	jc	@F			;  no adjustment needed
	add	si,4C0h			; Bump to enhanced alpha parms

@@:
	xor	al,al			; Now use mode as final index

ifdef	OS2
	shr	ax,2
else	; NOT OS2
	shr	ax,1			; Funky math does the job
	shr	ax,1
endif	; NOT OS2

	add	si,ax

mbX:
	ret				; ES:SI -> correct table

MakeBase	endp

;-----------------------------------------------------------------------
; HandleIODelay -- Delay for doing close together I/O for hardware
;			to catch it's breath
;
; Entry: None
;
; Exit:  None
;
; Alters: None
;
; Note:	This was implemented because processors (e.g. 80486) keep
;		getting faster and smarter (prefetch and caching)
;		and ruin our old jmp $+2 scheme, so this is a better
;		(i.e. more processor independent) method.
;
;-----------------------------------------------------------------------

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

HandleIODelay	proc	near

	push	ax			; Save environment
	in	al,43h			; Delay by reading status register
	in	al,43h			; Delay by reading status register
	pop	ax			; Restore environment
	ret

HandleIODelay	endp

	page

;
; ChangeRegs - reinitialize all shadow maps and EGA state info
;
; ENTRY
;	ah	=  video mode
;	al	=  low byte of CRTC io address
;			Used in EGAChooseMonoColorDisplay macro
; EXIT
;	ds	=  cs
; DESTROYS
;	ax, si
;

⌨️ 快捷键说明

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