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

📄 ega.asm

📁 Dos6.0
💻 ASM
📖 第 1 页 / 共 5 页
字号:
;	per function being called
; DESTROYS
;	ax, si for this particular procedure,
;	otherwise,  per function being called
;

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

ContextInfo	proc	near

	push	bp			; Save environment
	mov	bp,sp			; Set up stack addressing
	mov	al,byte ptr [bp].userAX	; Get old ax from stack
	pop	bp			; Restore environment
	cmp	al,MaxContextCall	; If not one of our subfunctions,
	ja	ciX			;  get out now
	xor	ah,ah			; Reset ah for dispatch
	shl	ax,1			; *2 for word addresses
	mov	si,ax
	jmp	[ContextTable][si]	; MUST jmp for stack integrity

ContextInfo	endp

;
; GetContextSize - return size in bytes needed to save EGA.SYS context
;
; ENTRY
;	none
; EXIT
;	userAX	=  size in bytes needed to save EGA.SYS context
; DESTROYS
;	AX
;

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

GetContextSize	proc	near

	push	bp			; Save environment
	mov	bp,sp			; Set up stack addressing
	mov	[bp].userAX,SizeEGAContext ; Stash size on stack for ax
	pop	bp			; Restore environment

ciX:					; Mind if we use your ret?  Thanks.
	ret

GetContextSize	endp

	page

;
; SaveContext - dump current EGA.SYS context data to user buffer
;
;	If an app or TSR must change the EGA regs, but wants to restore
;	EGA.SYS and the hardware to the original state on entry, it should
;	first call GetContextSize.  Based on the value returned, it should
;	allocate the necessary buffer (possibly on the stack), set es:bx to
;	point to it, and issue this call.  The app is then free to issue other
;	EGA.SYS or int 10h calls at will.  When finished, it should call
;	RestoreContext data with a pointer to the saved context data.  Since
;	the current state of the dirty flags is included in the context data,
;	these too will be properly restored.
;
;	Note that apps must not assume a given size for the context data.
;	An app should call GetContextSize at least once, beforehand, to
;	determine how much memory to provide.  Also, apps must not assume a
;	given structure for the context data or modify it in any way.
;
;	If an app or TSR plans to make semi-permanent changes to the EGA regs,
;	it may avoid the Save/Restore context calls.  EGA.SYS will shadow any
;	int 10h calls that modify the EGA regs, updating both the default and
;	current shadow maps, but not touching any of the dirty flags.  This
;	allows the interrupted app to continue making RevertDefault calls, yet
;	keeps the new changes in effect until the app explicitly changes a reg
;	which the TSR modified.
;
; ENTRY
;	es:bx	->  user save area buffer for EGA context
; EXIT
;	none
; DESTROYS
;	ax, si, ds, flags
;

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

SaveContext	proc	near

	push	cx			; Save environment
	push	dx			; Save environment
	push	di			; Save environment
	push	bx			; Save environment
	call	GetLatchLocation	; Get EGA/VGA latch save location
	or	di,di			; Are we in text mode?
	jz	@F			; Yes - skip

;
; Save the EGA/VGA latches
;

	mov	ah,ReadRegNum		; Read 1 register
	mov	dx,10h			; Graphics port register
	mov	bx,5			; Index 5
	int	10h			; Get it
	mov	si,ds			; Find a place for our byte
					; in vram, past visible memory
	mov	dx,egamem
	mov	ds,dx
	assume	ds:egamem
	mov	ax,(MR_SET shl 8) or GRAF_MODE_REG ; Set mode reg
					; to writethrough (mode 1)
	mov	dx,EGA_BASE + GRAF_CONT ; Set the port
	OutWord	,DestroyAX,DestroyDX
	mov	egamem:[di],al		; Actually write to vram and store
					; latches at offset [bx]
	mov	bh,bl			; Position it properly
	mov	bl,5			; Index 5
	mov	ah,WriteRegNum		; Write 1 register
	mov	dx,10h			; Graphics port register
	int	10h			; Restore original port value
	mov	ds,si
	assume	ds:CODE

;
; Save the EGA/VGA registers
;

@@:
	call	UpdateCRTCMap		; Get latest readable regs
	pop	bx			; Restore environment
	mov	di,bx
	mov	si,offset StartEGAContext
	mov	cx,SizeEGAContext / 2

if	SizeEgaContext AND 1
	movsb
endif	; SizeEgaContext AND 1

rep	movsw
	pop	di			; Restore environment
	pop	dx			; Restore environment
	pop	cx			; Restore environment
	ret

SaveContext	endp

	page

;
; RestoreContext - restore EGA.SYS context data from user buffer
;
;	RestoreContext copies a previously saved EGA context pointed to by
;	es:bx to the internal data areas of EGA.SYS and updates the hardware
;	to reflect the restored state.	The only caveat is that the state of
;	the Attribute index/data flip-flop is reset to the "index" state since
;	SaveContext is unable to save this information.  Note that this should
;	not be a problem if the caller checks the fInBIOS flag before
;	attempting to reprogram the EGA and if the interrupted application
;	only uses EGA.SYS or int 010h to modify the hardware.  This is because
;	EGA.SYS and int 010h always reset this flip-flop to the "index" state
;	on return.
;
; ENTRY
;	es:bx	-> previously saved EGA context
; EXIT
;	none
; DESTROYS
;	ax, si, ds, flags
;

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

RestoreContext	proc	near

	push	cx			; Save environment
	push	dx			; Save environment
	push	di			; Save environment
	push	es			; Save environment

;
; Restore the EGA/VGA latches
;

	call	GetLatchLocation	; Get EGA/VGA latch save location
	or	di,di			; Are we in text mode?
	jz	@F			; Yes - skip
	mov	dx,egamem
	mov	ds,dx
	assume	ds:egamem
	mov	dx,EGA_BASE + GRAF_ADDR	; Setup for writethrough mode
	mov	ax,(DR_SET shl 8) or GRAF_DATA_ROT
	pushf				; Save interrupt flag state
	cli				; No interrupts while changing regs
	OutWord	NoInts,DestroyAX
	IOdelay
	mov	ax,(0ffh shl 8) or GRAF_BIT_MASK ; Don't mask any bits
	OutWord	NoInts,DestroyAX,DestroyDX
	IOdelay
					; DH already set correctly
	mov	dl,SEQ_ADDR		; Enable all planes, set seq
	mov 	ax,(MM_ALL shl 8) or SEQ_MAP_MASK ; Addr reg to point
	OutWord	NoInts,DestroyAX,DestroyDX ; to map mask reg
	popf				; Restore interrupt flag state
	mov	al,egamem:[di]		; Actually write to vram to
					; restore the latches

@@:
	mov	si,bx
	mov	di,offset StartEGAContext
	mov	ax,es			; ES = CS
	mov	dx,cs			; DS = Old ES
	mov	es,dx			; "
	assume	es:CODE
	mov	ds,ax			; Get new clocking mode 1st
	assume	ds:nothing
	mov	al,ds:[si + offset SeqRegs - offset StartEgaContext + 01h]
	cmp	al,CODE:[di + offset SeqRegs - offset StartEgaContext + 01h]
	jne	@F			; If same, compare mem mode
	mov	al,ds:[si + offset SeqRegs - offset StartEgaContext + 04h]
	cmp	al,CODE:[di + offset SeqRegs - offset StartEgaContext + 04h]
	jne	@F			; If same, compare misc regs
	mov	al,ds:[si + offset GraphicsRegs - offset StartEgaContext + 06h]
	cmp	al,CODE:[di + offset GraphicsRegs - offset StartEgaContext + 06h]

@@:
	mov	cx,SizeEGAContext / 2

if	SizeEgaContext AND 1
	movsb
endif	; SizeEgaContext AND 1

rep	movsw
	pop	es			; ES = old ES
	assume	es:nothing
	mov	ds,dx			; DS = CS
	assume	ds:CODE
	mov	cl,NumSeqRegs - 2 	; Don't do clocking/memory modes
	mov	dh,3			; "prefix" for port addresses
	mov	si,offset SeqRegs
	je	@F	 		; Jump if no changes here
	mov	ax,0100h
	mov	dl,(EGA_BASE + SEQ_ADDR) AND 0FFh
	pushf				; Save interrupt flag state
	cli				; RAM refresh will be off now!
	OutWord	NoInts			; Synchronous reset to sequencer
	IOdelay
	inc	ax			; Now select clocking mode reg
	mov	ah,CODE:[si + 01h]
	OutWord	NoInts,DestroyAX	; Write its new value (in ah)
	IOdelay
	mov	al,04h			; Now select memory mode reg
	mov	ah,CODE:[si + 04h]
	OutWord	NoInts,DestroyAX,DestroyDX ; Write its new value (in ah)
	IOdelay
	mov	dl,(EGA_BASE + GRAF_CONT) AND 0FFh
	mov	al,06h			; Now select grphx misc reg
	mov	ah,[GraphicsRegs + 06h]
	OutWord	NoInts,DestroyAX,DestroyDX ; Write its new value, too (ah)
	popf				; Restore interrupt flag state

@@:
	mov	dl,(EGA_BASE + SEQ_ADDR) AND 0FFh ; Setup for seq loop
	mov	al,ch			; AL = 0

recSeqLoop:
	mov	ah,CODE:[si]
	IOdelay
	OutWord 			; No ints can occur until after

@@:
	inc	si
	inc	ax
	cmp	al,01h			; Clocking mode reg next?
	je	@B			; If so, skip it
	loop	recSeqLoop		; Otherwise continue if more
	mov	al,cl			; AL = 0
	mov	cl,NumGraphicsRegs - 1
	mov	si,offset GraphicsRegs
	mov	dl,(EGA_BASE + GRAF_CONT) AND 0FFh

recGrphLoop:
	mov	ah,CODE:[si]
	IOdelay
	OutWord

@@:
	inc	si
	inc	ax
	cmp	al,06h			; Grphx misc reg next?
	je	@B			; If so, skip it
	loop	recGrphLoop		; Otherwise continue if more
	mov	al,cl			; AL = 0
	mov	cl,NumCRTCRegs
	mov	dl,byte ptr [PortTable][0].prPortAddr
	mov	si,offset CRTCRegs

@@:
	mov	ah,CODE:[si]
	IOdelay
	OutWord
	inc	si
	inc	ax
	loop	@B
	mov	cl,[PortTable][3 * SIZE PortRec].prNumRegs
	mov	si,offset AttrRegs
	pushf				; Save interrupt flag state
	WaitRetrace			; Also disables interrupts
	mov	al,ch			; Restore index (0)
	mov	dl,AttCtrlAddrReg AND 0FFh ; Restore dx to AttrAddr

@@:
	mov	ah,CODE:[si] 		; Get data
	IOdelay
	OutWordAttr	,NoInts		; Write index/data to AttrAddr
	inc	si
	inc	ax
	loop	@B
	mov	al,PaletteAddressSource	; Since dx still has AttrAddr,
	IOdelay
	out	dx,al			; enable video now
	IOdelay
	InitFlipFlop	NoSaveAX	; Reset FF and get FeatAddr!
	popf				; Restore interrupt flag state
	IOdelay
	mov	al,[FeatureReg] 	; Since dx still has FeatAddr,
	out	dx,al			; program it now
	IOdelay
	mov	dl,MiscAddr AND 0FFh
	mov	al,[MiscOutReg]
	out	dx,al
	cmp	[fVga],CL		; If VGA is present,
	jne	@F			;  skip GR1&2 processing
	mov	dl,Gr1PosAddr AND 0FFh
	mov	al,[GR1PosReg]
	IOdelay
	out	dx,al
	IOdelay
	mov	dl,Gr2PosAddr AND 0FFh
	mov	al,[GR2PosReg]
	out	dx,al

@@:
	pop	di			; Restore environment
	pop	dx			; Restore environment
	pop	cx			; Restore environment
	ret

RestoreContext	endp

	page

;
; GetLatchLocation - dump current EGA.SYS context data to user buffer
;
; ENTRY
;	None
; EXIT
;	If currently in graphics mode
;		DI -> Latch location
;	Else (Text mode)
;		DI = 0
; DESTROYS
;	AX
;

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

GetLatchLocation	proc	near

	xor	di,di			; Assume text mode
	mov	al,[biosmode]		; Get current video mode
	and	al,01111111b		; Reset noclear bit
	cmp	al,13h			; Is it a mode we can handle?
	ja	@F			; No - skip (fake text mode)
	sub	al,0dh			; Adjust to zero base
	js	@F			; Skip if text mode
	xor	ah,ah			; No high byte
	add	di,ax			; Position to video mode in table
	mov	di,CODE:[di] + offset EGALatchTable ; Get desired latch location

@@:
	ret

GetLatchLocation	endp

	page

;
; GetFontInfo - dump current font data in FontInfo format to user buffer
;
;	GetInfo is provided for environments like Windows that need to know
;	which alpha fonts have been downloaded and which banks they are in.
;
;	This call copies the current EGA.SYS FontInfo structure to a user
;	buffer pointed to by es:bx.  Based on this information, the caller can
;	determine the need to save alpha font data in plane 2, as well as
;	determine the most efficient way to do it.  For example, font ID's
;	001h and 002h need not be saved since a copy exists in the EGA ROM.
;
;	Graphics font data is maintained by the EGA BIOS via int 01Fh and int
;	043h and does not exist in the EGA hardware.  Since these interrupts
;	can be directly manipulated for Save/Restore operations, EGA.SYS does
;	not attempt to record any graphics font information.
;
;	FontInfo format:
;
;	FontInfo	struc
;	  fibank0	db	?
;	  fibank1	db	?
;	  fibank2	db	?
;	  fibank3	db	?
;	FontInfo	ends
;
;	where each fiBankx contains a byte defined as follows:
;
;	000h	-  user font in specified bank
;	001h	-  08x14 ROM font in specified bank (Default for EGA)
;	002h	-  08x08 ROM font in specified bank
;	004h	-  08x16 ROM font in specified bank (Default for VGA)
;	0FFh	-  empty bank
;
; ENTRY
;	es:bx	-> user buffer for FontInfo
; EXIT
;	none
; DESTROYS
;	ax
;

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

GetFontInfo	proc	near

	mov	ax,word ptr [FontBank][0]
	mov	es:[bx],ax
	mov	ax,word ptr [FontBank][2]
	mov	es:[bx][2],ax
	ret

GetFontInfo	endp

;
; GetInBiosFlag - return segment:offset of the InBiosFlag
;
; ENTRY
;	none
; EXIT
;	es:bx	->  InBiosFlag
; DESTROYS
;	none
;

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

GetInBiosFlag	proc	near

	mov	bx,cs
	mov	es,bx
	assume	es:CODE
	mov	bx,offset fInBIOS
	ret

GetInBiosFlag	endp

	subttl	InquireDriver
	page

;
; InquireDriver - return ptr to driver version number
;
; ENTRY
;	none
; EXIT
;	es:bx	-> DriverInfo data area
; DESTROYS
;	None
;

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

InquireDriver	proc	near

	mov	bx,ds
	mov	es,bx
	assume	es:CODE
	mov	bx,offset DriverInfo
	ret

InquireDriver	endp

ifdef	Sys
	include	int10rtn.inc		; Contains Int10Routine and Int2FRoutine
					; Also in load.inc for .COM version
endif	; Sys

EndOfResidentCode	label	near

;
; I N C L U D E S
;

	include	load.inc

CODE	ends

	end	main

⌨️ 快捷键说明

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