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.

Delays for PIC

Status
Not open for further replies.

vaineo

New Member
i need to use a PIC16F628 to controll a light over a 24 hour period, but all the delay routines i've seen for the pic seem extremly unacurate. i need to break the day into one hour segments. i've tryed PIC Loops. the routines for that weren't even acurate for 30 secondds. should i use an external timer to send a signal to the chip or can i do this in the pic itself?
 
A delay loop is inherently inaccurate as you have seen. Configure one of the PIC's timers and respond to it on an interrupt basis. Its accuracy is equal to the accuracy of the main clock crystal as long as you can respond to the interrupts fast enough to ensure you do not miss an interrupt flag set. For example, if you have an 8-bit timer which interrupts every 256 cycles but your routine uses more than 256 cycles between its execution and saving/restoring context, it'll break. Generally you would probably utilize a slower timer (16 bit) for generating interrupts.
 
For a start I would disagree with the statement about delay loops, a delay loop uses the same clock signal as a hardware timer, so has the same basic accuracy - as long as it's designed correctly!.

However, for this purpose I agree a better solution would be to use one of the timers to generate regular interrupts - once a second would be useful, and you could use this to provide a count of seconds, minutes, hours etc.

I would suggest using timer2 for the interrupts, this is probably the most convenient to use - if you want it, I have some simple code I was playing with earlier this year?. It generates an interrupt every 10mS, and uses that to give a clock display on an LCD module - it'll probably appear as a tutorial eventually!.
 
vaineo said:
well if you have it that would be great, i'll try it out.

OK, here's the code I was playing with:

Code:
	LIST	p=16F628		;tell assembler what chip we are using
	include "P16F628.inc"		;include the defaults for the chip
	ERRORLEVEL	0,	-302	;suppress bank selection messages
	__config 0x3D18			;sets the configuration settings (oscillator type etc.)



;***** VARIABLE DEFINITIONS
w_temp          EQU     0x20    ; variable used for context saving 
status_temp     EQU     0x21    ; variable used for context saving

        cblock 0x22             ; define a series of variables.
                Hours		; hours counter
		Mins            ; minutes counter
                Secs            ; seconds counter
                count1          ; The MSB of a 2-byte register counting
                                ; the number of Timer 2 interrupts 
                                ; which have occurred.
                count0          ; The LSB of the same 2-byte register.
                flagsecs       ; Contains a 0 unless 500 1-ms Timer 2
                                ; interrupts have been processed.
		flag10s		; ten second flag
		flag60s		; sixty second flag
		count			;used in looping routines
		countc			;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_TRIS	Equ	TRISB
LCD_RS		Equ	0x04			;LCD handshake lines
LCD_RW		Equ	0x06
LCD_E		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
                                ; Increment the LSB of the 1-ms counter.
        incf    count0,F
                                ; If it rolls over, increment the MSB.
        btfsc   STATUS,Z
        incf    count1,F
                                ; See if the count has reached 1000.
                                ; If so, set the toggle flag for the main processor
                                ; to take action.
        movlw   3               ; Is the MSB of the count 3?
        subwf   count1,W
        btfss   STATUS,Z        ; If count1 is not 3, we haven't reached 1000.
        goto    EndTimer2Interrupt
                                ; Is the LSB = 1000 - 768 = 232?
        movlw   D'1000' - D'768'
        subwf   count0,W
        btfss   STATUS,Z        ; If not, we still haven't reached 1000.
        goto    EndTimer2Interrupt
; If we get here, it's because we have processed 1000 1-ms Timer 2 Interrupts.
; Set the flagsecs variable to a non-zero value.
        movlw   H'FF'
        movwf   flagsecs
; Reinitialize count1 and count0
        clrf    count1
        clrf    count0

        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, don't flash.
        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, don't flash.
        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, don't flash.
        goto    EndTimer2Interrupt
        movlw   H'FF'
        movwf   flag60s
; Reinitialize Hours
        clrf    Hours

EndTimer2Interrupt

        BCF PIR1,TMR2IF 	; Clear flag and continue.
        return

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

	movlw	0x07
	movwf	CMCON			;turn comparators off (make it like a 16F84)

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

        clrf    count1          ; Re-initialize count1 and count0.
        clrf    count0
        clrf    Secs
        clrf    Mins
	clrf	Hours

        clrf    flagsecs       ; Turn off the flag which, when set, says 500 ms has elapsed.
	clrf    flag10s
	clrf    flag60s

; ***********************************************************************************
; 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	0x00		;make all pins outputs
	movwf	LCD_TRIS

        bcf     STATUS,RP0      ; Revert to Bank 0

; ***********************************************************************************
; 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'25'-1         ; Set the PR2 register for Timer 2 to divide by 25.
        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
        movf    flagsecs, W     ; Has the flagsecs been set?
        btfsc   STATUS,Z
        goto    loop            ; Not yet.  Keep looking.

	call	LCD_Line1

	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

        goto loop               ; Now wait for the next occurence.

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

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	Delay100		;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 	Delay5
		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 	Delay5
		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

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 (4 MHz clock)
d0		movwf	countc
d1		movlw	0xC7			;delay 1mS
		movwf	counta
		movlw	0x01
		movwf	countb
Delay_0
		decfsz	counta, f
		goto	$+2
		decfsz	countb, f
		goto	Delay_0

		decfsz	countc	,f
		goto	d1
		retlw	0x00

Pulse_e		bsf	LCD_PORT, LCD_E
		nop
		bcf	LCD_PORT, LCD_E
		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''
 
Nigel Goodwin said:
For a start I would disagree with the statement about delay loops, a delay loop uses the same clock signal as a hardware timer, so has the same basic accuracy - as long as it's designed correctly!.

True, wouldn't want to imply that instruction time isn't predictable. It's accurate provided you want to calculate out what everything takes, don't have code doing anything else which isn't 100% predictable, and resolve not to go around changing code inside the loop since it would require recalculating everything. Of course, this is exactly why timers were invented.
 
Status
Not open for further replies.

Latest threads

New Articles From Microcontroller Tips

Back
Top