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

📄 eisapnp.nvm

📁 award bios 源代码,喜欢汇编程序及想研究主板BIOS程序的人可以参考哦.我是费了老大的劲才找到的哦.
💻 NVM
字号:
;	[]===========================================================[]
;
;	NOTICE: THIS PROGRAM BELONGS TO AWARD SOFTWARE INTERNATIONAL(R)
;	        INC. IT IS CONSIDERED A TRADE SECRET AND IS NOT TO BE 	
;	        DIVULGED OR USED BY PARTIES WHO HAVE NOT RECEIVED	
;	        WRITTEN AUTHORIZATION FROM THE OWNER.
;
; 	[]===========================================================[]
;

IF	BUS_TYPE EQ EISA_BUS
;[]========================================================================[]
;Procedure:	Ct_ESCD_Info
;Function :
;Input    :	SS:EBP = index structure
;			DWORD PTR [EBP+2] = pointer for MinESCDWriteSize(word)
;			DWORD PTR [EBP+6] = pointer for ESCDSize(word)
;			DWORD PTR [EBP+10] = pointer for NVStorageBase(dword)
;Output   :	CF = 0 successful
;		CF = 1 fail
;Registers:
;Note	  :
;[]========================================================================[]
		public	Ct_ESCD_Info
Ct_ESCD_Info	proc	near

;Minimum write storage size

		mov	di, [ebp+4]
		mov	es, di
		mov	di, [ebp+2]
		mov	word ptr es:[di], ESCD_SIZE

;Maximum storage size

		mov	di, [ebp+8]
		mov	es, di
		mov	di, [ebp+6]
		mov	word ptr es:[di], ESCD_SIZE

;Non-volatile storage 32-bit physical base address

		mov	di, [ebp+12]
		mov	es, di
		mov	di, [ebp+10]
		mov	dword ptr es:[di], 0h
		clc
		ret
Ct_ESCD_Info	endp

;[]========================================================================[]
;Procedure:	Ct_Get_ESCD
;Function :
;Input	  :
;		ES:DI = pointer for caller's ESCD buffer
;Output   :	CF = 0 successful
;		CF = 1 fail
;Registers:
;Note	  :
;		read the function information from int 15h and store it into the
;		EisaNVRAMCopy. This function should be called from AcfgInit()
;[]========================================================================[]
		public	Ct_Get_ESCD
Ct_Get_ESCD	proc	near
		pushad			
		push	ds		
		; ds:si should get the offset of the function information
		push	es
		push	di
		pop	si
		pop	ds

		mov	es:[di].ESCD_CFGHDR_Adr.wOffs,di	;save the address of
		mov	es:[di].ESCD_CFGHDR_Adr.wSegm,es	;CfgHdr structure

; reserve space for ESCD header
		call	init_CfgHdr			;initial CfgHdr structure
		add	si, TYPE ESCD_CFGHDR

		xor	cl,cl				;Start from slot 0

; repeat for each slot in the system
bn_while0_start:

		mov	es:[di].ESCD_BRDHDR_Adr.wOffs,si	;save the address of
		mov	es:[di].ESCD_BRDHDR_Adr.wSegm,ds	;BrdHdr structure

		; read EISA slot information: we care about the current contents of cx
		call	init_BrdHdr			;initial BrdHdr structure
		push	ds
		push	si
		push	cx
                push    es
                push    di
		mov	ax, EISA_SLOT_INFO
;int 15h
                call    EISA_Func_D8
                pop     di
                pop     es
		mov	es:[di].wBrdChksum, cx		;save checksum
		pop	cx				;cl is current slot number
		pop	si
		pop	ds
		jnc	short bn_card_present

; if the slot is corrupted, it is impossible to get ESCD.
		cmp	ah, NVM_CORRUPT
		je	short bnError

; if the slot is empty, there is no need to insert anything into the
; resource map. Since the Slot array already has all the slot records
; initialized as empty there is no need to call AcfgPackData.
		cmp	ah, EISA_SLOT_EMPTY
		jne	short bn_card_present

		or	cl,cl			;slot 0 ?
		je	short bnError

		jmp	short bn_while0_continue

bn_card_present:
		mov	es:[di].bCfgUtilMajorNum, bh
		mov	es:[di].bCfgUtilMinorNum, bl


bn_cfg_nums_saved:


		; reserve space for ESCD header
		add	si, TYPE ESCD_BrdHdr_S

; dh = the number of functions in the card
; get resource information about each function


		xor	ch,ch			       ;ch is function number to read

; repeat for each function in the card
bn_while1_start:

		cmp	ch, dh
		jae	short bn_while1_end

; cl is still the current slot number
; read EISA function information
;		mov	ax, EISA_FUNC_INFO		;use int 15 to detect
;		int	15h				;whether NVM is good

; Empty slot error should not happen
		call	get_packed_function
		jc	short bnError

		call	update_brdhdr
		or	ch,ch
		jnz	short bn_not_function0
		add	si,8
bn_not_function0:
		mov	ax,ds:[si]			;load current function length
		add	ax,2				;add length field
		add	si,ax				;point to header of next function

		inc	ch				;process next function
		jmp	short bn_while1_start

bn_while1_end:
		call	add_null_function
		add	si,4				;add length of null function

		call	update_cfghdr

bn_while0_continue:

		cmp	cl, max_slot-1
		je	short bn_while0_end

		inc	cl
		jmp	short bn_while0_start

bn_while0_end:

		les	di, es:[di].ESCD_CfgHdr_Adr
		mov	cx, es:[di]
		add	word ptr es:[di],2		;add 2 bytes of checksum
		xor	dx, dx
bn_while3_start:
		movzx	ax, BYTE PTR es:[di]		;Kuldge, double check checksum!
		add	dx, ax

		inc	di
		dec	cx
		jnz	short bn_while3_start
bn_while3_end:
		not	dx
		mov	ds:[si], dx


		clc

bnRet:
		pop	ds		
		popad			
		ret

bnError:
		stc
		jmp	short bnRet
Ct_Get_ESCD	endp


;[]--------------------------------------------------------------------------[]
;
; Procedure Name: EISA_Func_D8
;
;	This is the a substitution of the INT 15H D8 EISA extensions.
;
; Saves: All
;
; Inputs: AL - EISA D8 Subfunction
;	  Other registers depending upon Subfunction.
;
; Outputs: If no error
;		AL = 0
;		CY = 0
;		Other regs depend upon Subfunction
;	   If error
;		AL = Error Code (depends upon Subfunction)
;		CY = 1
;
; Notes: This procedure should be called in 16-bit mode only.  
;[]==========================================================================[]

EISA_Func_D8	PROC	NEAR
	cmp	al,MAX_SUBFUNC+1		;Is subfunction legal?
	jb	SHORT d8_chk_slot		;RobertH change	
;
; Subfunction was illegal
;
bad_func:
	mov	ah,INVALID_CALL			;Invalid subfunction
	stc
	jmp	SHORT eisa_exit

;
; Test if slot out of limit

d8_chk_slot:


; Don't do slot check if sub-function is less than 2

	cmp	al,2
	jae	d8_valid			;RobertH

	cmp	cl,MAX_SLOT+1   		;Is slot legal?
	jb	SHORT d8_valid	        	;Jump if yes ;RobertH change
;
; Subfunction was illegal
;
bad_slot:
	mov	ah,INVALID_SLOT			;Invalid subfunction
	stc
	jmp	SHORT eisa_exit

d8_valid:
	call	Func_D8				;Returns CY flag which will be 
						; placed in flag byte in stack
eisa_exit:
	ret

EISA_Func_D8	ENDP



;[]--------------------------------------------------------------------------[]
;
; Procedure Name: get_packed_function
;
;	Get the function information (FUNC_NUM) of slot (SLOT_NUM) in NVM.  
;	Write the information to the ESCD buffer
;
; Saves: Nothing
;
; Inputs:  CL: slot number
;          CH: function number
;          DS:SI point to return ESCD buffer
;	
;
; Outputs: AH
;	       00 - successful
;	       81H - invalid function number,
;	   CY set if not successful
;
; Author: Robert Hsiao
; Date: September 18, 1995
;[]==========================================================================[]
;
        public  get_packed_function
get_packed_function     PROC

        PUSHA

	MOV	AL,CL
	CALL    GET_NVMADDR		;Load DI with ptr to slot

	MOV	BX,DI			;Save start of slot
;
	ADD	DI,8			;1st NVM func length address
;
	MOV	DH,CH           	;Save function-to-extract number
	xor	dl,dl			;Current function (cycle upward)
aGFI2:
;-------- Check that function number valid before loading struct
;
; Get this function length (if = 0000, passed last function)
;
	CALL    READ_NVM_WORD
	or	ax,ax			;Last function?
	JNZ	SHORT aGFI25		;Jump if no
;	
	MOV	AH,INVALID_FUNC		;Function number too great
	JMP	short aGFIERROR		;Exit
aGFI25:
        ADD     AX,2                    ;Pass function-length
	CMP	DL,DH			;Reached function-to-extract?
	JZ	SHORT aGFI3		;Jump if yes (legal function)
;
	ADD	DI,AX			;Point at next function (length word)
	INC	DL			;Next function number
	JMP	SHORT aGFI2		;Continue
aGFI3:
;
; Start loading function information (ID and slot info, 8 bytes total)
;
	PUSH	DI
        PUSH    AX
;	MOV	SI,SI                   ;SI Pointer to buffer
	CALL    CLR_STRUCT		;Clear memory buffer
        OR      CH,CH                   ;First function
        JNZ     short aGF130            ;Skip header
	MOV	DI,BX			;NVM start
	MOV	CL,8			;Move 1st 8 bytes into buffer
	CALL    EXTRACT_INFO		;.
	ADD	SI,8
aGF130:
        POP     AX
	POP	DI	
	MOV	CX,AX
	CALL    EXTRACT_INFO		;Transfer TYPE field to structure
aGFI31:
	XOR	AH,AH			;Error code = successful
	CLC
	JMP	SHORT aXGFI		;Exit
;
; An error occured
;
aGFIERROR:
	STC
;
aXGFI:
        POPA
	ret
;
get_packed_function     endp

;[]========================================================================[]
;Procedure:	init_cfghdr
;Function :
;Input	  :	NONE
;Output   :
;Registers:
;Note	  :
;	  :
;[]========================================================================[]
init_cfghdr proc	 near
		ret
init_cfghdr	endp


;[]========================================================================[]
;Procedure:	update_cfghdr
;Function :
;Input	  :	CL: current slot number
;Output   :	NONE
;Registers:
;Note	  :	updates the ESCD configuration header. EISA SCD format does
;	  :	not contains information for ESCD configuration header;
;	  :	the header data is compiled from all slots on motherboard.
;	  :	In case of processing motherboard slot, it also initialize
;	  :	the configuration structure.
;	  :
;[]========================================================================[]
update_cfghdr	proc	near
		push	ds
		push	si
		push	es
		push	di
		lds	si,es:[di].ESCD_CfgHdr_Adr
		or	cl,cl
		jnz	short not_slot0
		mov	dword ptr ds:[si].dSignature,"GFCA"
		mov	ds:[si].bVerMinor,01
		mov	ds:[si].bVerMajor,02
		mov	ds:[si].wEscdSize,TYPE ESCD_CfgHdr
		mov	ds:[si].bBrdCnt,0

not_slot0:
		lds	si,es:[di].ESCD_BrdHdr_Adr
		mov	ax,ds:[si].wBrdSize_S
                lds     si,es:[di].ESCD_CfgHdr_Adr
		add	ds:[si].wEscdSize,ax
		add	ds:[si].bBrdCnt,1
		pop	di
		pop	es
		pop	si
		pop	ds
		ret
update_cfghdr	endp


;[]========================================================================[]
;Procedure:	init_brdhdr
;Function :
;Input	  :	NONE
;Output   :	NONE
;Registers:
;Note	  :	Initialize ESCD board header.
;	  :
;[]========================================================================[]
init_brdhdr	proc	near
		ret
init_brdhdr	endp


;[]========================================================================[]
;Procedure:	update_brdhdr
;Function :
;Input	  :
;	  :	CH:   current function
;Output   :	NONE
;Registers:
;Note	  :	updates the ESCD board header. EISA SCD format does
;	  :	not contains information for ESCD board header;
;	  :	the header data is compiled from all functions of the board.
;	  :	In case of processing the 1st function, it also initialize
;	  :	the board configuration structure.
;	  :
;[]========================================================================[]

update_brdhdr	proc	near
		push	es
		push	di
		push	ds
		push	si
		les	di,es:[di].ESCD_BrdHdr_Adr
		xor	ax,ax				;clear board size
		or	ch,ch
		jnz	short not_function0
		mov	es:[di].wBrdSize, 0		;clear board size
		mov	es:[di].bslotNum, cl		;Initialize slot number
		add	si,8				;advance 8 byte for func header
		add	ax,TYPE ESCD_BrdHdr		;add board header field

not_function0:
		add	ax,ds:[si].wFuncSize		;add func length field
		add	ax,2				;advance 2 byte for func length field

update_exit:
		add	es:[di].wBrdSize,ax
		pop	si
		pop	ds
		pop	di
		pop	es
		ret
update_brdhdr	endp

;[]========================================================================[]
;Procedure:	add_null_function
;Function :
;Input	  :	ds:si address of current function in ESCD buffer
;Output   :	NONE
;Registers:
;Note	  :	append a null function at end of board configuration block.
;	  :	the null function has function length 0 , followed by 2 bytes
;	  :	of checksum. Since the chceksum is not used by anyone, just
;	  :	filled with zero.
;	  :
;[]========================================================================[]

add_null_function   proc    near
		push	es
		push	di
		mov	ax,es:[di].wBrdChksum
		les	di,es:[di].ESCD_BrdHdr_Adr
		add	es:[di].wBrdSize,4
		mov	word ptr ds:[si],0
		mov	word ptr ds:[si+2],ax
		pop	di
		pop	es
		ret
add_null_function   endp


;[]========================================================================[]
;Procedure:	Ct_Set_ESCD
;Function :
;Input	  :	DS:SI = pointer for caller's ESCD buffer
;		ES = ESCD storage selector/segment (reported by Ct_ESCD_Info)
;		CX = length, no used in EISA case
;Output   :	CF = 0 successful
;		CF = 1 fail
;Registers:
;Note	  :
;	   Copies the contents of the slot array into the NVRAM.
;	   This routine is invoked at close time after the power-up copy of the
;	   NVRAM is found to be different from the NVRAMCopy.
;	   Individual writes are performed by int 15h calls

;[]========================================================================[]
		public	Ct_Set_ESCD
Ct_Set_ESCD	proc	near
		pusha

		push	ds
		push	si
                xor     cx, cx
		mov	ax, EISA_SLOT_INFO
;int 15h
                call    EISA_Func_D8
		pop	si
		pop	ds
		jnc	short wtn_card_present
                xor     bx, bx


wtn_card_present:
;		mov	es:[di].bCfgUtilMajorNum, bh
;		mov	es:[di].bCfgUtilMinorNum, bl

; clear NVRAM before writing to it.
; major/minor numbers are obtained from slot 0 header
		mov	ax, EISA_CLEAR_NVRAM
;int 15h
                call    EISA_Func_D8
                mov     ax, si                          ;load addr of ESCD head
                add     ax, ds:[si]                     ;add size of ESCD
                sub     ax, 2                           ;sub ESCD checksum
                mov     di, ax                          ;di point to end of ESCD
		add	si, TYPE ESCD_CFGHDR		;skip board header
; write all slots (including ones that are never modified by ACFG BIOS)
; Slots that are empty have cx initialized to zero.
		xor	bl,bl

wtn_while0_start:
		cmp	bl, ds:[si].bslotNum
		jne	short wtn_size_zero_slot
		mov	cx, ds:[si].wBrdSize		;Get total slot size
		push	cx
		push	si				;save the pointer of
							;curret board header
		add	si, TYPE ESCD_BrdHdr_S		;Exclude board header
		sub	cx, TYPE ESCD_BrdHdr_S		;Exclude board header

		mov	ax, EISA_WRITE_NVRAM
;int 15h
                call    EISA_Func_D8
		pop	si				;restore
		pop	cx
		jc	short wtn_error
		add	si, cx				;point to block of next board
		jmp	short wtn_next_slot

wtn_size_zero_slot:
		xor	cx, cx				;size is zero
		mov	ax, EISA_WRITE_NVRAM
;int 15h
                call    EISA_Func_D8
		jc	short wtn_error

wtn_next_slot:
                cmp     si, di
                jae     short wtn_while0_end            ;no more data to update
		cmp	bl, max_slot
		je	short wtn_while0_end

		inc	bl
		jmp	short wtn_while0_start

wtn_while0_end:

		clc

wtn_error:
		popa
		ret
Ct_Set_ESCD	endp

ENDIF	;BUS_TYPE EQ EISA_BUS

⌨️ 快捷键说明

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