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

📄 spdi2c.asm

📁 X86 GX1 BOOTLOAD代码 ,支持WINCE操作系统!
💻 ASM
📖 第 1 页 / 共 2 页
字号:
;**************************************************************************
;*
;*  SPDI2C.ASM
;*
;*  Copyright (c) 1999 - 2000 National Semiconductor Corporation.
;*  All Rights Reserved.
;*
;*  Function:
;*    Support routines for reading the SPD on SDRAM.
;*
;*  $Revision:: 1   $
;*
;**************************************************************************

	;.MODEL TINY
	.486P


	INCLUDE DEF.INC
	INCLUDE MACROS.INC
	INCLUDE PORT80.INC
	INCLUDE CPU.INC
	INCLUDE OPTIONS.INC



_TEXT SEGMENT PUBLIC use16 'CODE'

OFF_FLAG	EQU 001h
ACK_FLAG	EQU	002h

;**************************************************************************
;*
;*	csI2C_Read
;*
;*	(STACKLESS)
;*
;*	This routine performs a Read Operation on the I2C interface.
;*	The protocol is as follows:
;*	  1) Issue a START condition
;*	  2) Write out the Slave address i.e. the EEPROM address
;*	  3) Check for ACK
;*	  4) Read in the data w/Ack
;*	  5) Go back to #4 if more bytes to read
;*	  6) Issue STOP
;*
;*	Entry:
;*		BH = Offset
;*		BL = chip address
;*		CH  = Control flag 
;*				bit 0 : 1 = send offset, 0 = don't
;*				bit 1 : 1 = Acknowledge 0 = don't
;*				bits 2-7 : reserved
;*		CL = Number of bytes to read
;*		DX = return address
;*		ES:DI = Pointer to buffer to stick the data (if CL > 4)
;*
;*	Exit:
;*	  EBX = data read (1, 2, 3, or 4 bytes) (if CL <= 4) otherwise 0
;*    ES:DI = pointer to data read (if CL > 4)
;*		CF=0 success
;*		CF=1 failure BH = ERROR
;*			BH = 01h	Invalid size ( CL = 0 )
;*			BH = 02h	I2C Comm Error
;*			BH = 03h	Buffer address wrap 
;*
;*	Destroys:
;*	  EAX, EBX, ECX, EDX, EDI, BP, SI
;*
;**************************************************************************
csI2C_Read PROC NEAR PUBLIC

	; Save Parameters
	mov	bp, dx						; Save return address in BP

	mov	ah, 001h					; Size error
	cmp	cl, 0						; 0 bytes?
	stc								; Default to error (CY set)
	je	abortGet					; yes, get out (ZF checked)

	rol	ebx, 16						; save flags (CH) and count (CL) in EBX
	mov bx, cx				
	ror	ebx, 16
	
	; Call I2C Initialization Procedure
	NOSTACK	si, csInitI2C			; Set up GPIO pins in CX55XX, uses EAX, DX

	test ch, OFF_FLAG
	jz	csI2C_Skip_Off

	; Prepare to send offset
	; Need to initiate a dummy write (write without data)
	mov	eax, ebx					; preserve BX in upper EAX
	shl	eax, 16

	; Start Condition
	NOSTACK	si, csStartCondition	; uses AX, DX

	; Write EEPROM address
	and	bl, 0FEh					; force it to be a write
	NOSTACK	si, csWriteI2CData		; BL => write data, uses AX, BL, CX, DX
	mov	ah, 002h					; default to comm error
	jc	abortGet					; check for comm error

	; Write Offset address
	shr	bx, 8
	NOSTACK	si, csWriteI2CData		; BL => write data, uses AX, BL, CX, DX
	mov	ah, 002h					; default to comm error
	jc	abortGet					; check for comm error

	shr eax, 16						; restore BX
	mov bx, ax

csI2C_Skip_Off:

	; Start Condition
	NOSTACK	si, csStartCondition	; uses AX, DX

	; Write EEPROM address
	or	bl, 001h					; Make it a read
	NOSTACK	si, csWriteI2CData		; BL => write data, uses AX, BL, CX, DX
	mov	ah, 002h					; default to comm error
	jc	abortGet					; check for comm error

	shr	ebx, 16						; get flags (BH) and count (BL)
	movzx cx, bl					; set count

	IOPAUSE
	IOPAUSE

	ror	edi, 16						; save DI
	mov	di,	bx						; BH = flags
	shr	di, 8
	rol	edi, 16						; restore DI

	cmp	cl, 4						; more than 4 bytes?
	ja	csI2C_Top_Big				; yes, do big read

	mov	di, cx						; Save # bytes in EDI
	rol	edi, 16						; move count to upper EDI and restore flags
	xor	ebx, ebx					; clear EBX for data coming in

csI2C_Top:
	cmp	cx, 1
	ja	@f
	and	di, NOT ACK_FLAG			; last byte clear ACK flag
@@:

	shl ecx, 16						; save CX

	; Read the Data, DI setup with Ack flag
	NOSTACK	si, csRealReadI2CData	; Read Data => BL, uses AX, BX, CX, DX
	ror	ebx, 8
	shr	ecx, 16						; restore CX
	loop csI2C_Top					; Go back if more

	; Perform final shift to get data into correct position
	; (4-count) * 8 = shift factor
	ror	edi, 16						; Get byte count back
	mov	cx, 4						; 4	
	sub	cx, di						; - count
	shl	cx, 3						; * 8 => CL = shift factor
	ror	ebx, cl						; shift first byte down
	jmp	csI2C_Read_End

csI2C_Top_Big:
	ror	edi, 16						; save DI pointer/restore flags
	cmp	cx, 1
	ja	@f
	and	di, NOT ACK_FLAG			; last byte clear ACK flag
@@:

	shl ecx, 16						; save CX

	; Read the Data w/Acknowledge
	NOSTACK	si, csRealReadI2CData	; Read Data => BL, uses AX, BX, CX, DX

	rol	edi, 16						; restore DI pointer/save flags
	mov	es:[di], bl
	inc	di

	cmp	di, 0						; Check for address wrap
	stc								; default to error (sets CY)
	mov	ah, 003h					; buffer address wrap error
	je	abortGet					; check ZF 

	shr	ecx, 16						; restore CX
	loop csI2C_Top_Big				; Go back if more

	xor	ebx, ebx					; clear EBX

csI2C_Read_End:
	; Stop Condition
	NOSTACK	si, csStopCondition

	mov	ah, bh						; save BH so it isn't destroyed below
	clc								; Indicate success

abortGet:
	mov	bh, ah						; mov error code (or data) to BH
	jmp	bp			; Return to calling address
csI2C_Read ENDP

;**************************************************************************
;*
;*	csI2C_ReadStack
;*
;*	This routine calls csI2C_Read (above) and saves/restores
;*	registers
;*
;*	Entry:
;*	  BL = chip address
;*	  CL = Number of bytes to read
;*	  DX = return address
;*	  ES:DI = Pointer to buffer to stick the data
;*
;*	Exit:
;*	  EBX = data read (1, 2, 3, or 4 bytes) if (CL <= 4) otherwise 0
;*    ES:DI = data read (if CL > 4)
;*		CF=0 success
;*		CF=1 failure BH = ERROR
;*			BH = 01h	Invalid size ( CL = 0 )
;*			BH = 02h	I2C Comm Error
;*			BH = 03h	Buffer address wrap 
;*
;*	Destroys:
;*	  EBX
;*
;**************************************************************************
csI2C_ReadStack PROC NEAR PUBLIC

	; Save Registers
	pushad

	; Call stackless procedure
	NOSTACK	dx, csI2C_Read

	; Restore Registers
	mov	DWORD PTR ss:[esp+16], ebx	; Hack EBX onto stack
	popad

	ret
csI2C_ReadStack ENDP

;**************************************************************************
;*
;*	csGetSPDByte
;*
;*	For backward compatibility, see csReadINDEXEDbyte for details
;*
;*	Entry:
;*	Exit:
;*	Destroys:
;*
;**************************************************************************
csGetSPDByte PROC NEAR PUBLIC
	jmp	csReadINDEXEDbyteStack
csGetSPDByte ENDP

;**************************************************************************
;*
;*	csReadINDEXEDbyte
;*
;*	(STACKLESS)
;*
;*	This routine performs a Randon Read Operation on the I2C interface.
;*	The protocol is as follows:
;*	  1) Issue a START condition
;*	  2) Write out the Slave address i.e. the EEPROM address
;*	  3) Check for ACK
;*	  4) Write out the offset to read
;*	  5) Check for ACK
;*	  6) Issue a START condition
;*	  7) Write out the Slave address
;*	  8) Check for ACK
;*	  9) Read in the data
;*	 10) Issue STOP
;*
;*	This is a wrapper for the real procedure.  If fixes the count at 1
;*	and request the offset to be sent
;*
;*	Entry:
;*	  BL = chip address
;*	  CL = byte address to access
;*	  DX = return address
;*
;*	Exit:
;*		BL = Data read
;*		CF=0 success BH = 0
;*		CF=1 failure BH = ERROR
;*			BH = 01h	Invalid size ( CL = 0 )
;*			BH = 02h	I2C Comm Error
;*			BH = 03h	Buffer address wrap 
;*
;*	Destroys:
;*	  EAX, EBX, ECX, EDX, EDI, BP, SI
;*
;**************************************************************************
csReadINDEXEDbyte PROC NEAR PUBLIC
	; Adjust some parameters and call the read procedure
	mov	bh, cl
	mov	cx, 00101h		; CH= Ack=0, offset=1 and CL=write 1 byte
	jmp	csI2C_Read
csReadINDEXEDbyte ENDP

;**************************************************************************
;*
;*	csReadINDEXEDbyteStack
;*
;*	This routine calls csReadINDEXEDbyte (above) and saves/restores
;*	registers.  See above for details.
;*
;*	Entry:
;*	  BL = chip address
;*	  CL = register address
;
;*	Exit:
;*		BL = Data read
;*		CF=0 success BH = 0
;*		CF=1 failure BH = ERROR
;*			BH = 01h	Invalid size ( CL = 0 )
;*			BH = 02h	I2C Comm Error
;*			BH = 03h	Buffer address wrap 
;*
;*	Destroys:
;*		BX
;*
;**************************************************************************
csReadINDEXEDbyteStack PROC NEAR PUBLIC

	; Save Registers
	pushad

	; Call Above PROC
	NOSTACK	dx, csReadINDEXEDbyte

	; restore all while preserving BH
	mov	eax, DWORD PTR ss:[esp+16]
	mov	ax, bx
	mov	DWORD PTR ss:[esp+16], eax
	popad
	ret
csReadINDEXEDbyteStack ENDP

;**************************************************************************
;*
;*	csReadI2CBlockStack 
;*
;*	See above csI2C_Read for details
;*
;*	Entry:  
;*		CH = chip address
;*		CL = register
;*		DL = number of bytes to transfer
;*		ES:DI = pointer to buffer 
;*
;*	Exit:
;*    ES:DI = pointer to data read
;*		CF=0 success
;*		CF=1 failure
;*
;*	Destroys:
;*	  nothing only flags changed
;*
;**************************************************************************
csReadI2CBlockStack PROC NEAR PUBLIC
	pushad

	mov	bh, cl		; Offset
	mov bl, ch		; Address
	mov	ch, 003h	; Ack=1,  offset=1
	mov	cl, dl		; # of bytes
	push cx			; save count
	push di			; save DI

	NOSTACK	dx, csI2C_Read
	pop	di			; restore DI
	pop	cx			; restore count
	jc	csRIBS_Done	; error? get out

	; no error, adjust data
	mov	ch, 0		; wipe out address
	cmp	cl, 4
	ja	csRIBS_Done

	; 4 or less bytes, move data from EBX to ES:DI
@@:
	mov	BYTE PTR es:[di], bl
	shr	ebx, 8
	inc	di
	loop @b
	clc				; indicate success

csRIBS_Done:
	; Update BH on the stack before restoring other registers
	;mov	eax, DWORD PTR ss:[esp+16]
	;mov	ah, bh
	;mov	DWORD PTR ss:[esp+16], eax
	popad
	ret
csReadI2CBlockStack ENDP

;**************************************************************************
;*
;*	csI2C_Write
;*
;*	(STACKLESS)
;*
;*	This routine performs a Write Operation on the I2C interface.
;*	The protocol is as follows:
;*	  1) Issue a START condition
;*	  2) Write out the Slave address i.e. the EEPROM address
;*	  3) Check for ACK
;*	  4) Write offset if requested
;*	  5) Write out the data
;*	  6) Check for ACK
;*	  7) Go back to 5 until all bytes are used
;*	  8) Issue STOP
;*
;*	Entry:
;*		BH  = byte offset
;*		BL	= chip address
;*		CH  = Control flag 
;*				bit 0 : 1 = send offset, 0 = don't
;*				bits 1-7 reserved
;*		CL	= Number of bytes to write
;*		EAX	= data to write (1, 2, 3 or 4 bytes) if (CL <= 4)
;*		DX	= return address
;*		ES:DI = pointer to buffer (if CL > 4)
;*
;*	Exit:
;*		CF=0 success BH = 0
;*		CF=1 failure BH = ERROR
;*			BH = 01h	Invalid size ( CL = 0 )
;*			BH = 02h	I2C Comm Error
;*			BH = 03h	Buffer address wrap 
;*
;*	Destroys:
;*	  EAX, EBX, ECX, EDX, EDI, BP, SI
;*
;**************************************************************************
csI2C_Write PROC NEAR PUBLIC
	mov	bp, dx			; Save return address in BP

	; Save inputs while we go off and do some work
	ror	ebx, 16			; preserve BH and BL
	mov	bx, cx

	mov ecx, eax		; save data in upper ECX and EDX
	mov dx, cx
	shl	edx, 16

	mov	ah, 001h		; Set size error
	cmp	bl, 0			; Perform size check before losing size in EBX
	rol ebx, 16			; restore BH and BL
	stc					; default to error (CY set)
	je	abortWrite		; yes, get out (ZF checked)

	; Call I2C Initialization Procedure
	NOSTACK	si, csInitI2C

	; Start Condition
	NOSTACK	si, csStartCondition

	; Write EEPROM address
	and	bl, 0FEh				; Make it a write
	NOSTACK	si, csWriteI2CData	; BL = Write data
	mov	ah, 002h				; default to comm error
	jc	abortWrite

	ror	ebx, 16					; bring the control flags in range
	test bh, 001h				; test for offset
	rol	ebx, 16
	jz	csI2CWrite_Skip_Off

	; Write byte offset
	shr	bx, 8					; shift BH => BL
	NOSTACK	si, csWriteI2CData	; BL = Write data
	mov	ah, 002h				; default to comm error
	jc	abortWrite

csI2CWrite_Skip_Off:
	ror	edx, 16					; restore data (Upper EDX to CX)
	mov cx, dx					; ECX now has all the data
	rol	edx, 16					; put DX back
	xchg ecx, ebx				; mov data to EBX and get count back to ECX
	shr	ecx, 16					; shift count to CX

	mov ch, 000h				; clear control flags
	cmp	cx, 4
	ja	csI2CWrite_Top_Big

csI2C_Write_Top:
	shl	ecx, 16					; save CX

	; Write the data
	NOSTACK	si, csWriteI2CData	; BL = Write data
	mov	ah, 002h				; default to comm error
	jc	abortWrite				; Acknowledge bit set?

	shr	ebx, 8
	shr	ecx, 16					; restore CX
	loop csI2C_Write_Top
	jmp	csI2CWrite_End

csI2CWrite_Top_Big:
	shl	ecx, 16					; save CX

	; Write the data
	mov	bl, es:[di]
	NOSTACK	si, csWriteI2CData	; BL = Write data
	mov	ah, 002h				; default to comm error
	jc	abortWrite				; Acknowledge bit set?

	inc	di
	cmp	di, 0
	stc
	mov	ah, 003h				; buffer address wrap error
	je	abortWrite

	shr	ebx, 8
	shr	ecx, 16					; restore CX
	loop csI2CWrite_Top_Big

csI2CWrite_End:
	; Stop Condition
	NOSTACK	si, csStopCondition
	xor	ax, ax
	clc

abortWrite:
	mov	bx, ax		; mov error code (if any)
	jmp	bp			; Return to calling address
csI2C_Write ENDP

;**************************************************************************
;*
;*	csI2C_WriteStack
;*
;*	This routine calls csI2C_Write (above) and saves/restores
;*	registers
;*
;*	Entry:
;*		BH  = byte offset or 0 (don't send offset)
;*		BL	= chip address
;*		CH  = Control flag 
;*				bit 0 : 1 = send offset, 0 = don't
;*				bits 1-7 reserved
;*		CL	= Number of bytes to write
;*		EAX	= data to write (1, 2, 3 or 4 bytes) if (CL <= 4)
;*		DX	= return address
;*		ES:DI = pointer to buffer (if CL > 4)
;*
;*	Exit:
;*		CF=0 success BH = 0
;*		CF=1 failure BH = ERROR
;*			BH = 01h	Invalid size ( CL = 0 )
;*			BH = 02h	I2C Comm Error
;*			BH = 03h	Buffer address wrap 
;*
;*	Destroys:
;*	  BH
;*
;**************************************************************************
csI2C_WriteStack PROC NEAR PUBLIC
	pushad

	NOSTACK	dx, csI2C_Write

	; restore all while preserving BH
	mov	eax, DWORD PTR ss:[esp+16]
	mov	ah, bh
	mov	DWORD PTR ss:[esp+16], eax
	popad

	ret
csI2C_WriteStack ENDP

;**************************************************************************
;*
;*	csWriteINDEXEDbyte
;*
;*	(STACKLESS)
;*
;*	This routine performs a Write Operation on the I2C interface.
;*
;*	The protocol is as follows:
;*	  1) Issue a START condition
;*	  2) Write out the Slave address i.e. the EEPROM address
;*	  3) Check for ACK
;*	  4) Write offset if requested
;*	  5) Write out the data
;*	  6) Check for ACK
;*	  7) Go back to 5 until all bytes are used
;*	  8) Issue STOP
;*
;*	This is a wrapper for the real procedure.  If fixes the count at 1
;*	and request the offset to be sent
;*
;*	Entry:
;*	  BL = chip address
;*	  CL = byte address to access
;*	  AL = byte to write
;*	  DX = return address
;*
;*	Exit:
;*		CF=0 success BH = 0
;*		CF=1 failure BH = ERROR
;*			BH = 01h	Invalid size ( CL = 0 )
;*			BH = 02h	I2C Comm Error
;*			BH = 03h	Buffer address wrap 
;*
;*	Destroys:
;*	  EAX, EBX, ECX, EDX, EDI, BP, SI
;*
;**************************************************************************
csWriteINDEXEDbyte PROC NEAR PUBLIC
	; Adjust some parameters and call the write procedure

⌨️ 快捷键说明

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