please dont rip this site

Microchip 24LC16B 16Kb I2C RAM Driver

Ron Kreymborg


The following files demonstrate how to use the multi-byte read and write protocol of the Microchip 24LC16B 16Kb serial RAM chip. The complete test program consists of four files. The main program is 24LC_TST.ASM, and is here used only to show examples of how the RAM driver is called. The driver itself is 24LC.ASM and is simply included into your program, typically at the end. There are two definition files called RKMACROS.INC and TIMER.INC which are from my project toolbox. The former defines the macros used while the latter computes at compile time the required internal timer time constants. Both can be left out after appropriate editing of the source files. The programs are written in Microchip MPASM assembler and can be included in an MPLAB project.

Starting from address zero, the demonstration program writes BYTES bytes to the chip, reads them back, checks they are the same, increments the address by BYTES bytes, then does the same again until the entire 16Kb have been written, read and checked. In my project I am reading and writing eight bytes at a time to a data base on this chip, so by default the constant BYTES is here set to 8. However it can be set to any value in the range 1 to 16.

Note that the 24LC16 writes multiple bytes by incrementing only the low 4 bits of the address in its internal counter. Thus if the low address was 0xC0 you could write 16 bytes, but if was 0x7 you could only write 9 bytes (ie 16-7=9) before the counter overflowed and you started writing somewhere else. This means you can only write multiple data groups in a controlled way, where you know the destination starting address. The following table might make this a little clearer:

Start Address (hex) Possible Write Lengths
xxx0 1 thru 16
xxx1 1 thru 15
xxx2 1 thru 14
... ...
xxxD 1 thru 3
xxxE 1 thru 2
xxxF 1 only

It is usually easier to write in multiples of 2 (1,2,4,8 and 16) based on the address you start from. Thus if you always write in groups of 4 from a starting address of zero, the overflow problem will never arise. Of course it will also never arise if you always write one byte at a time no matter where you start from, but this is none too efficient. With a little extra work, you could consider the 24LC16 as a 1024 sector disk, with the 16-byte buffer in data memory as a sector cache which you maintain just like a disk cache, along with dirty bits and all.

Data is written from a structure with two more bytes than BYTES:

1 AAAAABBB AAAAA = number of bytes,
BBB = high 3 bits of address (ie the bank)
2 CCCCCCCC low 8 bits of address (0-255)
3 Byte[1] 1st byte of BYTES bytes
4 Byte[2] 2nd byte of BYTES bytes
... .. ..
BYTES+2 Byte[BYTES] Last byte

Reading is done to exactly the same type of structure, where the first 2 bytes define the address to be read. It can re-use the same address as the write structure if required.

If you connect an LED/resistor combination between RA2 and ground, it will blink briefly at the completion of a succesful write/read of the entire chip, and flash for 200mSecs for an error.

A zipped copy of these four files is available: 24LC.ZIP

Please refer all queries to Ron Kreymborg

RKMACROS.INC

	NOLIST
;******************************************************************
;
; A set of standard macros.
;
; Ron Kreymborg
;
;******************************************************************

intoff	macro
	bcf	intcon,gie
	btfsc	intcon,gie
	goto	$-2
	endm
bank0	macro
	bcf	STATUS,RP0
	endm
bank1	macro
	bsf	STATUS,RP0
	endm
dotris	macro	arg1, arg2
	bsf	STATUS,RP0
	movlw	arg1
	movwf	arg2
	bcf	STATUS,RP0
	endm
dodelay	macro	arg1
	movlw	arg1
	call	delay
	endm
	LIST

TIMER.INC

; PRESCL and TMRVAL computation
	NOLIST
; Take the processor clock frequency in Hz (clock), and
; the required time delay in uSecs (dusec), and compute
; a value for the prescaler (PRESCL) and another for
; TMR0 (TMRVAL).

_cycle	equ	clock >> 2
_dfreq	equ	1000000 / dusec
_divr	equ	_cycle / _dfreq
	if (_divr < 512)
	error "Delay time too short. Assign PSA to WDT."
	endif
_test	set	_divr / 256
_testB	equ	_divr % 256
	if (_testB > 0)
_test	set	_test + 1
	endif
	if (_test > 1)
_temp	set	2
PRESCL	set	0
	endif
	if (_test > 2)
_temp	set	4
PRESCL	set	1
	endif
	if (_test > 4)
_temp	set	8
PRESCL	set	2
	endif
	if (_test > 8)
_temp	set	16
PRESCL	set	3
	endif
	if (_test > 16)
_temp	set	32
PRESCL	set	4
	endif
	if (_test > 32)
_temp	set	64
PRESCL	set	5
	endif
	if (_test > 64)
_temp	set	128
PRESCL	set	6
	endif
	if (_test > 128)
_temp	set	256
PRESCL	set	7
	endif
	if (_test > 255)
	error "Timer requirement is outside range"
	endif
TMRVAL	equ	256 - (_cycle / _temp / _dfreq)
	LIST

24LC_TST.ASM

;******************************************************************
;
; Test program for Microchip 24LC16B RAM chip
;
; Takes about 660mSecs to write then read 16Kbytes @ 16bytes a time.
;
;******************************************************************

	title	"Main Routine Test Program"
	list p=pic16f84,r=dec,n=80,x=off,st=off
	include ‹p16f84.inc›
	include ‹rkmacros.inc›
	errorlevel -302		; no bank warnings
	errorlevel -305		; no default dest warnings

clock	equ	10000000	; my crystal frequency
dusec	equ	1000		; required delay (in uSecs)
	include	‹timer.inc›	; (note include must be after 
				;   previous two definitions)

	constant BYTES=8	; number of bytes to transfer
	constant BLOCKSIZE=BYTES+2
	
; Masks -

maska	equ	b'11110000'	; RA0 and RA1 are used by 24LC16 driver
				; RA2 and RA3 are free

; Data -
	CBLOCK	0xc		; start of data area
	dval			; delay cycle counter
	cntr			; general counter
	temp			; temporary storage
	w_data:BLOCKSIZE	; write data structure
	r_data:BLOCKSIZE	; read data structure
	lo_address		; low address (8 bits)
	hi_address		; high address (3 bits)
	spntr			; source data pointer
	dpntr			; destination data pointer
	ENDC

; Flags -

;****************************************************************

	org	0			; for future expansion
	goto	start			;
	org	4			;
	retfie				;
	
	
;****************************************************************
; Main program begins

start	clrwdt				; setup 1mSec timer
	bsf	STATUS,RP0
	movlw	b'11010000' | PRESCL	; prescaler to TMR0
	movwf	OPTION_REG
	bcf	STATUS,RP0
	dotris	0,PORTA			; PORTA all outputs for now
	clrf	PORTA

; Call initialisation routines

	call	preprw24		; initialise the 24LC16B driver

; Start the test code

mloop	clrf	hi_address		; start from zero in the ram
	clrf	lo_address
	
mn1	movlw	BYTES*8		; number of bytes
	addwf	hi_address,w	; add in page address
	movwf	w_data
	movwf	r_data

mn2	movf	lo_address,w
	movwf	w_data+1	; put in write structure
	movwf	r_data+1	; and read
	movlw	w_data+2	; start address of data
	movwf	FSR		; store for indirect
	movlw	BYTES		; fill data values
	movwf	cntr		; byte counter
	movlw	1
loop1	movwf	INDF		; w to indirect
	incf	FSR,f		; step pointer
	addlw	1		; step w
	decfsz	cntr,f
	goto	loop1		; for BYTES byte

	movlw	BYTES		; zero the read area
	movwf	cntr
	movlw	r_data+2	; start address of data
	movwf	FSR
loop2	clrf	INDF
	incf	FSR,f
	decfsz	cntr,f
	goto	loop2

; Do the read/write test

re_wrt	movlw	w_data		; address of write data structure
	call	write24		; go write it to eeprom
	btfss	STATUS,z	; success? (ie zero return?)
	goto	re_wrt		; no, re-write
	
re_read	movlw	r_data		; address of read data structure
	call	read24		; go read the eeprom
	btfss	STATUS,z	; success? (ie zero return?)
	goto	re_read		; no, re-read
	
; now check they are the same

check	movlw	BYTES
	movwf	cntr
	movlw	w_data+2	; written data
	movwf	spntr		; make write pointer
	movlw	r_data+2	; read data
	movwf	dpntr		; make read pointer
chk1:	movf	dpntr,w		; read pointer
	movwf	FSR		; to FSR
	movf	INDF,w		; get read data
	movwf	temp		; save in temp
	incf	dpntr,f		; step pointer
	movf	spntr,w		; written pointer
	movwf	FSR		; to FSR
	movf	INDF,w		; compare with temp
	subwf	temp,f		; same?
	btfss	STATUS,z
	goto	bad		; no match!!
	incf	spntr,f		; step pointer
	decfsz	cntr,f
	goto	chk1

; Phew!

chk2	movlw	BYTES		; step low address by BYTES
	addwf	lo_address,f
	btfss	STATUS,z	; skip if went to zero
	goto	mn2		; around again
	incf	hi_address,f	; step high address to next page
	btfss	hi_address,3	; gone to 4?
	goto	mn1		; no

	bsf	PORTA,2		; blip a led on RA2 to say all is well
	dodelay	5	
	bcf	PORTA,2
	goto	mloop
	
bad	bsf	PORTA,2		; long blink for error
	dodelay	200
	bcf	PORTA,2		; copy to lcd
	goto	chk2
	

;****************************************************************
; Delay routine using the internal timer. Will delay for W
; times the value of ‹dusec› in microseconds.

delay	movwf	dval
dy1	clrf	TMR0
	bcf	INTCON,T0IF
	movlw	TMRVAL			; set timer
	movwf	TMR0
dy2	btfss	INTCON,T0IF		; timer overflow yet?
	goto	dy2			; no
	decfsz	dval,f			; yes, all cycles?
	goto	dy1			; no
	return				; yes, delay finished


;****************************************************************
; Includes

	include	<24lc.asm>
	
	end

24LC.ASM

;****************************************************************
;
; Multi-byte Read and Write routines for the Microchip 24LC16B.
;
; Data is written from a structure:
;      AAAAABBB      AAAAA = number of bytes, 
;                    BBB = high 3 bits of address (ie bank)
;      CCCCCCCC      low 8 bits of address (0-255)
;      BYTE-1        1st byte of data
;      BYTE-2
;      etc
;
; Reading is done to exactly the same type of structure, with 
; only the first 2 bytes requiring definition. It can be at the
; same address as the write structure if required.
;
; A constant must be defined called BYTES that represents the
; number of bytes to transfer during a read or write (1-16).
; If the structure started at w_data, it could be prepared as:
;
;        movlw    BYTES*8       ; BYTES in hi 5
;        addwf    hi_addr,w     ; hi part of address in lo 3
;        movwf	  w_data,f
;        movf     lo_addr,w
;        movwf    w_data+1,f
;
; Note that the 24LC16 writes multiple bytes by incrementing
; only the low 4 bits of the address. Thus if the low address
; was 0xC0 you could write 16 bytes, but if was 0x7 you could
; only write 9 bytes (ie 16-7=9). This means you can only write
; data groups in multiples of 2 (1,2,4,8 and 16).
;
; Initialisation requires RA0 and RA1 be set up as outputs.
; The routines require a mask be defined called  that
; defines how the other pins on porta are defined. For example,
; if RA3 is an output and RA2 an input, the mask would be:
; maska   equ    b'11110100'
; Note that RA0 and RA1 must be set to zero in this mask.
;
; As part of initialisation, call the following subroutine
; to set up RA0/RA1:
;         call    preprw24   ; set RA0/RA1
;
; A call to write24 is preceeded by loading W with the address of
; the write data structure. It will return with zero in W and the
; Z flag set for success. An error is indicated by a 1 in W and
; the Z flag cleared. Only possible error is 24LC16 busy, so
; just retry, either immediately or at some later time.
;
; A call to read24 requires the same setup as write24. Errors are
; also the same and should also be retried.
;
; The following Special Function Registers are used or modified
; in some way:
;       FSR
;       STATUS
;       PORTA, TRISA
;
; The routines use 3 levels of the stack in addition to the call. 
; You can use an INCLUDE to integrate this routine with your program.
;
; Ron Kreymborg, February 1998
;
;****************************************************************

maska	equ	b'11110000'	; RA0 and RA1 are used by read/write
				; RA2 is CRO synch line
				; RA3 is LED driver

	CBLOCK
	flags24			; general flags
	cont24			; control byte for 24LC16
	cntr24			; general counter
	bcntr24			; byte counter
	ENDC
	
; Flags -
rwbit24	equ	0		; high for read
ack24	equ	1		; high for valid ack
; Port A defs -
scl24	equ	0		; SCL clock line
sda24	equ	1		; SDA data line

;****************************************************************
; Write the data - enter with a pointer to the start of the write 
; data structure in W.

write24		call	setup24
		addlw	0		; success?
		btfss	STATUS,z	; (ie zero return?)
		goto	write24c	; no, error
write24a	movf	INDF,w		; get next byte
		movwf	cont24
		call	sendb24		; send it
		incf	FSR,f		; step to next
		decfsz	bcntr24,f
		goto	write24a	; around again
write24b	movlw	0		; no errors
write24c	call	stop24		; all done
		addlw	0		; force zero flag
		return


;****************************************************************
; Read the data - enter with a pointer to the start of the read 
; data structure in W.

read24		call	setup24		; send the two preamble bytes
		addlw	0		; success?
		btfss	STATUS,z	; (ie zero return?)
		goto	write24c	; no, error
		call	prestart24
		call	start24		; start again
		bsf	flags24,rwbit24	; now set for reading
		decf	FSR,f		; point back to structure start
		decf	FSR,f
		call	comm24		; send hi address again
		incf	FSR,f		; skip lo address, point to data area
	
read24a		movlw	8		; read in 8 bits
		movwf	cntr24
		call	sda_in24	; set SDA for reading
read24b		bcf	STATUS,c	; clear carry
		bsf	PORTA,scl24	; clock high
		btfsc	PORTA,sda24	; check sda
		bsf	STATUS,c	; set carry if high
		bcf	PORTA,scl24	; clock low
		rlf	INDF,f		; put carry into output byte
		decfsz	cntr24,f
		goto	read24b		; for all bits
		call	outall24	; make all outputs again
		bcf	PORTA,sda24	; ensure SDA low
		decf	bcntr24,f	; all bytes?
		btfsc	STATUS,z
		goto	write24b	; yes, send stop

read24d		bsf	PORTA,scl24	; send ack unless last byte
		nop			; not really needed at 4MHZ
		bcf	PORTA,scl24	; clock low again
		incf	FSR,f		; step to next place
		goto	read24a		; get next byte
	

;****************************************************************
; Common subroutines. These are the I2C routines.

setup24		movwf	FSR		; setup pointer
		bcf	flags24,rwbit24	; set for writing
		call	start24
		call	comm24		; send hi address
		btfsc	flags24,ack24	; continue only if valid ack
		retlw	1		; return error
		movf	INDF,w		; get low address byte
		movwf	cont24
		call	sendb24		; send it
		incf	FSR,f		; step on to start of data
		retlw	0
	
	
comm24		bcf	flags24,ack24	; clear ack bit
		movf	INDF,w		; get 1st byte of structure
		movwf	cntr24		; save temporarily
		rrf	cntr24,f	; get byte count
		rrf	cntr24,f
		rrf	cntr24,w
		andlw	0x01f
		movwf	bcntr24		; make a counter
		movf	INDF,w		; get 1st byte again
		addwf	INDF,w		; shift left one bit
		andlw	0x0e		; mask to 3 bits
		btfsc	flags24,rwbit24	; reading or writing?
		addlw	1		; set R/W bit if required
		addlw	0xa0		; attention bits
		movwf	cont24		; put in control byte
		call	sendb24		; send control byte
		incf	FSR,f		; step on to low address
		return
	


; Clock out the byte in ‹cont24›.

sendb24		movlw	8		; 8 bits
		movwf	cntr24
sendb24a	rlf	cont24,f	; bit 7 into carry
		btfsc	STATUS,c	; is it 1?
		bsf	PORTA,sda24	; yes, set SDA high
		bsf	PORTA,scl24	; clock high
		nop			; not really needed at 4MHZ
		bcf	PORTA,scl24	; clock low
		bcf	PORTA,sda24	; ensure SDA low
		decfsz	cntr24,f
		goto	sendb24a
	
; now check for an aknowledge

		call	sda_in24	; make SDA input now
		bsf	PORTA,scl24	; clock high
		btfsc	PORTA,sda24	; ack from 24LC16?
		bsf	flags24,ack24	; yes, set ack bit
		bcf	PORTA,scl24	; clock low
;		bcf	PORTA,sda24	; ensure is low
		call	outall24	; SDA output again
		return
	
	
start24		bcf	PORTA,sda24	; data low for start condition
		nop			; setup time
		bcf	PORTA,scl24	; now clock low
		return
	

stop24		bsf	PORTA,scl24	; stop sequence
		nop
		bsf	PORTA,sda24
		return


outall24	bsf	STATUS,rp0
		movlw	maska		; SDA and SDL are outputs
		movwf	TRISA
		bcf	STATUS,rp0
		return


sda_in24	bsf	STATUS,rp0
		movlw	maska + b'10'	; SDA is input for reading
		movwf	TRISA
		bcf	STATUS,rp0
		return
		
		
preprw24	call	outall24	; make SDA /SCL outputs
prestart24	bsf	PORTA,sda24	; establish pre-start
		nop
		bsf	PORTA,scl24
		return
		


file: /Techref/mem/eeprom/24x16/Kreymborg.htm, 18KB, , updated: 2002/9/18 20:33, local time: 2024/3/28 05:34,
TOP NEW HELP FIND: 
44.221.43.88: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://www.ecomorder.com/techref/mem/eeprom/24x16/Kreymborg.htm"> 24LC16B Drivers</A>

After you find an appropriate page, you are invited to your to this massmind site! (posts will be visible only to you before review) Just type a nice message (short messages are blocked as spam) in the box and press the Post button. (HTML welcomed, but not the <A tag: Instead, use the link box to link to another page. A tutorial is available Members can login to post directly, become page editors, and be credited for their posts.


Link? Put it here: 
if you want a response, please enter your email address: 
Attn spammers: All posts are reviewed before being made visible to anyone other than the poster.
Did you find what you needed?

 

Welcome to ecomorder.com!

 

Welcome to www.ecomorder.com!

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

  .