please dont rip this site

IO I2C I2C.TXT

_PROGRAMMING THE I2C INTERFACE_
by Mitchell Kahn


[LISTING ONE]

$pagelength (30)
$mod186
$debug
$xref

NAME 	i2c_transmit;

$include (\include\pcp_io.inc)

PUBLIC i2c_xmit

;******   EQUates  ******    
BUS_FREE_MIN	        EQU	2       ; Loop counter for free bus delay.
MAXIMUM_MESSAGE_LEN     EQU     255

CODE_ILLEGAL_ADDR       EQU     020H
CODE_MSG_LEN            EQU     040H

;****** STACK FRAME STRUCTURE ******
stack_frame     STRUC
ret_ip          DW      ?
ret_cs          DW      ?
buffer_offset   DW      ?
buffer_segment  DW      ?
count           DW      ?
address         DW      ?
stack_frame     ENDS

%*DEFINE(Drive_SCL_Low)(
        mov     dx, P2LTCH
        in      al, dx
        and     al, 10111111B           ; SCL is bit 6
        out     dx, al
        )
%*DEFINE(Release_SCL_High)(
        mov     dx, P2LTCH
        in      al, dx
        or      al, 01000000B
        out     dx, al
        )
%*DEFINE(Drive_SDA_Low)(
        mov     dx, P2LTCH
        in      al, dx
        and     al, 01111111B           ; SDA is bit 6
        out     dx, al
        )
%*DEFINE(Release_SDA_High)(
        mov     dx, P2LTCH
        in      al, dx
        or      al, 10000000B
        out     dx, al
        )
%*DEFINE(Wait_4_7_uS)(
        mov     cx, 5
        loop    $
        nop
        nop
        )
%*DEFINE(Wait_Half_Bit_Time)(
        mov     cx, 3
        loop    $
        )
%*DEFINE(Wait_SCL_Low_Time)(
        mov     cx, 5
        loop    $
        nop
        nop
        )
%*DEFINE(Wait_SCL_High_Time)(
        mov     cx, 5
        loop    $
        nop
        nop
        )
%*DEFINE(Wait_For_SCL_To_Go_Low)LOCAL wait(
        mov     dx, P2PIN
%wait:  in      al, dx
        test    al, 01000000B
        jne     %wait
        )
%*DEFINE(Wait_For_SCL_To_Go_High)LOCAL wait(
        mov     dx, P2PIN
%wait:  in      al, dx
        test    al, 01000000B
        je      %wait
%*DEFINE(Wait_For_SDA_To_Go_High)LOCAL wait(
        mov     dx, P2PIN
%wait:  in      al, dx
        test    al, 10000000B
        je      %wait
        )
        )
%*DEFINE(Get_SDA_Bit)(
        mov     dx, P2PIN
        in      al, dx
        and     al, 0080H
        )
%*DEFINE(Check_For_Bus_Free)(
        mov	dx, P2PIN
	in	al, dx
        mov     bl, 0C0H         ; Mask for SCL and SDA.
        and     al, bl           ; If SCL and SDA are high
        xor     al, bl           ; this sequence will leave a zero in AX.
        )

;*****************************************************************************
;**  Revision History: 0.0 (7/90): First frozen working verion. No slave wait 
;**    timeout. No arbitration turn around.  Inefficient register usage. 
;**    0.1 (7/16/90): 8-bit registers used (improves  80C188EB. Use STRUCT for
;**    stack frame clarity. Implements slave wait timeout. Saves ES.  
;*****************************************************************************

;*****************************************************************
;**                     Procedure I2C_XMIT                      **
;**             Call Type:      FAR                             **
;**             Uses     :      All regs.                       **
;**             Saves    :      DS and ES only.                 **
;**             Stack Frame:                                    **
;**             [bp]=   ip                                      **
;**             [bp+2]= cs                                      **
;**             [bp+4]= message offset                          **
;**             [bp+6]= message segment                         **
;**             [bp+8]= message count                           **
;**             [bp+10]= slave adress                           **
;**             Return Codes in AX register:                    **
;**             XX00 = Transmisiion completed without error     **
;**             XX01 = Bus unavailable                          **
;**             XX02 = Addressed slave not responding           **
;**             nn04 = Addressed slave aborted during xfer      **
;**                    (nn= number of bytes transferred before  **
;**                     transfer aborted)                       **
;**             XX08 = Arbitration loss (note 1)                **
;**             XX10 = Bus wait timeout                         **
;**             XX20 = Illegal address                          **
;**             XX40 = Illegal message count                    **
;**             note 1: Arbitration loss requires that the      **
;**                     I2C unit switch to slave receive        **
;**                     mode.  This is not implemented.         **
;*****************************************************************

code    	segment  public
                assume cs:code
i2c_xmit	proc	far
                mov     bp, sp
                push    ds
                push    es
                test    word ptr [bp].address,01H       ; Check for illegal
                                                        ; address (a READ).
                jz      addr_ok
                mov     ax, CODE_ILLEGAL_ADDR           ; Illegal addr
                pop     es
                pop     ds
                ret     8                       ; Tear down stack frame
addr_ok:    
                mov	cx, [bp].count          ; Get message length.
                cmp     cx, MAXIMUM_MESSAGE_LEN
                jle     message_len_ok          ; Message is 256 or less
                                                ; characters.
                mov     ax, CODE_MSG_LEN        ; Bad length return code.
                pop     es
                pop     ds
                ret     8
message_len_ok:
                mov     si, [bp].buffer_offset  ; Get message offset.
                mov     ax, [bp].buffer_segment ; Get message segment
                mov     ds, ax                  ; and put in DS.
		; Test for I2C bus free condition.
                ; SCL and SDA must be high at least 4.7uS
                mov     cx, BUS_FREE_MIN        ; initialize free time counter.
                
                ; The following loop takes 48 clocks while cx>1 and 33 clocks 
                ; on the last iteration. To insure that bus is free, samples 
                ; of bus must span at least 4.7uS. At 16Mhz: 48*(62.5ns)=3uS 
                ; The first sample is at 0us, the second at 3us, and the 
                ; third will be at 6.  Although this exceeds the 4.7us
                ; spec, it is better safe than sorry.
bus_free_wait:
                %Check_For_Bus_Free
                jz     i2c_bus_free
                ; At this point the bus is not available.
                mov     ax, 01H                 ; 01= return code for
                pop     es                      ; a busy bus.
                pop     ds
                ret     8                       ; return and tear down
                                                ; stack frame.
i2c_bus_free:   loop    bus_free_wait		; bus may be free but wait 
	                                	; the 4.7uS required!
                ; I2C bus is available, generate a START condition
                %Drive_SDA_Low
                %Wait_4_7_uS
                mov     ax, [bp].address
                xchg    ah, al                  ; ah = address
next_byte:	mov	di, 8			; set up bit counter
next_bit:	%Drive_SCL_Low
                %Wait_Half_Bit_Time		
		mov	bl, ah  		; get current data
		and	bl, 080H		; strip MSB
		mov	dx, P2LTCH
		in	al, dx
		and	al, 7fh
		or	al, bl			; set bit 7 to reflect
						; data bit
		out	dx, al			; xmit data bit
                %Wait_Half_Bit_Time
                %Release_SCL_High
                %Wait_For_SCL_To_Go_High

                ; At this point SCL is high so if there is another master 
                ; attempting to gain the bus, it's data would be valid here.  
                ; We need only check when our data is "1"...

                test    bl, 80H            ; Is data a "1"?
                jz      won_arbitration    ; If not -> don't check arbitration.

                mov     dx, P2PIN
                in      al, dx
                test    al, 80H                 ; Is SDA high?
                jnz     won_arbitration
                jmp     lost_arbitration        ; If SDA != 1 then we lost
                                                ; arbitration....
won_arbitration:
                %Wait_SCL_High_Time
		shl	ah, 1                   ; shift current byte
                dec	di			; tick down bit counter
		jne	next_bit		; continue bits
; a byte has been completed.  Time to get an ACKNOWLEDGE.
                %Drive_SCL_Low
                %Wait_Half_Bit_Time
                %Release_SDA_High
                %Wait_Half_Bit_Time
                %Release_SCL_High
                %Wait_For_SCL_TO_Go_High
                ; SCL is now high.  We must loop while checking SDA for 4.7us.  
                ; With a count of 3 we have a delay of 89 clocks (5.5uS). This 
                ; could be find tuned with NOPs when performance is critical.
                mov     cx, 3
check_4_ack:
                %Get_SDA_Bit                    ; Is SDA a "0"
		jnz	abort_no_ack		; if so -> abort
		loop	check_4_ack 
; if we've gotten to here, then an acknowledge was received.
                mov     ah, byte ptr [si]
		inc	si			; point to next byte
                dec	word ptr [bp].count	; dec string counter
		js      xfer_done
                jmp	next_byte
; END OF MESSAGE: Issue a STOP condition
xfer_done:      
                mov     di, 0                   ; Normal completion code.
                jmp     i2c_bus_stop
abort_no_ack:
                cmp     si, [bp].buffer_offset  ; Check if this is the
                je      slave_did_not_respond   ; first byte (the address ).
                mov     di, 4H                  ; Abort during xfer code.
                jmp     i2c_bus_stop
slave_did_not_respond:
                mov     di, 02H                 ;
i2c_bus_stop:
                %Drive_SCL_Low
                %Wait_Half_Bit_Time
		%Drive_SDA_Low
	        %Wait_4_7_uS
                %Release_SCL_High
                %Wait_For_SCL_To_Go_High
                %Wait_4_7_uS
                %Release_SDA_High
                %Wait_For_SDA_To_Go_High

                mov     ax, di
                pop     es
                pop     ds
                ret     8                       ; Return and tear
                                                ; down stack frame.
lost_arbitration:
                mov     dx, P2LTCH
                in      al, dx                  ; Release SDA and SCL
                or      al, 0C0H
                out     dx, al 
                mov     ax, 08H                 ; Lost arbitration code.
                pop     es
                pop     ds
                ret     8
i2c_xmit	endp
code 		ends
end


[LISTING TWO]

$pagelength (30)
$mod186
$debug
$xref

NAME    i2c_receive;

$include (/include/pcp_io.inc)

PUBLIC i2c_recv

;****** EQUates ******
BUS_FREE_MIN     EQU     1H             ; Loop counter for free bus delay.
MAXLEN           EQU     255

;****** STACK FRAME STRUCTURE  ******
stack_frame     STRUC
ret_ip          DW      ?
ret_cs          DW      ?
buffer_offset   DW      ?
buffer_segment  DW      ?
count           DW      ?
address         DW      ?
stack_frame     ENDS

%*DEFINE(Drive_SCL_Low)(
        mov     dx, P2LTCH
        in      al, dx
        and     al, 10111111B           ; SCL is bit 6
        out     dx, al
        )
%*DEFINE(Release_SCL_High)(
        mov     dx, P2LTCH
        in      al, dx
        or      al, 01000000B
        out     dx, al
        )
%*DEFINE(Drive_SDA_Low)(
        mov     dx, P2LTCH
        in      al, dx
        and     al, 01111111B           ; SDA is bit 6
        out     dx, al
        )
%*DEFINE(Release_SDA_High)(
        mov     dx, P2LTCH
        in      al, dx
        or      al, 10000000B
        out     dx, al
        )
%*DEFINE(Wait_4_7_uS)(
        mov     cx, 5
        loop    $
        nop
        nop
        )
%*DEFINE(Wait_Half_Bit_Time)(
        mov     cx, 3
        loop    $
        )
%*DEFINE(Wait_SCL_Low_Time)(
        mov     cx, 5
        loop    $
        nop
        nop
        )
%*DEFINE(Wait_SCL_High_Time)(
        mov     cx, 5
        loop    $
        nop
        nop
        )
%*DEFINE(Wait_For_SCL_To_Go_Low)LOCAL wait(
        mov     dx, P2PIN
%wait:  in      al, dx
        test    al, 01000000B
        jne     %wait
        )
%*DEFINE(Wait_For_SCL_To_Go_High)LOCAL wait(
        mov     dx, P2PIN
%wait:  in      al, dx
        test    al, 01000000B
        je      %wait
%*DEFINE(Wait_For_SDA_To_Go_High)LOCAL wait(
        mov     dx, P2PIN
%wait:  in      al, dx
        test    al, 10000000B
        je      %wait
        )
        )
%*DEFINE(Get_SDA_Bit)(
        mov     dx, P2PIN
        in      al, dx
        and     al, 0080H
        )
%*DEFINE(Check_For_Bus_Free)(
        mov dx, P2PIN
    in  al, dx
        mov     bl, 0C0H                ; Mask for SCL and SDA.
        and     al, bl                  ; If SCL and SDA are high
        xor     al, bl                  ; this sequence will leave
        )                               ; a zero in AX.
code    segment  public
        assume cs:code

i2c_recv    proc    far

              ; The LSB of the address for a READ always has a "1" in the LSB.
              ; The first step is to check for a legal address....
                mov     bp, sp
                push    ds
                push    es
                test    word ptr [bp].address,01H    ; Check for illegal
                                                     ; address (an XMIT).
                jnz     addr_ok
                ; The address passed was for a transmit (WRITE). This is 
                ; illegal in this procedure....    
                mov     ax, 20H                 ; Illegal addr
                pop     es
                pop     ds
                ret     8                       ; Tear down stack frame
addr_ok: 
                cmp     word ptr [bp].count, MAXLEN
                jg      message_wrong_len
                cmp     word ptr [bp].count, 1  ; check message length
                jge     len_ok
message_wrong_len:
                mov     ax, 40H                 ; error code
                pop     es
                pop     ds
                ret     8                       ; tear down frame
len_ok:
                ; Test for I2C bus free condition.
                ; SCL and SDA must be high at least 4.7uS
                mov     cx, BUS_FREE_MIN        ; initialize free time counter.
; Following loop takes 48 clocks while cx>1 and 33 clocks on last iteration. 
; To insure that bus is free, samples of bus must span at least 4.7uS. At 16Mhz
; 48*(62.5ns)= 3uS. First sample is at 0us, second at 3us, and third will be at
; 6. Although this exceeds 4.7us spec, it is better safe than sorry.
bus_free_wait:
                %Check_For_Bus_Free
                jz     i2c_bus_free
                ; At this point the bus is not available.
                mov     ax, 01H                 ; 01= return code for
                pop     es                      ; a busy bus.
                pop     ds
                ret     8             ; return and tear down stack frame.
i2c_bus_free:   loop    bus_free_wait ; bus may be free but wait 4.7uS required
                ; I2C bus is available, generate a START condition
                %Drive_SDA_Low
                %Wait_4_7_uS
                ; A receive begins with transmission of the ADDRESS
            mov di, 8           ; set up bit counter
next_bit:   
        %Drive_SCL_Low
        %Wait_Half_Bit_Time
                mov     bx, [bp].address
        and bl, 080H        ; strip MSB
        mov dx, P2LTCH
        in  al, dx
        and al, 7fh
        or  al, bl          ; set bit 7 to reflect data bit
        out dx, al          ; xmit data bit
        sal [bp].address,1          ; shift current byte
                %Wait_Half_Bit_Time
                %Release_SCL_High
                %Wait_For_SCL_To_Go_High
                ; At this point SCL is high so if there is another master 
                ; attempting to gain the bus, it's data would be valid here. 
                ; We need only check when our data is a "1"...
                test    bl, 10000000B      ; Is data a "1"?
                je      won_arbitration    ; If not -> don't check arbitration.
                mov     dx, P2PIN
                in      al, dx
                test    al, 10000000B           ; Is SDA high?
                jnz     won_arbitration
                jmp     lost_arbitration
won_arbitration:
                %Wait_4_7_uS                ; count off high time.
        dec di          ; tick down bit counter
        jne next_bit        ; continue bits
; The address has been completed.  Time to get an ACKNOWLEDGE.
                %Drive_SCL_Low
                %Wait_Half_Bit_Time
                %Release_SDA_High
                %Wait_Half_Bit_Time
                %Release_SCL_High
; Here we are expecting to see an acknowledge from addressed slave receiver:
        %Wait_For_SCL_To_Go_High        ; a wait state
        mov cx, 3
check_4_ack:
        mov dx, P2PIN
        in  al, dx          ; get SDA value
        and al, 10000000B       ; is it high?
        jnz abort_no_ack        ; if so -> abort
        nop
        nop
        nop                             ; NOPs for timing at 16Mhz
                loop    check_4_ack 
; if we've gotten to here, then an acknowledge was received.
; At this point in the code, slave receiver has acknowledged
; receipt of its address. SCL has just been driven low, SDA is floating.
                jmp     start_recv
abort_no_ack:
                %Drive_SCL_Low
                mov     di, 02H                 ; Code for unresponsive slave.
                jmp     i2c_bus_stop
; Now the master transmitter switches to master receiver....
start_recv:
                mov     di, [bp].buffer_offset
                mov     ax, [bp].buffer_segment
                mov     es, ax
next_byte_r:    mov     bx, 0
                mov     si, 8
next_bit_r:    
                %Drive_SCL_Low
                %Wait_4_7_uS
                %Release_SCL_High
                %Wait_For_SCL_To_Go_High
                %Get_SDA_Bit
                shr     al, 7                   ; move SDA value to LSB
                or      bl, al                  ; drop in lsb of bl
                %Wait_4_7_uS
        dec si              ; tick down bit counter
        je  byte_Recv_comp      ; continue bits
                shl     bl, 1                   ; shift bl for next bit
                jmp     next_bit_r
; The word has been completed.  Time to send an ACKNOWLEDGE.
byte_Recv_comp:
                mov     al, bl
                stosb
        %Drive_SCL_Low
                %Wait_Half_Bit_Time
; Here we need to decide whether or not to transmit an acknowledge. If this is 
; last byte required from slave, we do not send an ack; otherwise we do....
                dec     [bp].count              ; decrement the message count
                cmp     [bp].count, 0
                jne     send_ack
                %Release_SDA_High
                jmp     do_ack
send_ack:       %Drive_SDA_Low

do_ack:     
        %Wait_Half_Bit_Time
                %Release_SCL_High
        %Wait_For_SCL_To_Go_High
                %Wait_4_7_uS
                %Drive_SCL_Low
                %Wait_Half_Bit_Time
                %Release_SDA_High
                cmp     [bp].count, 0
                je      recv_done
                jmp     next_byte_r
recv_done:      mov     di, 00

i2c_bus_stop:
                %Wait_Half_Bit_Time
        %Drive_SDA_Low
            %Wait_4_7_uS
                %Release_SCL_High
                %Wait_For_SCL_To_Go_High
                %Wait_4_7_uS
                %Release_SDA_High
                %Wait_For_SDA_To_Go_High
                mov     ax, di
                pop     es
                pop     ds
                ret     8              ; Return and tear down stack frame.
lost_arbitration:
                mov     dx, P2LTCH
                in      al, dx                  ; Release SDA and SCL
                or      al, 0C0H
                out     dx, al 
                pop     es
                pop     ds
                ret     8
i2c_recv    endp
code        ends
end



[LISTING THREE]

$mod186        
$debug
$xref

$include (\include\pcp_io.inc)  ; a file of EQUates for 186EB register names

NAME    i2c_example
EXTRN   i2c_recv:far, i2c_xmit:far

%*DEFINE(XMIT(ADDR,COUNT,MESSAGE))(
        push    %ADDR
        push    %COUNT
        push    seg %MESSAGE
        push    offset %MESSAGE
        call    i2c_xmit
        )
%*DEFINE(RECV(ADDR,COUNT,BUFFER))(
        push    %ADDR
        push    %COUNT
        push    seg %BUFFER
        push    offset %BUFFER
        call    i2c_recv
        )
stack   segment stack
        DW      20 DUP (?)
 t_o_s  DW      0
stack   ends
data    segment para public 'RAM'
bus_msg     db  00h,77h,01h,02h,04h,08h  ; the LED I2C message 
recv_buff       db      255 dup(?)
data            ends
usr_code        segment para 'RAM'
                assume cs:usr_code
start:          mov     ax, data                ; data segment init
                mov     ds, ax
                cli
                assume ds:data
                mov     ax, stack               ; set up stack
                mov     ss, ax
                assume ss:stack
                mov     sp, offset t_o_s
                mov     dx, P2DIR               ; set up open-drain 
                in      ax, dx                  ; port pins on 186EB
                and     ax, 3FH         
                out     dx, ax
                mov     dx, P2CON
                in      ax, dx
                and     ax, 03FH
                out     dx, ax
                ; The I2C address of the LED driver is 70H for a transmit.
                %XMIT(70H,6,bus_msg)            ; send "bus" message
                ; The address for the clock is 0xA3 for a receive.
                %RECV(0A3H,15,recv_buff)   ; read first 15 bytes in clock chip.
usr_code        ends
                end     start





Example 1: (a) 80C186 implementation of 4.7uS wait macro; (b) 80960CA 
implementation of 4.7uS wait macro.


(a)


%*DEFINE(Wait_4_7_uS)(
        mov     cx, 5           ; 4 clocks 
        loop    $               ; 4*15+5 = 65 clocks
        nop                     ; 3 clocks
        nop                     ; 3 clocks
                                ; total = 75 clocks
                                ; 75 * 62.5ns = 4.69uS (close enough)
        )


(b)


define(Wait_4_7_uS,'            
        
        lda     0x17, r4        # instruction may be issued in parallel
                                # so assume no clocks. 
0b:     cmpdeco 0, r4           # compare and decrement counter in r4
        bne.t   0b              # if !=0 branch back (predict taken
                                # branch)
                                #
                                # The cmpdeco and bne.t together take 3
                                # clocks in parallel minimum.
                                #
                                # 0x17 (25 decimal) * 3 = 75 clocks
                                # at 16MHz this is 4.69uS
')





file: /Techref/io/i2c/i2c.txt, 23KB, , updated: 1992/5/18 08:04, local time: 2024/3/18 19:00,
TOP NEW HELP FIND: 
54.226.222.183:LOG IN

 ©2024 These pages are served without commercial sponsorship. (No popup ads, etc...).Bandwidth abuse increases hosting cost forcing sponsorship or shutdown. This server aggressively defends against automated copying for any reason including offline viewing, duplication, etc... Please respect this requirement and DO NOT RIP THIS SITE. Questions?
Please DO link to this page! Digg it! / MAKE!

<A HREF="http://techref.massmind.org/techref/io/i2c/i2c.txt"> io i2c i2c</A>

Did you find what you needed?

 

Welcome to massmind.org!

 

Welcome to techref.massmind.org!

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

  .