Clock and Dual Termometer


Closed Thread
Results 1 to 25 of 25

Hybrid View

  1. #1
    Join Date
    Oct 2005
    Location
    Sweden
    Posts
    3,615


    Did you find this post helpful? Yes | No

    Default

    Hi,
    If I read this correctly you have an interrupt frequency of 61.035Hz (prescaler 1:64, 256*64=16384, 1/0.016384=61.035Hz) when you ideally should have 61Hz - that's 0.057% off and as Anand says 2 seconds over one hour is 0.055%.

    I currently have no idea why it starts running correct when you remove the DS1820 code - are you sure that's the case?

  2. #2
    Join Date
    Oct 2004
    Posts
    448


    Did you find this post helpful? Yes | No

    Default

    Quote Originally Posted by HenrikOlsson View Post
    that's 0.057% off and as Anand says 2 seconds over one hour is 0.055%.
    Closer to .056, actually since its .055555.. So, you might me spot on..

    Anand

  3. #3
    Join Date
    Dec 2008
    Location
    Ploiesti, ROMANIA
    Posts
    582


    Did you find this post helpful? Yes | No

    Default

    Somebody, in a forum of my country, propose this code. It' work ok, just 1 sec/hour faster !
    Code:
    @ __config _XT_OSC & _WDT_OFF & _PWRTE_OFF & _MCLRE_OFF & _LVP_OFF & _CP_OFF
    
    define OSC 4
    TRISA= %11111000                       ' RA0..3=Outputs RA4=Input
    TRISB= %00001111              ' RB0..RB2=Inputs, RB3..RB7=Outputs
    CMCON=7                                     ' Disable comparators
    OPTION_REG=%00000111
    
    
    DEFINE LCD_DREG PORTB               ' LCD on port B
    DEFINE LCD_DBIT 4                        ' Data bits B4..B7
    DEFINE LCD_RSREG PORTA            ' RS on PORTA
    DEFINE LCD_RSBIT 1                     ' RS on A1
    DEFINE LCD_EREG PORTA              ' E on PORTA
    DEFINE LCD_EBIT 0                       ' E on A0
    DEFINE LCD_BITS 4                      ' LCD 4 bit mode
    DEFINE LCD_LINES 2                     ' 2 line LCD display
    
    wsave   VAR BYTE    $70     SYSTEM
    TempC           var     word
    Float           var     word
    Sign          var   bit         ' +/- sign
    DQ          var     PORTA.4      ' One-wire data pin
    TempC2          var     word
    Float2          var     word
    Sign2          var   BIT         ' +/- sign
    DQ2          var     PORTA.3      ' One-wire data pin
    Delay           var     byte
    Mode            var     byte
    semn          var     word
    semn2           var     word
    
    INCLUDE "DT_INTS-14.bas"     ; Base Interrupt System ; Attention ! Modified file !
    INCLUDE "ReEnterPBP.bas"
    
    DS18B20_1_12bit CON %00011111          ' NOW 9 BIT
    DS18B20_2_12bit CON %00011111          ' NOW 9 BIT
    
    
    Ticks      var   byte                   ; Tick count (61 ticks=1 sec)
    Hour      var   byte             ; Hour variable
    Minute   var   byte                   ; Minute variable
    Second   var   byte               ; Second variable
    ZIUA        var   byte
    LUNA        var   byte    
    Disp      var   BIt                   ; Disp=1 to update display
    
    PAUSE 500                   ; Wait 0.5sec for LCD to initialize
    
    Hour=0 : Minute=0 : Second=0
    Ticks=0  : ZIUA=01 : LUNA=01
    
    
    
    
    
    
    ' Init Sensor 1
    OWOUT DQ, 1, [$CC, $4E, 0, 0, DS18B20_1_12bit]
    OWOut DQ, 1, [$CC, $48]             
    OWOut DQ, 1, [$CC, $B8]
    OWOut DQ, 1, [$CC, $BE]
    Pause 50
    OWIn DQ, 2, [TempC.byte0, TempC.byte1]
    Pause 50
    ' Init Sensor 2
    OWOUT DQ2, 1, [$CC, $4E, 0, 0, DS18B20_2_12bit]
    OWOut DQ2, 1, [$CC, $48]             
    OWOut DQ2, 1, [$CC, $B8]
    OWOut DQ2, 1, [$CC, $BE]
    Pause 50
    OWIn DQ2, 2, [TempC2.byte0, TempC2.byte1]
    Pause 50
    OPTION_REG=$05                ; Set prescaler
    INTCON=$A0                   ; Enable TMR
    ASM
    INT_LIST  macro                ; IntSource,   Label,  Type, ResetFlag?
            INT_Handler     TMR0_INT,  _ISR,   PBP,  yes
        endm
        INT_CREATE                ; Creates the interrupt processor
    ENDASM
                       
    @   INT_ENABLE   TMR0_INT
    
    LCDOUT $FE, 1                   ; Clear LCD
    LOOP:
    
    If PORTB.0=0 then                       ' Mode switch preSeconded
         Pause 50                          ' Debounce
       LcdOut $FE, 1
       LcdOut $FE, $C0, "         SETTING"    ' Show that coMinuteand is accepted
       PAUSE 500
       LcdOut $FE, 1
    If PORTB.0=0 then Loop                  ' Wait until button is released 
      Mode=Mode+1                           ' Increment mode
    ENDIF
    
    
    If Mode=1 then                          ' SET HOUR
    LcdOut $FE, $80, dec2 Hour
    LcdOut $FE, $C0, "HOUR     SETTING"
       if portb.1=0 then
          Hour=Hour+1
            IF Hour=24 then
              Hour=0
            ENDIF
          Gosub Debounce
       endif
    
       if portb.2=0 then
            IF Hour = 0 then
              Hour=24
            ENDIF
          Hour=Hour-1
          Gosub Debounce
       endif
    EndIf
    
    If Mode=2 then                          ' SET MINUTES
    LcdOut $FE, $80, dec2 Hour,":",dec2 Minute
    LcdOut $FE, $C0, "MINUTES  SETTING"       
    
       if portb.1=0 then
          Second=0                       
          Minute=Minute+1
            IF Minute=60 THEN
              Minute=0
            ENDIF
          Gosub Debounce
       endif
    
       if portb.2=0 then
          Second=0                       
            IF Minute =<0 THEN
              Minute=60
            ENDIF
          Minute=Minute-1
       Gosub Debounce
       endif
    EndIf
    
    If Mode=3 then                          ' SET DAY
    LcdOut $FE, $80, dec2 Hour,":",dec2 Minute,":",dec2 Second,"   ",DEC2 ZIUA,"/"
    LcdOut $FE, $C0, "DAY      SETTING"
       if portb.1=0 then
          ziua=ziua+1
                IF LUNA=2 THEN
                      IF ZIUA > 28 THEN
                      ZIUA=1
                      ENDIF
                ENDIF
                IF LUNA=4 OR LUNA=6 OR LUNA=9 OR LUNA=11 THEN 
                      IF ZIUA > 30 THEN ZIUA=1
                      ELSE
                      IF ZIUA > 31 THEN ZIUA=1
                      ENDIF
          Gosub Debounce
       endif
    
       if portb.2=0 then
          ZIUA=ZIUA-1
                IF ZIUA = 0 THEN ZIUA=31
          Gosub Debounce
       endif
    EndIf
    
    If Mode=4 then                           ' SET MONTH
    LcdOut $FE, $80, dec2 Hour,":",dec2 Minute,":",dec2 Second,"   ",DEC2 ZIUA,"/",DEC2 LUNA
    LcdOut $FE, $C0, "MONTH    SETTING"
       if portb.1=0 then
          luna=luna+1
                if luna>12 then
                luna=1
                endif
          Gosub Debounce
       endif
    
       if portb.2=0 then
          luna=luna-1
                if luna<1 then
                luna=12
                endif
          Gosub Debounce
       endif
    EndIf
    
    If Mode > 4 then
       LCDOUT $FE, $C0, "END      SETTING"
       PAUSE 100
        LCDOUT $FE, 1, $FE, $0C
       mode=0
    EndIf
    If Mode > 0 then Loop               
    IF Disp=1 THEN
    
    LcdOut $FE, $80, DEC2 Hour, ":",DEC2 Minute, ":",DEC2 Second,"   ",DEC2 ZIUA,"/",DEC2 LUNA
    
    LCDOUT $FE, $C0, semn,DEC ABS TempC/100,".", DEC1 ABS TempC/10, 223,"C ", $FE, $C0 + 9, semn2,DEC ABS TempC2/100,".", DEC1 ABS TempC2/10, 223,"C   "
    
    Disp=0
    ENDIF
    
    GOTO LOOP
    
    @   INT_DISABLE   TMR0_INT
    ISR:
    Ticks=Ticks + 1
    IF Ticks < 61 THEN NoUpdate
    Ticks=0
    Second=Second + 1          ; Update second
    IF Second=60 THEN
    Second=0
    Minute=Minute + 1          ; Update Minute
    IF Minute=60 THEN
    Minute=0
    Hour=Hour + 1             ; Update Hour
    IF Hour=24 THEN
    Hour=0
    ZIUA=ZIUA+1
              IF LUNA=2 THEN
                   IF ZIUA > 28 THEN
                        ZIUA=1
                        LUNA=3
                        ENDIF
              ENDIF
           
              IF LUNA=4 OR LUNA=6 OR LUNA=9 OR LUNA=11 THEN 
                   IF ZIUA > 30 THEN
                        ZIUA=1
                        LUNA=LUNA+1                             
                        ENDIF
                   ENDIF
         
              IF LUNA=1 OR LUNA=3 OR LUNA=5 OR LUNA=7 OR LUNA=8 OR LUNA=10  THEN
                   IF ZIUA > 31 THEN
                        ZIUA=1
                        LUNA=LUNA+1
                   ENDIF                             
              ENDIF           
    
             IF LUNA=12 THEN
                   IF ZIUA > 31 THEN
                        ZIUA=1
                        LUNA=1
                   ENDIF
              ENDIF           
    ENDIF
    ENDIF
    ENDIF
    Gosub Read_temp
    Disp=1                ; Set to update display
    
    
    NoUpdate:
    INTCON.2=0                ; Re-enable TMR0 interrupts
    @ INT_RETURN                ; Re-enable interrupts
    END
    
    
    ;=================================
    ;Subrutine
    
    Debounce:
    FOR Delay=1 To 200
    Pause 1                ; Delay 1ms inside a loop. This way,
    NEXT Delay                ; timer interrupts are not stopped
    Disp=1                ; Set display flag to 1
    RETURN
    ;==================================
    Read_Temp:
        OWOut DQ, 1, [$CC, $44]
        OWOut DQ, 1, [$CC, $BE]
        OWIn  DQ, 2, [TempC.byte0, TempC.byte1]         
    
        Sign = TempC.15
        TempC = ABS(TempC)
        TempC = ((TempC >> 4)*100) + ((TempC & $F)*100 >> 4)
        IF Sign THEN TempC = -TempC
    IF TempC.15 THEN
    Semn="-"
    else
    Semn="+"
    endif
    
        OWOut DQ2, 1, [$CC, $44]
        OWOut DQ2, 1, [$CC, $BE]
        OWIn  DQ2, 2, [TempC2.byte0, TempC2.byte1]         
    
        Sign2 = TempC2.15
        TempC2 = ABS(TempC2)
        TempC2 = ((TempC2 >> 4)*100) + ((TempC2 & $F)*100 >> 4)
        IF Sign2 THEN TempC2 = -TempC2
    IF TempC2.15 THEN
    Semn2="-"
    else
    Semn2="+"
    endif
    Return
    ;=====================================
    
    END                   ; End of program

  4. #4
    Join Date
    Oct 2005
    Location
    Sweden
    Posts
    3,615


    Did you find this post helpful? Yes | No

    Default

    Great - as long as it works for your needs.

    But you can't get away from the fact that you're interrupting at 61.035Hz while it ideally should be 61Hz. That little difference WILL make it run fast.

    Let's see.... For a duration of 100.000 interrupts a time of 100,000/61.035=1638.40 seconds have passed. Your code, because it divides by 61, will "display" 1639.34 seconds (the clock runs fast).

    Here's an idea... If you keep a second WORD sized tick counter incrementing in your ISR and when it hits 1754 you reset it to zero and skip updating your normal Ticks variable for that interrupt only. This way, in 100,000 interrupts you'll only increment your Ticks variable 100,000 - (100,000/1754) = 99943 times, resulting in "time" of 99943/61 = 1638.40 seconds - pretty darn close to ideal. The clock will zig-zag a little bit but the period is only about 28 seconds so I don't think you'll notice.

    It's still early here, I may have made some terrible misstake in the math (doesn't have to be early for that). Anyway, it's an idea you may want to look into.

    /Henrik.

  5. #5
    Join Date
    Dec 2008
    Location
    Ploiesti, ROMANIA
    Posts
    582


    Did you find this post helpful? Yes | No

    Default If You see one crazy man, it's me !

    I re-re-re-read all the topics on this forum (searching for "timer") and I found one code (Josepino's code) for HIGH-accuracy clock.
    I try to compile them, but I have errors. What I do wrong ?
    Code:
    DEFINE NO_CLRWDT
    Define	OSC	4
    
    DEFINE  LCD_DREG        PORTB      ' LCD Data Port
    DEFINE  LCD_DBIT        4      ' Starting Data Bit
    DEFINE  LCD_RSREG       PORTA      ' Register Select Port
    DEFINE  LCD_RSBIT       1      ' Register Select Bit
    DEFINE  LCD_EREG        PORTA      ' Enable Port
    DEFINE  LCD_EBIT        0      ' Enable Bit
    DEFINE  LCD_BITS      4      ' Data Bus Size
    DEFINE  LCD_LINES      2      ' Number of Lines on LCD
    
    DEFINE LCD_COMMANDUS 2000
    DEFINE LCD_DATAUS 50
    
    
    
    TRISA= %11111000                    ' RA0..3=Outputs RA4=Input
    TRISB= %00001111                 	' RB0..RB2=Inputs, RB3..RB7=Outputs
    
    CMCON = 7        
    
    pushButton1 var portb.0 'switch
    pushButton2 var portb.1 
    pushButton3 Var portb.2
    pushButton4 Var portb.3
    
    pressed con 0   		;value of button pressed
    notPressed con 1 		;value of button not pressed
    
    dhour   var     byte    ' Define display hour variable
    
    i       var     byte    ' Debounce loop variable
    
    ticks   var     byte    ' Define pieces of seconds variable
    Seconds  var byte
    Minutes  var byte
    Hours    var byte
    Days     var byte
    Months   var BYTE 
    
    TempC           var     word
    Float           var     word
    Sign            var     bit           ' +/- sign
    DQ              var     PORTA.4       ' One-wire data pin
    TempC2          var     word
    Float2          var     word
    Sign2           var     bit           ' +/- sign
    DQ2             var     PORTA.3       ' One-wire data pin
    semn            var     word
    semn2           var     word
    DS18B20_1 CON %01011111         
    DS18B20_2 CON %01011111         
         
    
    ;DS18B20_9bit  CON %00011111         ; 93.75ms, 0.5°C
    ;DS18B20_10bit CON %00111111         ; 187.5ms, 0.25°C 
    ;DS18B20_11bit CON %01011111         ; 375ms,   0.125°C
      
    SecondsChanged   var bit
    MinutesChanged   var bit
    HoursChanged     var bit
    DaysChanged      var bit
    SecondsChanged = 1
    MinutesChanged = 1
        
            
        Seconds = 0
        Minutes = 0
        Hours = 12
        Days = 1
        Months = 1
        SecondsChanged = 1
        MinutesChanged = 1
        HoursChanged = 1
        DaysChanged = 1
    
    
    
    include "timp.pbp.txt"
    
    Pause 200                          ' Wait for LCD to Initialize
    
    ' Init Sensor 1
    OWOUT DQ, 1, [$CC, $4E, 0, 0, DS18B20_1]
    OWOut DQ, 1, [$CC, $48]             
    OWOut DQ, 1, [$CC, $B8]
    OWOut DQ, 1, [$CC, $BE]
    Pause 50
    OWIn DQ, 2, [TempC.byte0, TempC.byte1]
    Pause 50
    ' Init Sensor 2
    OWOUT DQ2, 1, [$CC, $4E, 0, 0, DS18B20_2]
    OWOut DQ2, 1, [$CC, $48]             
    OWOut DQ2, 1, [$CC, $B8]
    OWOut DQ2, 1, [$CC, $BE]
    Pause 50
    OWIn DQ2, 2, [TempC2.byte0, TempC2.byte1]
    Pause 50
    
    
    mainloop:
    if tick.0=1 then
    tick.0=0
    Seconds = Seconds + 1
           SecondsChanged = 1
           if Seconds = 60 then
              Minutes = Minutes + 1
              MinutesChanged = 1
              Seconds = 0
           endif
           if Minutes = 60 then
              Hours = Hours + 1
              HoursChanged = 1
              Minutes = 0
           endif
           if Hours = 24 then
              Days = Days + 1
              DaysChanged = 1
              Hours = 0
           endif
           if Days = 32 then
              Months = Months + 1
              Days = 1
           endif
           if months = 13 then
           months = 1
           endif
    endif
    
    
        ' Check button pressed to set time
        if pushbutton1 = pressed Then
        gosub set_minutes
        endif
        if pushbutton2 = pressed then
        gosub set_hours
        endif
        if pushbutton4 = pressed then
        gosub set_days
        endif
        if pushbutton3 = pressed then
        gosub set_Months
        endif    
            ' Check for time to update screen
        
        If SecondsChanged = 1  Then
            SecondsChanged = 0  ' Display time as hh:mm:ss
    LCDout $FE, $80, dec2 Hours,":",dec2 Minutes,":",dec2 Seconds,"   ",DEC2 Days,"/",DEC2 Months
    LCDOUT $FE, $C0, semn,DEC ABS TempC/100,".", DEC1 ABS TempC/10, 223,"C ", $FE, $C0 + 9, semn2,DEC ABS TempC2/100,".", DEC1 ABS TempC2/10, 223,"C   " 
    '                pauseus 1386
        Endif
    
    Goto mainloop   ' Do it all forever
            
              
            
    set_minutes:
    Minutes = Minutes + 1
    if Minutes = 60 then
    Minutes = 0
    endif
    gosub debounce
    return
    
    set_hours:
    Hours = Hours + 1
    if Hours = 24 then
    Hours = 0
    endif
    gosub debounce
    return
    
    set_days:
    Days = Days + 1
    if Days = 32 then
    Days = 1
    endif
    gosub debounce
    return
    
    set_months:
    Months = Months +1
    if Months = 13 then
    Months = 1
    endif
    gosub debounce
    return
    debounce:
    For i = 1 To 100	' Debounce and delay for 100ms
    	Pause 1	' 1ms at a time so no interrupts are lost
    	Next i
    SecondsChanged = 1
    return
    
    ;===================================================
    Read_Temp:
        ' Skip ROM search & do temp conversion
        OWOut DQ, 1, [$CC, $BE]
        OWIn  DQ, 2, [TempC.byte0, TempC.byte1]
    
        Sign = TempC.15
        TempC = ABS(TempC)
        TempC = ((TempC >> 4)*100) + ((TempC & $F)*100 >> 4)
        IF Sign THEN TempC = -TempC
    IF TempC.15 THEN
    Semn="-"
    else
    Semn="+"
    endif
        OWOut DQ2, 1, [$CC, $BE]
        OWIn  DQ2, 2, [TempC2.byte0, TempC2.byte1]         
    
        Sign2 = TempC2.15
        TempC2 = ABS(TempC2)
        TempC2 = ((TempC2 >> 4)*100) + ((TempC2 & $F)*100 >> 4)
        IF Sign2 THEN TempC2 = -TempC2
    IF TempC2.15 THEN
    Semn2="-"
    else
    Semn2="+"
    endif
    Return
    ;===================================================
       End

    and timp.pbp.txt
    Code:
    INCLUDE "DT_INTS-14.bas"     ; Base Interrupt System
    
    ASM
    INT_LIST  macro    ; IntSource,        Label,  Type, ResetFlag?
            INT_Handler   TMR0_INT,   int_handler,   ASM,  yes
        endm
        INT_CREATE               ; Creates the interrupt processor
    
        INT_ENABLE  TMR0_INT     ; Enable Timer 1 Interrupts  
    ENDASM
            OPTION_REG = %00001000	' Set TMR0 configuration
           INTCON = %10100000	' Enable TMR0 interrupts
    
    
    		bres_hi	VAR	BYTE bank0 system		' hi byte of our 24bit variable
    		bres_mid	VAR	BYTE bank0 system	'	; mid byte
    		bres_lo	VAR	BYTE bank0 system		'; lo byte
    						'; (we only need 3 bytes for this system)
    bres_hi = $0F
    bres_mid= $42
    bres_lo= $40
    		tick	VAR	BYTE bank0 system
    
    ASM
    ;******************************************************************************
    ;  INTERRUPT HANDLER     (runs this code each timer0 interrupt)
    ;******************************************************************************
    ;
    ;------------------
    int_handler				;
    ;------------------
    
    	;-------------------------------------------------
    
    
    
    	;-------------------------------------------------
    	; Note! we get here every 256 instructions, we
    	; can now do our special one second timing system.				
    
    	; This consists of three main steps;
    	; * subtract 256 counts from our 24bit variable
    	; * test if we reached the setpoint
    	; * if so, add 1,000,000 counts to 24bit variable and generate event.
    	;-------------------------------------------------
    						; * optimised 24 bit subtract here 
    						; This is done with the minimum instructions.
    						; We subtract 256 from the 24bit variable
    						; by just decrementing the mid byte.
    
    	tstf bres_mid			; first test for mid==0
    	skpnz				; nz = no underflow needed
    	decf bres_hi,f			; z, so is underflow, so dec the msb
    
    	decfsz bres_mid,f		; dec the mid byte (subtract 256)
    
    						; now the full 24bit optimised subtract is done!
    						; this is about 4 times faster than a "proper"
    						; 24bit subtract.
    
    	goto int_exit			; nz, so definitely not one second yet.
    						; in most cases the entire 'fake" int takes
    						; only 9 instructions.
    	;------------------------
    						; * test if we have reached one second.
    						; only gets here when mid==0, it MAY be one second.
    						; only gets to here 1 in every 256 times.
    						; (this is our best optimised test)
    						; it gets here when bres_mid ==0.
    
    	tstf bres_hi			; test hi for zero too
    	skpz					; z = both hi and mid are zero, is one second!
    	goto int_exit			; nz, so not one second yet.
    
    	;-------------------------------------------------
    	; Only gets to here if we have reached one second.
    
    	; now we can generate our one second event, like add
    	; one second to our clock or whatever.
    	; (in this example we toggle a led)
    
    	; The other thing we need to do is add 1,000,000 counts
    	; to our 24bit variable and start all over again.
    	;-------------------------------------------------
    						; Add the 1,000,000 counts first.
    						; One second = 1,000,000 = 0F 42 40 (in hex)
    
    						; As we know hi==0 and mid==0 this makes it very fast.
    						; This is an optimised 24bit add, because we can
    						; just load the top two bytes and only need to do
    						; a real add on the bottom byte. This is much quicker
    						; than a "proper" 24bit add.
    
    	movlw 0x0F			; get msb value 
    	movwf bres_hi			; load in msb
    
    	movlw 0x42			; get mid value
    	movwf bres_mid			; load in mid
    
    	movlw 0x40			; lsb value to add
    	addwf bres_lo,f		; add it to the remainder already in lsb
    	skpnc				; nc = no overflow, so mid is still ok
    
    	incf bres_mid,f		; c, so lsb overflowed, so inc mid
    						; this is optimised and relies on mid being known
    						; and that mid won't overflow from one inc.
    
    						; that's it! Our optimised 24bit add is done,
    						; this is roughly twice as quick as a "proper"
    						; 24bit add.
    	;-------------------------
    						; now we do the "event" that we do every one second.
    
    						; Note! for this example we toggle a led, which
    						; will give a flashing led which is on for a second
    						; and off for a second.
    						; Add your own code here for your one second event.
    
    						; Note! My led is on porta,3
    						; your led may be on a different pin.
      movlw b'00000001'		; mask for bit 3
      xorwf tick,f			; toggle PORTA,bit3 (toggle the led)
    						
    	;-------------------------------------------------
    	; now our one second event is all done, we can exit the
    	; interrupt handler.
    	;-------------------------------------------------
    						; finally we restore w and status registers.
    						; also clears TMRO int flag now we are finished.
    						
    int_exit
    	INT_RETURN
    ENDASM
    Attached Images Attached Images  

Members who have read this thread : 0

You do not have permission to view the list of names.

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts