Continue to Site

Welcome to our site!

Electro Tech is an online community (with over 170,000 members) who enjoy talking about and building electronic circuits, projects and gadgets. To participate you need to register. Registration is free. Click here to register now.

  • Welcome to our site! Electro Tech is an online community (with over 170,000 members) who enjoy talking about and building electronic circuits, projects and gadgets. To participate you need to register. Registration is free. Click here to register now.

pic16f877 tmr0!!!

Status
Not open for further replies.

procos

New Member
i want to display on lcd the time of function in format 00:00:00:00(day,hours,min , seconds).
The cause is if i can this with TIMER0 OF PIC16F877 /20 MHz crystal...?
any conceit?
thx very much.
bye!
 
Yes you can, but it's easier to use tmr2 than tmr0, tmr0 is a VERY old timer and has problems with generating regular interrupts - which you have to compensate for (check the PICList for suitable routines).

Far easier to use tmr2, which has no such problems.

I use tmr2 to generate an interrupt every 10mS, the interrupt routine keeps a running count of seconds, minutes, hours and days - setting a flag everytime the seconds change. The main program loop checks this flag, and updates the clock display when it changes.
 
Re: thanx

procos said:
any little sample?
:oops:

This is some early code from last year, it's all I have with me at work!.

It might be using faster interrupts than 10mS, probably 1mS at 4MHz, and I added an extra count of 5 when I swapped to a 20MHz 16F876 in this particular version. Later on I changed the timer value for 20MHz, and used 10mS interrupts instead.

Code:
; Generate interrupts every 10mS, display count of hours, minutes, seconds, and hundreths.

	LIST	p=16F876		;tell assembler what chip we are using
	include "P16F876.inc"		;include the defaults for the chip
	ERRORLEVEL	0,	-302	;suppress bank selection messages
	__CONFIG    0x393A		;sets the configuration settings (oscillator type etc.)



;***** VARIABLE DEFINITIONS

        cblock 0x20             ; define a series of variables.
		w_temp		; variable used for context saving 
                status_temp	; variable used for context saving
		Hours		; hours counter
		Mins            ; minutes counter
                Secs            ; seconds counter
		MSecs		; 10's of millisconds counter
                count0          ; Interrupt counter
                flagsecs        ; Contains a 0 unless 500 1-ms Timer 2
                                ; interrupts have been processed.
		flag10s		; ten second flag
		flag60s		; sixty second flag
		HoursA		; alarm hours register
		MinsA           ; alarm minutes register
                SecsA           ; alarm seconds register
		count		;used in looping routines
		count1		;used in delay routine
		counta		;used in delay routine
		countb		;used in delay routine
		tmp1		;temporary storage
		tmp2
		templcd		;temp store for 4 bit mode
		templcd2

        	NumL		;Binary inputs for decimal convert routine
	        NumH	

        	TenK		;Decimal outputs from convert routine
	        Thou	
        	Hund	
	        Tens	
        	Ones
        endc

; Bits within PORTA
ToggleBit       equ     1       ; An output bit, toggled every 500 ms.
TenSecBit	equ	2
MinuteBit	equ	4
PortAMask       equ     B'00000000' ;  We'll make all of PORT A an output.

LCD_PORT	Equ	PORTB	;LCD on PortB
LCD_TRIS	Equ	TRISB
LCD_RS		Equ	0x04	;LCD handshake lines
LCD_RW		Equ	0x06
LCD_E		Equ	0x07
SW_PORT		Equ	PORTC
SW_TRIS		Equ	TRISC
LED1		Equ	0x00
LED2		Equ	0x01
LED3		Equ	0x02
LED4		Equ	0x03
BUT1		Equ	0x04
BUT2		Equ	0x05
BUT3		Equ	0x06
BUT4		Equ	0x07

;**********************************************************************
                ORG     0x000             ; processor reset vector
                clrf    PCLATH            ; ensure page 0 is used
                goto    main              ; go to beginning of program


                ORG     0x004           ; interrupt vector location
                movwf   w_temp          ; save off current W register contents
                swapf   STATUS,W        ; move status register into W register
                clrf    STATUS          ; select Bank 0
                movwf   status_temp     ; save off contents of STATUS register
                                        ; There's no need to save PCLATH since
                                        ; we'll stick to Bank 0 of program memory.

; isr code can go here or be located as a call subroutine elsewhere


                btfsc   PIR1,TMR2IF     ; If Timer 2 caused the interrupt, handle it.
                call    Timer2


                swapf   status_temp,w     ; retrieve copy of STATUS register
                movwf   STATUS            ; restore pre-isr STATUS register contents
                swapf   w_temp,f
                swapf   w_temp,w          ; restore pre-isr W register contents
                retfie                    ; return from interrupt

; *********************************************
;       Timer 2 Interrupt handler.
;       Timer 2 has overflowed
;
Timer2

        incf    count0,F	; increment interrupt counter
        movlw   d'5'          	; Is count0 5 yet?
        subwf   count0,W
        btfss   STATUS,Z        ; If count0 is not 5, end ISR.
        goto    EndTimer2Interrupt
; Reinitialize count0
        clrf    count0

        incf    MSecs,F		; increment milli second counter
        movlw   d'100'          ; Is MSecs 100 yet?
        subwf   MSecs,W
        btfss   STATUS,Z        ; If MSecs is not 100, end ISR.
        goto    EndTimer2Interrupt
        movlw   H'FF'
        movwf   flagsecs
; Reinitialize Secs
        clrf    MSecs

        incf    Secs,F		; increment 10 second counter
        movlw   d'60'           ; Is Secs 60 yet?
        subwf   Secs,W
        btfss   STATUS,Z        ; If Secs is not 60, end ISR.
        goto    EndTimer2Interrupt
        movlw   H'FF'
        movwf   flag10s
; Reinitialize Secs
        clrf    Secs

        incf    Mins,F		; increment 60 second counter
        movlw   d'60'           ; Is Mins 60 yet?
        subwf   Mins,W
        btfss   STATUS,Z        ; If Mins is not 60, end ISR.
        goto    EndTimer2Interrupt
        movlw   H'FF'
        movwf   flag60s
; Reinitialize Mins
        clrf    Mins

        incf    Hours,F		; increment hour counter
        movlw   d'24'           ; Is Mins 24 yet?
        subwf   Hours,W
        btfss   STATUS,Z        ; If Hours is not 24, end ISR.
        goto    EndTimer2Interrupt
        movlw   H'FF'
        movwf   flag60s
; Reinitialize Hours
        clrf    Hours		; reset hours to zero

EndTimer2Interrupt

        bcf PIR1,TMR2IF 	; Clear flag and continue.
        return

; HEX conversion table for LCD routines.

HEX_Table  	ADDWF   PCL       , f
            	RETLW   0x30
            	RETLW   0x31
            	RETLW   0x32
            	RETLW   0x33
            	RETLW   0x34
            	RETLW   0x35
            	RETLW   0x36
            	RETLW   0x37
            	RETLW   0x38
            	RETLW   0x39
            	RETLW   0x41
            	RETLW   0x42
            	RETLW   0x43
            	RETLW   0x44
            	RETLW   0x45
            	RETLW   0x46

main
; ***********************************************************************************
; START OF CODE to initialize the processor
; The initialization code goes here since we'll end up here shortly after a reset.
; ***********************************************************************************

; ***********************************************************************************
; Most Bank 0 initializations are done here and they come first.
; ***********************************************************************************

        bcf     STATUS,RP0      ; Select Bank 0
        bcf     STATUS,RP1

	BANKSEL ADCON1		;disable A2D for 16F876/7
    	movlw   0x06
    	movwf   ADCON1
    	BANKSEL PORTA

        clrf    PORTA           ; Initialize Port A by clearing the output latches.

        clrf    count0
	clrf	MSecs
        clrf    Secs
        clrf    Mins
	clrf	Hours

        clrf    flagsecs       ; Turn off the flag which, when set, says 500 ms has elapsed.
	clrf    flag10s
	clrf    flag60s
	
	clrf	HoursA		;clear alarm registers
        clrf    SecsA
        clrf    MinsA

; ***********************************************************************************
; Most Bank 1 initializations come next.
; ***********************************************************************************

        bsf     STATUS,RP0      ; Select Bank 1

        movlw   PortAMask       ; Initialize direction pins for Port A using TRISA.
        movwf   TRISA
        movlw	0xF0
        movwf	SW_TRIS		;set inputs for buttons
       	movlw	0x00		;make all LCD pins outputs
	movwf	LCD_TRIS

        bcf     STATUS,RP0      ; Revert to Bank 0
        
        movlw	b'00000000'
        movwf	SW_PORT		;clear LED's
        
        			;test alarm values
        
        movlw	0x01		;set 1 hour
        movwf	HoursA
        
        movlw	0x02
        movwf	MinsA		;set 2 minute
        
        movlw	0x1E		;set 30 seconds
        movwf	SecsA

; ***********************************************************************************
; START OF CODE to initialize Timer 2
; These come next only because it's convenient to group them together, not because
; it's a necessity.

; Set up Timer 2 to generate interrupts every 1 ms.  Since we're assuming an instruction
; cycle consumes 1 us, we need to cause an interrupt every 1000 instruction cycles.
; We'll set the prescaler to 4, the PR2 register to 25, and the postscaler to 10.  This
; will generate interrupts every 4 x 25 x 10 = 1000 instruction cycles.  
; ***********************************************************************************

        clrf    TMR2            ; Clear Timer2 register

        bsf     STATUS, RP0     ; Bank1
        bsf     INTCON,PEIE     ; Enable peripheral interrupts
        clrf    PIE1            ; Mask all peripheral interrupts except
        bsf     PIE1,TMR2IE     ; the timer 2 interrupts.
        bcf     STATUS, RP0     ; Bank0

        clrf    PIR1            ; Clear peripheral interrupts Flags
        movlw   B'01001001'     ; Set Postscale = 10, Prescale = 4, Timer 2 = off.
        movwf   T2CON

        bsf     STATUS, RP0     ; Bank1
        movlw   D'250'-1         ; Set the PR2 register for Timer 2 to divide by 250.
        movwf   PR2
        bcf     STATUS, RP0     ; Bank0

        bsf     INTCON,GIE      ; Global interrupt enable.
        bsf     T2CON,TMR2ON    ; Timer2 starts to increment

; ***********************************************************************************
; END OF CODE to initialize Timer 2
; ***********************************************************************************

	call	LCD_Init		;setup LCD

; ***********************************************************************************
; main()
; This is the main program.  It does only one thing:  check to see if it's time to
; toggle PORTA<togglebit> and do so if it is time.  Otherwise it's busily engaged
; in using up all the instruction cycles not required by the interrupt handlers.

loop
        call	Check_Keys
        movf    flagsecs, W     ; Has the flagsecs been set?
        btfsc   STATUS,Z
        goto    loop            ; Not yet.  Keep looking.
        
        call	Check_Alarm	; check alarm every LCD update

	call	LCD_Line1

	movlw	'T'
	call	LCD_Char
	movlw	'i'
	call	LCD_Char
	movlw	'm'
	call	LCD_Char
	movlw	'e'
	call	LCD_Char
	movlw	' '
	call	LCD_Char
	movlw	' '
	call	LCD_Char

	movf	Hours,	w
	movwf	NumL
	call	Display
	movlw	':'
	call	LCD_Char
	movf	Mins,	w
	movwf	NumL
	call	Display
	movlw	':'
	call	LCD_Char
	movf	Secs,	w
	movwf	NumL
	call	Display
	movlw	' '
	call	LCD_Char
	
	call	LCD_Line2
	
	movlw	'A'
	call	LCD_Char
	movlw	'l'
	call	LCD_Char
	movlw	'a'
	call	LCD_Char
	movlw	'r'
	call	LCD_Char
	movlw	'm'
	call	LCD_Char
	movlw	' '
	call	LCD_Char
	
	movf	HoursA,	w
	movwf	NumL
	call	Display
	movlw	':'
	call	LCD_Char
	movf	MinsA,	w
	movwf	NumL
	call	Display
	movlw	':'
	call	LCD_Char
	movf	SecsA,	w
	movwf	NumL
	call	Display
	movlw	' '
	call	LCD_Char

        goto loop               ; Now wait for the next occurence.

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

Check_Keys
		btfss	SW_PORT, BUT1
		goto	Clear_Clk
		btfss	SW_PORT, BUT2
		bcf     T2CON,TMR2ON    ; stop Timer2
		btfss	SW_PORT, BUT3
		bsf     T2CON,TMR2ON    ; start Timer2
		return
		
Clear_Clk
		bcf     T2CON,TMR2ON    ; stop Timer2
		clrf	Hours
		clrf	Mins
		clrf	Secs
		clrf	MSecs
		clrf	count0
		clrf    flagsecs
		clrf    flag10s
		clrf    flag60s
		clrf	SW_PORT		; turn off and LED's
		bsf     T2CON,TMR2ON    ; start Timer2
		return	
		
Check_Alarm
		movf	Hours, w	;check hours
		subwf	HoursA, w
		btfss	STATUS, Z
		return	
		movf	Mins, w		;check minutes
		subwf	MinsA, w
		btfss	STATUS, Z
		return	
		movf	Secs, w		;check seconds
		subwf	SecsA, w
		btfsc	STATUS, Z
		bsf	SW_PORT, LED1
		return			

Display		clrf	NumH
		call	Convert			;convert to decimal		
		movf	Tens,	w
		call	LCD_CharD
		movf	Ones,	w
		call	LCD_CharD
		return

;LCD routines

;Initialise LCD
LCD_Init	call 	LCD_Busy		;wait for LCD to settle

		movlw	0x20			;Set 4 bit mode
		call	LCD_Cmd

		movlw	0x28			;Set display shift
		call	LCD_Cmd

		movlw	0x06			;Set display character mode
		call	LCD_Cmd

		movlw	0x0c			;Set display on/off and cursor command
		call	LCD_Cmd			;Set cursor off

		call	LCD_Clr			;clear display

		retlw	0x00

; command set routine
LCD_Cmd		movwf	templcd
		swapf	templcd,	w	;send upper nibble
		andlw	0x0f			;clear upper 4 bits of W
		movwf	LCD_PORT
		bcf	LCD_PORT, LCD_RS	;RS line to 1
		call	Pulse_e			;Pulse the E line high

		movf	templcd,	w	;send lower nibble
		andlw	0x0f			;clear upper 4 bits of W
		movwf	LCD_PORT
		bcf	LCD_PORT, LCD_RS	;RS line to 1
		call	Pulse_e			;Pulse the E line high
		call 	LCD_Busy
		retlw	0x00

LCD_CharD	addlw	0x30			;add 0x30 to convert to ASCII
LCD_Char	movwf	templcd
		swapf	templcd,	w	;send upper nibble
		andlw	0x0f			;clear upper 4 bits of W
		movwf	LCD_PORT
		bsf	LCD_PORT, LCD_RS	;RS line to 1
		call	Pulse_e			;Pulse the E line high

		movf	templcd,	w	;send lower nibble
		andlw	0x0f			;clear upper 4 bits of W
		movwf	LCD_PORT
		bsf	LCD_PORT, LCD_RS	;RS line to 1
		call	Pulse_e			;Pulse the E line high
		call 	LCD_Busy
		retlw	0x00

LCD_Line1	movlw	0x80			;move to 1st row, first column
		call	LCD_Cmd
		retlw	0x00

LCD_Line2	movlw	0xc0			;move to 2nd row, first column
		call	LCD_Cmd
		retlw	0x00

LCD_Line1W	addlw	0x80			;move to 1st row, column W
		call	LCD_Cmd
		retlw	0x00

LCD_Line2W	addlw	0xc0			;move to 2nd row, column W
		call	LCD_Cmd
		retlw	0x00

LCD_CurOn	movlw	0x0d			;Set display on/off and cursor command
		call	LCD_Cmd
		retlw	0x00

LCD_CurOff	movlw	0x0c			;Set display on/off and cursor command
		call	LCD_Cmd
		retlw	0x00

LCD_Clr		movlw	0x01			;Clear display
		call	LCD_Cmd
		retlw	0x00

LCD_HEX		movwf	tmp1
		swapf	tmp1,	w
		andlw	0x0f
		call	HEX_Table
		call	LCD_Char
		movf	tmp1, w
		andlw	0x0f
		call	HEX_Table
		call	LCD_Char
		retlw	0x00

Pulse_e		bsf	LCD_PORT, LCD_E
		nop
		bcf	LCD_PORT, LCD_E
		retlw	0x00

LCD_Busy
		bsf	STATUS,	RP0		;set bank 1
		movlw	0x0f			;set Port for input
		movwf	LCD_TRIS
		bcf	STATUS,	RP0		;set bank 0
		bcf	LCD_PORT, LCD_RS	;set LCD for command mode
		bsf	LCD_PORT, LCD_RW	;setup to read busy flag
		bsf	LCD_PORT, LCD_E
		swapf	LCD_PORT, w		;read upper nibble (busy flag)
		bcf	LCD_PORT, LCD_E		
		movwf	templcd2 
		bsf	LCD_PORT, LCD_E		;dummy read of lower nibble
		bcf	LCD_PORT, LCD_E
		btfsc	templcd2, 7		;check busy flag, high = busy
		goto	LCD_Busy		;if busy check again
		bcf	LCD_PORT, LCD_RW
		bsf	STATUS,	RP0		;set bank 1
		movlw	0x00			;set Port for output
		movwf	LCD_TRIS
		bcf	STATUS,	RP0		;set bank 0
		return

Delay255	movlw	0xff		;delay 255 mS
		goto	d0
Delay100	movlw	d'100'		;delay 100mS
		goto	d0
Delay50		movlw	d'50'		;delay 50mS
		goto	d0
Delay20		movlw	d'20'		;delay 20mS
		goto	d0
Delay5		movlw	0x05		;delay 5.000 ms (20 MHz clock)
d0		movwf	count1
d1		movlw	0xE7		;delay 1mS
		movwf	counta
		movlw	0x04
		movwf	countb
Delay_0
		decfsz	counta, f
		goto	$+2
		decfsz	countb, f
		goto	Delay_0

		decfsz	count1	,f
		goto	d1
		retlw	0x00

;end of LCD routines

Convert:                        ; Takes number in NumH:NumL
                                ; Returns decimal in
                                ; TenK:Thou:Hund:Tens:Ones
        swapf   NumH, w
	iorlw	B'11110000'
        movwf   Thou
        addwf   Thou,f
        addlw   0XE2
        movwf   Hund
        addlw   0X32
        movwf   Ones

        movf    NumH,w
        andlw   0X0F
        addwf   Hund,f
        addwf   Hund,f
        addwf   Ones,f
        addlw   0XE9
        movwf   Tens
        addwf   Tens,f
        addwf   Tens,f

        swapf   NumL,w
        andlw   0X0F
        addwf   Tens,f
        addwf   Ones,f

        rlf     Tens,f
        rlf     Ones,f
        comf    Ones,f
        rlf     Ones,f

        movf    NumL,w
        andlw   0X0F
        addwf   Ones,f
        rlf     Thou,f

        movlw   0X07
        movwf   TenK

                    ; At this point, the original number is
                    ; equal to
                    ; TenK*10000+Thou*1000+Hund*100+Tens*10+Ones
                    ; if those entities are regarded as two's
                    ; complement binary.  To be precise, all of
                    ; them are negative except TenK.  Now the number
                    ; needs to be normalized, but this can all be
                    ; done with simple byte arithmetic.

        movlw   0X0A                             ; Ten
Lb1:
        addwf   Ones,f
        decf    Tens,f
        btfss   3,0
        goto   Lb1
Lb2:
        addwf   Tens,f
        decf    Hund,f
        btfss   3,0
        goto   Lb2
Lb3:
        addwf   Hund,f
        decf    Thou,f
        btfss   3,0
        goto   Lb3
Lb4:
        addwf   Thou,f
        decf    TenK,f
        btfss   3,0
        goto   Lb4

        retlw	0x00



                END                       ; directive 'end of program''
 
thanx

nice work.
is function if i have a input signal(ANALOG) on RA0 end i must to convert in digital?
i want to connect to PIC on rtc (ds 1307 or ds1302).
on LCD i want display :

time : 00 : 00 : 00
date : 00 : 00 : 00

after 5 sec :

Freq : xxxx.xx V / volts

is any conflict with your code?
thanks Nigel.
 
No, no conflict - in fact you can use the Convert routine to convert from hexadecimal/binary to decimal to display the value as decimal. Check my analogue tutorial for full details.

If you're planning using a ds1302/7 RTC, you don't really need the interrupt clock routine though?.
 
Status
Not open for further replies.

New Articles From Microcontroller Tips

Back
Top