please dont rip this site

PIC 16F876 USART, I2C, EERAM read/write, port setup, ISR, and full initialization sample program

from Tony Kübek of Flintab AB [tony.kubek at flintab.com]

;**********************************************************************
;                Something to do with a PIC                           *
;**********************************************************************
;                                                                     *
;    Filename:	    	snipp.asm                                    *
;    Date: 		2000-09-19                                    *
;    File Version:  	0.1B                                          *
;                                                                     *
;    Author: 		Tony Kübek                                    *
;    Company:           Flintab AB                                    *
;                                                                     * 
;                                                                     *
;**********************************************************************
;                                                                     *
;    Files required:                                                  *
;                                                                     *
;                                                                     *
;                                                                     *
;**********************************************************************
;                                                                     *
;    Notes:                                                           *
;                                                                     *
;**********************************************************************


	list      p=16f876            ; list directive to define processor
	#include <p16f876.inc>        ; processor specific variable definitions
	#include <macros.asm>         ; macro definitions


	__CONFIG _CP_OFF & _WDT_OFF & _BODEN_OFF & _PWRTE_ON & _HS_OSC & _WRT_ENABLE_ON & _LVP_OFF& _DEBUG_ON & _CPD_OFF 

; '__CONFIG' directive is used to embed configuration data within .asm file.
; The lables following the directive are located in the respective .inc file.
; See respective data sheet for additional information on configuration word.

; turn off crossing page boundary message
	ERRORLEVEL -306, -302


; base frequency
XTAL_FREQ	EQU	20000000	; OSC freq in Hz

; caulculates baudrate when BRGH = 1, adjust for rounding errors
#define CALC_HIGH_BAUD(BaudRate)	(((10*XTAL_FREQ/(16*BaudRate))+5)/10)-1
; caulculates baudrate when BRGH = 0, adjust for rounding errors
#define CALC_LOW_BAUD(BaudRate)		(((10*XTAL_FREQ/(64*BaudRate))+5)/10)-1

; caulculates timer1 delay when prescale is 1:8, adjust for rounding errors
#define CALC_TIMER(TickTime)	(0xFFFF-((TickTime*XTAL_FREQ)/32000))+1
; used for I2C calculations
#define  I2CClock    D'100000'           ; define I2C bite rate
#define  I2C_ClockValue  (((XTAL_FREQ/I2CClock)/4) -1) ; 


;***** RAM VARIABLES DEFINITIONS

	; *** Bank0 *** 80 bytes
	CBLOCK	0x020			
	Main_Temp:3			; temporary variables in main loop ( 3 byte ! )

	Temp:1				; temp byte ONLY to be used locally and no calls !
	EE_Byte:1			; for reading/writing to eeram
	ENDC
	
	; *** Bank0/1/2/3 mirrored in all banks 0x70, 0xF0, 0x170, 0x1F0, 16 bytes
	CBLOCK	0x070
	ICD_Reserved1:1	; for icd
	; ram variables accesible from all banks mainly used for context saving
	; ( ram area above 0x70 are mirrored in all banks )
	Saved_W:1    	; variable used for context saving 
	Saved_Status:1  ; variable used for context saving
	Saved_Pclath:1	; 
	Saved_Fsr:1	;
	Table_Temp:1	; table lookup temp variable
	ENDC
	
	; *** Bank1 *** 80 bytes
	CBLOCK	0x0A0

	ENDC

	; *** Bank2 *** extra ram 16 bytes
	CBLOCK	0x110
	
	ENDC

	; *** Bank2 ***	80 Bytes
	CBLOCK	0x120
	ENDC

	; *** Bank3 *** extra ram 16 bytes
	CBLOCK	0x190

	ENDC
	; *** Bank3 *** 80 bytes
	CBLOCK	0x1A0

	ENDC
	CBLOCK	0x1EB
	ICD_Reserved2:5 ; for icd
	ENDC
	

; ****************** Macro definitions ********************************
;+++++
;	PAGE/BANK0/1/2/3 selects register bank 0/1/2/3.
;	Leave set to BANK0 normally.

BANK0	MACRO
	BCF	STATUS,RP0	; clear bank select bits
	BCF	STATUS,RP1
	BCF	STATUS,IRP	; clear indirect adressing bit
	ENDM

BANK1	MACRO
	BSF	STATUS,RP0	; 
	BCF	STATUS,RP1	; 
	BCF	STATUS,IRP	; clear indirect adressing bit
	ENDM

BANK2	MACRO
	BCF	STATUS,RP0	; 
	BSF	STATUS,RP1
	BSF	STATUS,IRP	; set bit for indirect adressing
	ENDM

BANK3	MACRO
	BSF	STATUS,RP0	;
	BSF	STATUS,RP1
	BSF	STATUS,IRP	; set bit for indirect adressing
	ENDM
	; macros for accessing page's directly
PAGE0	MACRO
	BCF	PCLATH,3
	BCF	PCLATH,4
	ENDM

PAGE1	MACRO
	BSF	PCLATH,3
	BCF	PCLATH,4
	ENDM

PAGE2	MACRO
	BCF	PCLATH,3
	BSF	PCLATH,4
	ENDM

PAGE3	MACRO
	BSF	PCLATH,3
	BSF	PCLATH,4
	ENDM

;+++++
;	TABLE_JUMP Calculates an eventuntual table boundary crossing  
;	set's up the PCLATH register correctly
;	Offset must be in w-reg, offset 0 jumps to the next instr. 
;
TABLE_JUMP	MACRO	
	MOVWF	Table_Temp	; save wanted offset
	MOVLW	LOW($+8)	; get low adress ( of first instr. after macro )
	ADDWF	Table_Temp,F	; add offset
	MOVLW	HIGH($+6)	; get highest 5 bits ( of first instr. after macro )
	BTFSC	STATUS,C	; page crossed ? ( 256 byte )
	ADDLW	0x01		; Yes add one to high adress
	MOVWF	PCLATH		; load high adress in latch
	MOVF	Table_Temp,W	; get computed adress
	MOVWF   PCL	           ; And jump
	ENDM

;+++++
;	SET_PCLATH 'help' macro for LONG_CALL
;	Set's/clears PCLATH bits 3:4 according to 
; 	'variable' PCLATH_34
;  	
SET_PCLATH	MACRO   PCLATH_34
	IF(PCLATH_34&0x10)
	BSF	PCLATH,4	
	ELSE
	BCF	PCLATH,4
	ENDIF
	IF(PCLATH_34&0x08)
	BSF	PCLATH,3	
	ELSE
	BCF	PCLATH,3
	ENDIF
	ENDM

;+++++
;	SET_PCLATH4 'help' macro for LONG/SHORT_CALL
;	Set's/clears PCLATH bit 4 according to 
; 	'variable' PCLATH_4
;  	
SET_PCLATH4	MACRO   PCLATH_4
	IF(PCLATH_4&0x10)
	BSF	PCLATH,4	
	ELSE
	BCF	PCLATH,4
	ENDIF
	ENDM

;+++++
;	SET_PCLATH3 'help' macro for LONG/SHORT_CALL
;	Set's/clears PCLATH bit 3 according to 
; 	'variable' PCLATH_3
;  	
SET_PCLATH3	MACRO   PCLATH_3
	IF(PCLATH_3&0x08)
	BSF	PCLATH,3	
	ELSE
	BCF	PCLATH,3
	ENDIF
	ENDM

;+++++
;	LONG_CALL long call, sets the page bits 4:5 of PCLATH
;	so call can cross ANY page boundary, reset's PCLATH after call.
; 	w-reg is left untouched.

LONG_CALL	MACRO	LABEL	
	LOCAL	DEST_HIGH, SOURCE_HIGH, DIFF_HIGH

DEST_HIGH  	SET	(HIGH(LABEL)&0x18)  	; save bit's 4:5 of dest adress
SOURCE_HIGH	SET	(HIGH($)&0x18)		; --- || ---  source adress
DIFF_HIGH	SET     DEST_HIGH ^ SOURCE_HIGH ; get difference ( XOR )

	IF	(DIFF_HIGH == 0) ; same page, SHOULD generate no extra code, delta 0 pages
	MESSG	"Call on same page, replace LONG_CALL with PCALL " LABEL
	NOP	; redundant NOP's 
	NOP
	CALL	LABEL
	NOP
	NOP
	ELSE	
		; test if both bits must be set ? i.e. page0<->page3 or page2<->page3
		IF	(DIFF_HIGH == 0x18) ; difference in BOTH bit's, delta 2 pages
		;MESSG  "Setting page bit's for long page crossing call"
		SET_PCLATH	DEST_HIGH   ; set both bits in PCLATH
		CALL	LABEL		
		SET_PCLATH	SOURCE_HIGH ; reset both bits in pclath	
		ELSE
			; if we end up here then one BSF/BCF is enough, i.e. delta 1 page
			; i.e. page0<->1 or page2<->3
			MESSG "Call only one page, replace LONG_CALL with SHORT_CALL " LABEL
			IF	(DIFF_HIGH == 0x10) ; diff in high bit
			NOP	; redundant NOP
			SET_PCLATH4 	DEST_HIGH ; set high(4) bit of PCLATH
			CALL	LABEL
			SET_PCLATH4	SOURCE_HIGH
			NOP	; redundant NOP
			ELSE
			; lowest bit only
			NOP	; redundant NOP
			SET_PCLATH3 	DEST_HIGH ; set low(3) bit of PCLATH
			CALL	LABEL
			SET_PCLATH3	SOURCE_HIGH
			NOP
			ENDIF
		ENDIF
	ENDIF
	
	ENDM

;+++++
;	SHORT_CALL short call, code for calling between page0<->1 or page2<->3
;	Reset's PCLATH after call.
; 	w-reg is left untouched.

SHORT_CALL	MACRO	LABEL	
	LOCAL	DEST_HIGH, SOURCE_HIGH, DIFF_HIGH
DEST_HIGH  	SET	(HIGH(LABEL)&0x18)  	; save bit's 4:5 of dest adress
SOURCE_HIGH	SET	(HIGH($)&0x18)		; --- || ---  source adress
DIFF_HIGH	SET     DEST_HIGH ^ SOURCE_HIGH ; get difference ( XOR )

	IF	(DIFF_HIGH == 0) ; same page, SHOULD generate no extra code, delta 0 pages
	MESSG	"Call on same page, replace SHORT_CALL with PCALL " LABEL
	NOP	; redundant NOP's 
	CALL	LABEL
	NOP
	ELSE	
		; for safety check so we do not require LONG_CALL
		IF	((DIFF_HIGH&0x18)==0x18)
		MESSG  " WARNING ! Replace SHORT_CALL with LONG_CALL " LABEL
		ENDIF

		;MESSG  "Setting page bit's for short page crossing call"
		IF	(DIFF_HIGH == 0x10) ; diff in high bit
		SET_PCLATH4 	DEST_HIGH ; set high(4) bit of PCLATH
		CALL	LABEL
		SET_PCLATH4	SOURCE_HIGH
		ELSE
		; lowest bit only
		SET_PCLATH3 	DEST_HIGH ; set low(3) bit of PCLATH
		CALL	LABEL
		SET_PCLATH3	SOURCE_HIGH
		ENDIF
	ENDIF
	
	ENDM

;+++++
;	PCALL page call, code for calling on same page
;	outputs messages if LONG/SHORT call could/must be used
;

PCALL	MACRO	LABEL	
	LOCAL	DEST_HIGH, SOURCE_HIGH, DIFF_HIGH
DEST_HIGH  	SET	(HIGH(LABEL)&0x18)  	; save bit's 4:5 of dest adress
SOURCE_HIGH	SET	(HIGH($)&0x18)		; --- || ---  source adress
DIFF_HIGH	SET     DEST_HIGH ^ SOURCE_HIGH ; get difference ( XOR )

	IF	(DIFF_HIGH == 0) ; same page, call ok
	CALL	LABEL
	ELSE	
		; for safety check so we do not require LONG_CALL
		IF	((DIFF_HIGH&0x18)==0x18)
		MESSG  " WARNING ! Replace PCALL with LONG_CALL " LABEL
		CALL	LABEL	; INCORRECT Call !!!
		ELSE
		MESSG  " WARNING ! Replace PCALL with SHORT_CALL " LABEL
		CALL	LABEL
		ENDIF
	ENDIF
	
	ENDM


;+++++
;	PUSH/PULL save and restore W,PCLATH,STATUS and FSR registers -
;	used on interrupt entry/exit 

PUSH	MACRO
	MOVWF	Saved_W		; save w reg
	SWAPF	STATUS,W	;The swapf instruction, unlike the movf, affects NO status bits, which is why it is used here.
	CLRF	STATUS		; sets to BANK0
	MOVWF	Saved_Status	; save status reg
	MOVF	PCLATH,W
	MOVWF	Saved_Pclath	; save pclath
	CLRF	PCLATH
	MOVF	FSR,W
	MOVWF	Saved_Fsr	; save fsr reg
	ENDM

PULL	MACRO
	MOVF	Saved_Fsr,W	; get saved fsr reg
	MOVWF	FSR		; restore	
	MOVF	Saved_Pclath,W	; get saved pclath
	MOVWF	PCLATH		; restore
	SWAPF	Saved_Status,W	; get saved status in w 
	MOVWF	STATUS		; restore status ( and bank )
	SWAPF	Saved_W,F	; reload into self to set status bits
	SWAPF	Saved_W,W	; and restore
	ENDM


;+++++
;	DISABLE_IRQ disable global irq 

DISABLE_IRQ MACRO
	LOCAL	STOP_INT
STOP_INT	BCF	INTCON,GIE	; disable global interrupt
		BTFSC	INTCON,GIE	; check if disabled 
		GOTO	STOP_INT	; nope, try again
	ENDM
	
;+++++
;	ENABLE_IRQ enable global irq 

ENABLE_IRQ MACRO
	BSF	INTCON,GIE	; enable global interrupt
	ENDM



; ******************* END macro definitions ***************************

;**********************************************************************
	ORG     0x000          	; processor reset vector
	NOP			; required for the ICD 
	CLRF	STATUS		; ensure we are at bank0	
	CLRF    PCLATH        	; ensure page bits are cleared ( before GOTO xxx !!! )
	GOTO	INIT           	; go to initialisation of program

;**************** Interrupt service routine **************************


	ORG     0x004             ; interrupt vector location
	PUSH	; save registers		
INT
		
	; Interrupt code

INT_TEST_IRQ
	BTFSS	INTCON,INTF	; test if external irq
	GOTO	INT_TEST_RX_IRQ ; nope check next
	; ad irq
	PCALL	IRQ_INT_HANDLER	; dummy
	BCF	INTCON,INTF	; clear int pin flag

INT_TEST_RX_IRQ
	BTFSS	PIR1,RCIF	; test if serial recive irq
	GOTO	INT_TEST_TX_IRQ ; nope check next
	; rx irq
	PCALL	RX_INT_HANDLER	; dummy
	BCF	PIR1,RCIF	; clear rx int flag
INT_TEST_TX_IRQ
	BTFSS	PIR1,TXIF	; test if serial transmit irq
	GOTO	INT_TEST_TIMER1
	; tx irq
	PCALL	TX_INT_HANDLER	; dummy
	BCF	PIR1,TXIF	; clear tx int flag
INT_TEST_TIMER1
	BANKSEL PIE1                     ; select SFR bank
	BTFSS	PIE1,TMR1IE              ; test if interrupt is enabled
	GOTO	INT_EXIT                 ; no, so exit ISR
	BCF	STATUS,RP0               ; select SFR bank
	BTFSS   PIR1,TMR1IF              ; test if Timer1 rollover occured
	GOTO    INT_EXIT                 ; no so exit isr
	BCF	PIR1,TMR1IF              ; clear Timer1 H/W flag
	BANKSEL	T1CON                    ; select SFR bank
	MOVLW	LOW(CALC_TIMER(D'100'))
	MOVWF	TMR1L   ; initialize Timer1 low
	MOVLW	HIGH(CALC_TIMER(D'100'))    ;
	MOVWF	TMR1H   ; initialize Timer1 high
	BSF	T1CON,TMR1ON             ; turn ON Timer1 module
INT_EXIT
	PULL	; restore registers
	RETFIE  ; return from interrupt


;*************** end int routine *************************************


; ***********************************************************************
;
;  RX_INT_HANDLER - handles the received commands on serial com 
;  called from inside int.
;

RX_INT_HANDLER

	RETURN

; ***********************************************************************
;
;  TX_INT_HANDLER - handles the tramission of bytes on serial com 
;  called from inside int.
;

TX_INT_HANDLER

	RETURN

; ***********************************************************************
; EE_WRITE_BYTE - Routine to write a byte to ee ram 
; Adress in W, byte MUST be in EE_Byte

EE_WRITE_BYTE
	BANK2			; select bank2
	MOVWF	EEADR		; setup adress
	BANK0			; 
	MOVF	EE_Byte,W	; get byte
	BANK2
	MOVWF	EEDATA		; setup byte to write
	BSF	STATUS,RP0	; bank3 !!
	BCF	EECON1,EEPGD	; set to data ee ram
	BSF	EECON1,WREN	; enable writes
	DISABLE_IRQ		; disable irq's
	
	MOVLW	H'55'		; required sequence !!
	MOVWF	EECON2
	MOVLW	H'AA'
	MOVWF	EECON2
	BSF	EECON1,WR	; begin write procedure
	
	ENABLE_IRQ		; enable irq's again
	
	BCF	EECON1,WREN	; disable writes ( does not affect current write cycle )
	
	BANK0			; reset to bank0
	; wait for the write to complete before we return
	BTFSS  PIR2,EEIF	; wait for interrupt flag to be set
	GOTO   $-1		 
	; clear interupt bit and write enable bit
	BCF    PIR2,EEIF	;clear eewrite irq flag

	RETURN

; ***********************************************************************
; EE_READ_BYTE - Routine to read a byte from ee ram 
; Adress in W, byte will be delivered in W
EE_READ_BYTE
	BANK2
	MOVWF	EEADR		; put in adress reg.
	BSF	STATUS,RP0	; bank3 !!
	BCF	EECON1,EEPGD	; set to read data memory
	BSF	EECON1,RD	; set bit to read
	BCF	STATUS,RP0	; bank2 !!
	MOVF	EEDATA,W	; move data to W
	BANK0			; Reset to BANK0 !
	RETURN			; and return

; ***********************************************************************
; IS_HEX - Routine to check if value in W is ASCII hex digit 0-9, A-F or a-f
; Returns with zero SET if NOT hex ( value preserved )
; Else returns with zero flag clear and value of input as binary in W
;
IS_HEX
				;     0-9         A-F        a-f       Z
				; 0x30-0x39  0x41-0x46   0x61-0x66   0x4A

	ADDLW	0xC6		; 0xF6-0xFF  0x07-0x0C   0x27-0x2C   0x10
	ADDLW	0x0A		; 0x00-0x09  0x11-0x16   0x31-0x36   0x1A
	BTFSC	STATUS,C
	GOTO	IS_09

	ADDLW	0xE9		;            0xFA-0xFF   0x1A-0x1F   0x03
	ADDLW	0x06		;            0x00-0x05   0x20-0x25   0x09
	BTFSC	STATUS,C
	GOTO	IS_AF

	ADDLW	0xDA		;                        0xFA-0xFF   0xE3
	ADDLW	0x06		;                        0x00-0x05   0xE9
	BTFSC	STATUS,C
	GOTO	IS_AF

	ADDLW	0x61		;                                    0x4A
	BSF	STATUS,Z	; SET zero flag value is not HEX and return
	RETURN

IS_AF	ADDLW	0x0A		; add ten ( range is A-F )
IS_09	BCF	STATUS,Z	; clear zero flag value is HEX
	RETURN


; ***********************************************************************
; INIT - Cold start vector, called at startup
; 
; initilaize all ports to known state before setup routines are called
;
INIT
	; pclath and status is already cleared !
	; before entering this init routine
  	CLRF	INTCON		; ensure int reg is clear  
	CLRF	PIR1	; clear periphial irq's
	CLRF	PIR2	; ditto
	
	; make sure all individual irq's are disabled
	MOVLW	PIE1	; get adress for periphial irq enable
	MOVWF	FSR	; setup fsr
	CLRF	INDF	; and clear irq enable flags

	MOVLW	PIE2	; get adress for second periphial irq enable
	MOVWF	FSR	; setup fsr
	CLRF	INDF	; and clear irq enable flags

	; note porta as is set as ANALOGUE i/o as default

	; clear output data latches
	CLRF	PORTA
	CLRF	PORTB
	CLRF	PORTC

	; call initialize routines for periphials/ports
	; note must be at bank0 during initializing

	; NOTE ! DO NOT CHANGE ORDER OF THESE ROUTINES !!

	; clear all user ram ( set to all 0's )
	SHORT_CALL	CLEAR_RAM
	; setup our ports to in/out/analogue/rx/tx/spi/etc
	; must be done before calling any other INIT_XXX routine
	; as most of them depends on pin settings	
	SHORT_CALL	INIT_PORTS	
	; setup uart
	SHORT_CALL	INIT_UART
	; setup I2C
	SHORT_CALL	INIT_I2C
	; setup timer1
	SHORT_CALL	INIT_TIMER1
	; setup configurable parameters ( read from EE ram )
	SHORT_CALL	INIT_PARAMS
	; all pins/periphials configured, enable global irq
	ENABLE_IRQ

	BANK0


MAIN_LOOP
	; main loop

	; test for specific events
MAIN_DONE
	NOP
	NOP
	NOP
	NOP

	; and return to main loop
	GOTO	MAIN_LOOP





	ORG	0x0800	; second page




	ORG	0x1000	; third page
; ***********************************************************************
;
;  CLEAR_RAM - Reset all general purpose ram to 0's
;  Note ! does not clear watchdog, add CLRWDT where appropiate if enabled
;  Make sure to be at bank0

CLEAR_RAM
	MOVLW	0x20		; start ram bank0
	MOVWF	FSR
CLEAR_BANK0	
	CLRF	INDF		; Clear a register pointed to be FSR
	INCF	FSR,F
	MOVLW	0x7F		; Test if at top of memory bank0
	SUBWF	FSR,W
	BNZ	CLEAR_BANK0	; Loop until all cleared

	MOVLW	0xA0		; start ram bank1
	MOVWF	FSR
CLEAR_BANK1	
	CLRF	INDF		; Clear a register pointed to be FSR
	INCF	FSR,F
		
	; note this could also be set to 0xFF or 0xEF as the top 16 bytes are mirrored from
	; bank0

	MOVLW	0xEF		; Test if at top of memory bank1
	SUBWF	FSR,W
	BNZ	CLEAR_BANK1	; Loop until all cleared

	BANK2			; select bank2/3 ( with indirect adressing )

	MOVLW	0x10		; start ram bank2
	MOVWF	FSR
CLEAR_BANK2	
	CLRF	INDF		; Clear a register pointed to be FSR
	INCF	FSR,F
	
	; note this could also be set to 0x7F or 0x70 as the top 16 bytes are mirrored from
	; bank0
	MOVLW	0x70		; Test if at top of memory bank2
	SUBWF	FSR,W
	BNZ	CLEAR_BANK2	; Loop until all cleared

	MOVLW	0x90		; start ram bank3
	MOVWF	FSR
CLEAR_BANK3	
	CLRF	INDF		; Clear a register pointed to be FSR
	INCF	FSR,F
	; note this could also be set to 0xFF or 0xEF as the top 16 bytes are mirrored from
	; bank0
	MOVLW	0xEF		; Test if at top of memory bank3
	SUBWF	FSR,W
	BNZ	CLEAR_BANK3	; Loop until all cleared
	
	BANK0			; set back to bank0

	RETURN
; ***********************************************************************
;
;  INIT_PORTS - Initialises all ports on the PIC
;  i.e sets the pins as in/out/analog/etc
;  Make sure to be at bank0

INIT_PORTS
		
	; setup PORTA 
	; set all porta pins digital
	MOVLW	ADCON1	; get adress for ad/module config1 reg
	MOVWF	FSR	; setup fsr
	MOVLW	(1<<PCFG3)|(1<<PCFG2)|(1<<PCFG1);RA0 analoge the rest digital !!
							  ; result LEFT justified 
	MOVWF	INDF	; and store it

	; shutoff ad/module
	MOVLW	ADCON0	; get adress for ad/module config reg
	MOVWF	FSR	; setup fsr
	MOVLW	(1<<ADCS1)|(1<<ADON) ; enable ad-module, ad clock is osc/32
	MOVWF	INDF	; and set it

	; set in/out for porta pins
	MOVLW	TRISA	; get adress for porta control reg
	MOVWF	FSR	; setup fsr
	MOVLW	b'00000011'	; bit 0 is analoge input from keyboard, bit 1 is key available
				; the rest is outputs
	MOVWF	INDF	; and set it

	; setup PORTB
	; set in/out for portb pins
	MOVLW	TRISB	; get adress for portb control reg
	MOVWF	FSR	; setup fsr
	MOVLW	b'00000001'	;  RB0 input ( int ) ( se also option ) the rest outputs
	MOVWF	INDF	; and set it

	; setup PORTC
	; note PORTC must be setup properly when using SPI/UART/CCP/TIMER
	; look in data sheet, some setups are 'unlogical' and/or overridden
	; as TX pin configured as input etc.

	; set in/out for portc pins
	MOVLW	TRISC	; get adress for portc control reg
	MOVWF	FSR	; setup fsr
	
	MOVLW	b'11011100';b'11010100'; 7-6 for uart must be set,4 (SDI) MUST be input i.e set
			   ;  5 ( SDO ) must be cleared, 3 (SCK) must be cleared
			   ; for master mode. 1-2 is for CCP module, 0 is for timer inp.
	MOVWF	INDF	; and set it

	; setup OPTION reg
	
	MOVLW	OPTION_REG; get adress for option reg
	MOVWF	FSR	; setup fsr
	MOVLW	b'00000000'	; pull up portb by latch, int edge falling,TMR0 source internal
				; TMR0 source edge inc on low->high, prescaler to Timer0, TMR0 rate 1:2
	MOVWF	INDF	; and set it


	RETURN

; ***********************************************************************
;
;  INIT_TIMER1 - Initialises Timer1 module
;  
;  Make sure to be at bank0

INIT_TIMER1
	
	MOVLW	T1CON 	; get adress for timer1 control reg
	MOVWF	FSR	; setup fsr
	MOVLW   b'00110000'   ; 1:8 prescale, 100mS rollover
	MOVWF	INDF	; initialize Timer1

	MOVLW	LOW(CALC_TIMER(D'100'))
	MOVWF	TMR1L   ; initialize Timer1 low
	MOVLW	HIGH(CALC_TIMER(D'100'))    ;
	MOVWF	TMR1H   ; initialize Timer1 high
	BCF	PIR1,TMR1IF  ; ensure flag is reset
	BSF	T1CON,TMR1ON ; turn on Timer1 module

	; enable TIMER1 interrupt
	MOVLW	PIE1	; get adress for periphial irq's
	MOVWF	FSR	; setup fsr
	BSF	INDF,TMR1IE ; enable TIMER1 irq
	BSF	INTCON,PEIE ; and periphial irq must also be enabled
	RETURN               ; return from subroutine

	
; ***********************************************************************
;
;  INIT_UART - Initialises UART
;  enables recevier and transmitter
;  Make sure to be at bank0

INIT_UART
	; make sure pins are setup before calling this routine
	; TRISC:6 and TRISC:7 must be set ( as for output, but operates as input/output )
	; furthermore its advised that interrupts are disabled during this routine
	
	; setup baudrate
	MOVLW	SPBRG 	; get adress for serial baud reg
	MOVWF	FSR	; setup fsr
	MOVLW	CALC_LOW_BAUD(19200) ;BAUD_9600 ; get baudrate
	MOVWF	INDF	; and store it

	; enable transmitter
	MOVLW	TXSTA	; get adress for serial enable reg
	MOVWF	FSR	; setup fsr
	MOVLW	(1<<TXEN) ;|(1<<BRGH); preset enable transmitter and high speed mode
	MOVWF	INDF	; and set it

	; enable recevier
	MOVLW	(1<<SPEN)|(1<<CREN) ; preset serial port enable and continous recevie
	MOVWF	RCSTA	; set it

	; enable reciever interrupt
	MOVLW	PIE1	; get adress for periphial irq's
	MOVWF	FSR	; setup fsr
	BSF	INDF,RCIE ; enable reciever irq
	BSF	INTCON,PEIE ; and periphial irq must also be enabled

	RETURN

; ***********************************************************************
;
;  INIT_I2C - Initialises I2C, module, 100Khz, master mode, 
;  Make sure to be at bank0	

INIT_I2C
	; make sure pins are setup before calling this routine

	; setup MSSP adress register
	MOVLW	SSPADD	; get adress for synch serial port status reg
	MOVWF	FSR	; setup fsr
	MOVLW	I2C_ClockValue ; setup clock rate
	MOVWF	INDF	; and store it


	; setup MSSP status reg
	MOVLW	SSPSTAT	; get adress for synch serial port status reg
	MOVWF	FSR	; setup fsr
	MOVLW	(1<<SMP) ; enable slewrate control
	MOVWF	INDF	; and store it

	; setup MSSP control reg
	MOVLW	SSPCON	; get adress for synch serial port control reg
	MOVWF	FSR	; setup fsr
	MOVLW	((1<<SSPEN)|(1<<CKP)|(1<<SSPM3)); enable syncronous port, enable clock ,
						; I2C master mode clock = OSC/(4*(SSPADD)+1)
	MOVWF	INDF	; and set it

	; enable MSSP interrupt
	MOVLW	PIE1	; get adress for periphial irq's
	MOVWF	FSR	; setup fsr
	BSF	INDF,SSPIE  ; enable MSSP irq
	BSF	INTCON,PEIE ; and periphial irq must also be enabled (if not already )


	RETURN

; ***********************************************************************
;
;  INIT_PARAMS - Initialises user ram with parameters stored in EE ram
;  I.e. load values from ee ram offset 0 to ram area offset Ad_ModeReg
;  parameters must be in contignous ram area.
;  Make sure to be at bank0	
; 
INIT_PARAMS
	MOVLW	EERAM_End	; number of bytes
	MOVWF	Temp		; store temporarily
	MOVLW	StartRam ; get base adress ( of first byte in contignous ram )
	MOVWF	FSR	; setup FSR
	CLRF	EE_Byte	; start adress in EE ram
INIT_PARAMS_LOOP
	MOVF	EE_Byte,W ; store adress
	SHORT_CALL EE_READ_BYTE	; get byte
	MOVWF	INDF	; put it in ram
	INCF	FSR,F	; increase dest. adress
	INCF	EE_Byte,F ; increase source adress
	DECF	Temp,F  ; decrement byte counter
	BTFSS	STATUS,Z
	GOTO	INIT_PARAMS_LOOP ; continue

	RETURN	; all ram filled



	ORG	0x2100	; 256 bytes of eeram
EERAM_Base EQU	$
ADModeEE	EQU	$-EERAM_Base	; two bytes of ad mode
		DW	0x31
		DW	0x80	; cont. conv. 24 bit, 0-10mV, unipolar, 5 V ref,
				; channel Ain1+ Ain1-

EERAM_End	EQU	$-EERAM_Base	 
		

	END 		; directive 'end of program'



Questions:

Interested:

See:

Comments:


file: /Techref/microchip/16f877/snipp.htm, 27KB, , updated: 2010/5/12 11:36, local time: 2024/3/28 03:20,
TOP NEW HELP FIND: 
52.91.255.225: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.massmind.org/techref/microchip/16f877/snipp.htm"> PIC 16f876 USART, I2C, EERAM read/write, port setup, ISR, and full initialization sample program</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 massmind.org!

 

Welcome to www.massmind.org!

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

  .