Symbol not prev defined FSR - Elapsed Timer


+ Reply to Thread
Results 1 to 19 of 19
  1. #1
    Join Date
    Jan 2005
    Location
    Montreal, Quebec, Canada
    Posts
    2,980

    Default Symbol not prev defined FSR - Elapsed Timer

    16F18877

    Program:

    Code:
    #CONFIG
        __config _CONFIG1, _FEXTOSC_OFF & _RSTOSC_HFINT32 & _CLKOUTEN_OFF & _CSWEN_OFF & _FCMEN_ON
        __config _CONFIG2, _MCLRE_ON & _PWRTE_OFF & _LPBOREN_OFF & _BOREN_ON & _BORV_LO & _ZCD_OFF & _PPS1WAY_OFF & _STVREN_ON & _DEBUG_OFF
        __config _CONFIG3, _WDTCPS_WDTCPS_11 & _WDTE_OFF & _WDTCWS_WDTCWS_7 & _WDTCCS_LFINTOSC
        __config _CONFIG4, _WRT_OFF & _SCANE_available & _LVP_OFF
        __config _CONFIG5, _CP_OFF & _CPD_OFF
    #ENDCONFIG
    
    ;--- Interrupts ----------------------------------------------------------------
    
    ;--- Defines -------------------------------------------------------------------
    
    DEFINE OSC 32
    
    RA4PPS = 0                          ' Disable CCP5
    RB0PPS = 0                          ' Disable CCP4
    RB5PPS = 0                          ' Disable CCP3
    RC1PPS = 0                          ' Disable CCP2
    RC2PPS = 0                          ' Disable CCP1
    
    ANSELA = %00000000
    ANSELB = %00000000
    ANSELC = %00000000
    ANSELD = %00000000
    ANSELE = %00000000
    
    ;--- Setup Port directions -----------------------------------------------------
    
    TRISA = %00000000                        
    TRISB = %00000000                      
    TRISC = %00000000                       
    TRISD = %00000000                      
    TRISE = %00001000
    
    INCLUDE "Elapsed_DN_32MHz.bas"  ; Elapsed Timer Routines
    
    Days = 0                  ' set initial time
    Hours = 0
    Minutes = 0
    Seconds = 1
    
      LatB.5 = 0
        GOSUB StartTimer
      LatB.5 = 1
    
    Main:
        IF Ticks > 100 THEN  
            LatB.5 = 0
        ENDIF
      GOTO Main
    end

    Elapsed DN, with 32MHz mod:

    Code:
    '****************************************************************
    '*  Name    : ELAPSED.PBP                                       *
    '*  Author  : Darrel Taylor                                     *
    '*  Notice  : Copyright (c) 2003                                *
    '*  Date    : 12/16/2003                                        *
    '*  Notes   :                                                   *
    '****************************************************************
    
    Define  INTHAND _ClockCount    ' Tell PBP Where the code starts on an interrupt
    Include "ASM_INTS.bas"         ' ASM Interrupt Stubs
    
    Ticks    VAR BYTE   ' 1/100th of a second
    Seconds  VAR BYTE
    Minutes  VAR BYTE
    Hours    VAR BYTE
    Days     VAR WORD
    R0save   VAR WORD
    R1save   VAR WORD
    
    ZERO             VAR BIT
    CountDown        VAR BIT
    SecondsChanged   VAR BIT
    MinutesChanged   VAR BIT
    HoursChanged     VAR BIT
    DaysChanged      VAR BIT
    
    CountDown = 0
    SecondsChanged = 1
    MinutesChanged = 1
    
    Goto OverElapsed
    
    ' ------------------------------------------------------------------------------
    Asm
      IF OSC == 4                       ; Constants for 100hz interrupt from Timer1
    TimerConst = 0D8F7h                 ; Executed at compile time only
      EndIF
      If OSC == 8
    TimerConst = 0B1E7h
      EndIF
      If OSC == 10
    TimerConst = 09E5Fh
      EndIF
      If OSC == 20
    TimerConst = 03CB7h
      EndIF
      If OSC == 32			     ; T1CON
    TimerConst = 063C7h		     ;   TMR1CS bits 7-6, 00 = FOSC/4
      EndIF				     ;   T1CKPS bits 5-4, 01 = 1:2 Prescale value
      
    ; -----------------  ADD TimerConst to TMR1H:TMR1L
    ADD2_TIMER   macro
        CHK?RP  T1CON
        BCF     T1CON,TMR1ON           ; Turn off timer
        MOVLW   LOW(TimerConst)        ;  1
        ADDWF   TMR1L,F                ;  1    ; reload timer with correct value
        BTFSC   STATUS,C               ;  1/2
        INCF    TMR1H,F                ;  1
        MOVLW   HIGH(TimerConst)       ;  1
        ADDWF   TMR1H,F                ;  1
        endm
    
    ; -----------------  ADD TimerConst to TMR1H:TMR1L and restart TIMER1 
    RELOAD_TIMER  macro
        ADD2_TIMER
        BSF     T1CON,TMR1ON           ;  1    ; Turn TIMER1 back on
        CHK?RP  PIR1
        bcf     PIR1, TMR1IF           ; Clear Timer1 Interrupt Flag
        endm
    
    ; -----------------  Load TimerConst into TMR1H:TMR1L 
    LOAD_TIMER  macro
    EndAsm
        T1CON.0 = 0                    ; Turn OFF Timer1
        TMR1L = 0
        TMR1H = 0
    Asm
        ADD2_TIMER
        endm
    EndAsm
    
    ' ------[ This is the Interrupt Handler ]---------------------------------------
    ClockCount:   ' Note: this is being handled as an ASM interrupt
    @  INT_START                    
    @  RELOAD_TIMER                    ; Reload TIMER1
       R0save = R0                     ; Save 2 PBP system vars that are used during
       R1save = R1                     ; the interrupt
       Ticks = Ticks + 1
       if Ticks = 100 then
          Ticks = 0
          IF CountDown THEN
             IF Seconds > 0 THEN
                Seconds = Seconds - 1
                SecondsChanged = 1
                IF Seconds = 0 THEN
                   IF Days = 0 THEN
                      IF Hours = 0 THEN
                         IF Minutes = 0 THEN
                            GOSUB StopTimer    ; Zero reached
                            ZERO = 1
                         ENDIF
                      ENDIF
                   ENDIF
                ENDIF
             ELSE
                IF Minutes > 0 THEN
                   Minutes = Minutes - 1
                   Seconds = 59
                   SecondsChanged = 1
                   MinutesChanged = 1
                ELSE
                   IF Hours > 0 THEN
                      Hours = Hours - 1
                      Minutes = 59
                      Seconds = 59
                      SecondsChanged = 1
                      MinutesChanged = 1
                      HoursChanged = 1
                   ELSE
                      IF Days > 0 THEN
                         Days = Days - 1
                         Hours = 23
                         Minutes = 59
                         Seconds = 59
                         SecondsChanged = 1
                         MinutesChanged = 1
                         HoursChanged = 1
                         DaysChanged = 1
                      ELSE                     ; Zero already reached, shouldn't get here
                         GOSUB StopTimer
                         ZERO = 1
                      ENDIF
                   ENDIF
                ENDIF
             ENDIF
          ELSE                                ; Counting Up
             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
          endif
       ENDIF
       R1 = R1save                     ; Restore the PBP system vars
       R0 = R0save
    @ INT_RETURN                      ; Restore context and return from interrupt
    
    '-----====[ END OF TMR1 Interrupt Handler ]====---------------------------------
    
    StartTimer:
      IF NOT ZERO THEN
        T1CON.1 = 0                   ; (TMR1CS) Select FOSC/4 Clock Source
        T1CON.3 = 0                   ; (T1OSCEN) Disable External Oscillator
        PIR1.0  = 0                   ; (TMR1IF) Clear Timer1 Interrupt Flag
        PIE1.0  = 1                   ; (TMR1IE) Enable TMR1 overflow interrupt
        INTCON.6 = 1                  ; (PEIE) Enable peripheral interrupts
        INTCON.7 = 1                  ; (GIE) Enable global interrupts
        T1CON.0 = 1                   ; (TMR1ON) Start TIMER1
      ENDIF
    return
    
    ; -----------------
    StopTimer:
        T1CON.0 = 0                   ; Turn OFF Timer1
    return
    
    ; -----------------
    ResetTime:
        ZERO = 0
        R0save = T1CON.0              ; Save TMR1ON bit
        T1CON.0 = 0                   ; Turn OFF Timer1
        TMR1L = 0
        TMR1H = 0
    @   LOAD_TIMER                    ; Load TimerConst
        T1CON.0 = R0save              ; Restore TMR1ON bit
        Ticks = 0
        Seconds = 0
        Minutes = 0
        Hours = 0
        Days = 0
        SecondsChanged = 1
    return
    
    OverElapsed:

    ASM_INTS.bas:

    Code:
    '****************************************************************
    '*  Name    : ASM_INTS.PBP                                      *
    '*  Author  : Darrel Taylor                                     *
    '*  Notice  : Copyright (c) 2003                                *
    '*  Date    : JAN 4, 2003                                       *
    '****************************************************************
    
    wsave       var byte    $20     SYSTEM          ' location for W if in bank0
    
    ' --- IF any of these three lines cause an error ??  Simply Comment them out to fix the problem ----
    wsave1      var byte    $A0     SYSTEM          ' location for W if in bank1
    wsave2      var byte    $120    SYSTEM          ' location for W if in bank2
    wsave3      var byte    $1A0    SYSTEM          ' location for W if in bank3
    ' ------------------------------------------------------------------------------
    
    ssave       var byte    BANK0   SYSTEM          ' location for STATUS register
    psave       var byte    BANK0   SYSTEM          ' location for PCLATH register
    fsave       var byte    BANK0   SYSTEM          ' location for FSR register
    
    Asm
    INT_START  macro
        IF (CODE_SIZE <= 2)
            movwf   wsave            ; copy W to wsave register
            swapf   STATUS,W         ; swap status reg to be saved into W
            clrf    STATUS           ; change to bank 0 regardless of current bank
            movwf   ssave            ; save status reg to a bank 0 register
            movf    PCLATH,w         ; move PCLATH reg to be saved into W reg
            movwf   psave            ; save PCLATH reg to a bank 0 register
    	EndIF
        movf      FSR,W              ; move FSR reg to be saved into W reg
        movwf     fsave              ; save FSR reg to a bank 0 register
        endm
    EndAsm
    
    Asm
    INT_RETURN   macro
        MOVF    fsave,W              ; Restore the FSR reg 
        MOVWF   FSR
        Movf    psave,w              ; Restore the PCLATH reg
        Movwf   PCLATH
        swapf   ssave,w              ; Restore the STATUS reg			
        movwf   STATUS
        swapf   wsave,f
        swapf   wsave,w              ; Restore W reg
        Retfie                       ; Exit the interrupt routine	
        endm
    EndAsm

    For starters, I'm just trying to get a 100tick interval on the Logic Probe with LatB.5.
    My Creality Ender 3 S1 Plus is a giant paperweight that can't even be used as a boat anchor, cause I'd be fined for polluting our waterways with electronic devices.

    Not as dumb as yesterday, but stupider than tomorrow!

  2. #2
    Join Date
    Jan 2005
    Location
    Montreal, Quebec, Canada
    Posts
    2,980


    Did you find this post helpful? Yes | No

    Default Re: Symbol not prev defined FSR - Elapsed Timer

    Modded this code for program:

    https://dt.picbasic.co.uk/CODEX/ETimer


    Elapsed_DN.bas came from here:

    https://www.picbasic.co.uk/forum/con...sed-Timer-Demo


    ASM_INTS.bas came from here:

    https://dt.picbasic.co.uk/CODEX/ETimerExamples
    Last edited by Demon; - 5th October 2024 at 05:07.
    My Creality Ender 3 S1 Plus is a giant paperweight that can't even be used as a boat anchor, cause I'd be fined for polluting our waterways with electronic devices.

    Not as dumb as yesterday, but stupider than tomorrow!

  3. #3
    Join Date
    Aug 2011
    Posts
    442


    1 out of 1 members found this post helpful. Did you find this post helpful? Yes | No

    Default Re: Symbol not prev defined FSR - Elapsed Timer

    There is no FSR in the 16F18877, you have FSR0 and FSR1.

    You need to look at the TMR1 setup... you need to set different registers and bits (ie T1CON and T1CLK).

  4. #4
    Join Date
    Jan 2005
    Location
    Montreal, Quebec, Canada
    Posts
    2,980


    Did you find this post helpful? Yes | No

    Default Re: Symbol not prev defined FSR - Elapsed Timer

    Quote Originally Posted by tumbleweed View Post
    There is no FSR in the 16F18877, you have FSR0 and FSR1...
    I don't see a difference between FSR0 and FSR1. I assume I can use either one?

    Name:  FSR.png
Views: 429
Size:  103.1 KB

    EDIT: Wooops, highlighted the wrong one, but you get the idea. FSR1 is right there as well, and it points to the same blocks as FSR0.
    My Creality Ender 3 S1 Plus is a giant paperweight that can't even be used as a boat anchor, cause I'd be fined for polluting our waterways with electronic devices.

    Not as dumb as yesterday, but stupider than tomorrow!

  5. #5
    Join Date
    Jan 2005
    Location
    Montreal, Quebec, Canada
    Posts
    2,980


    Did you find this post helpful? Yes | No

    Default Re: Symbol not prev defined FSR - Elapsed Timer

    16F18877

    I start the timer, but I don't get a pulse on Logic Probe after 100 Ticks.


    Code:

    Code:
    #CONFIG
        __config _CONFIG1, _FEXTOSC_OFF & _RSTOSC_HFINT32 & _CLKOUTEN_OFF & _CSWEN_OFF & _FCMEN_ON
        __config _CONFIG2, _MCLRE_ON & _PWRTE_OFF & _LPBOREN_OFF & _BOREN_ON & _BORV_LO & _ZCD_OFF & _PPS1WAY_OFF & _STVREN_ON & _DEBUG_OFF
        __config _CONFIG3, _WDTCPS_WDTCPS_11 & _WDTE_OFF & _WDTCWS_WDTCWS_7 & _WDTCCS_LFINTOSC
        __config _CONFIG4, _WRT_OFF & _SCANE_available & _LVP_OFF
        __config _CONFIG5, _CP_OFF & _CPD_OFF
    #ENDCONFIG
    
    ;--- Interrupts ----------------------------------------------------------------
    
    ;--- Defines -------------------------------------------------------------------
    
    DEFINE OSC 32
    
    define  CCP1_REG     0              ' Must clear unused CCP pins or else unpredictable results
    DEFINE  CCP1_BIT     0
    define  CCP2_REG     0
    DEFINE  CCP2_BIT     0
    DEFINE  CCP3_REG     0
    DEFINE  CCP3_BIT     0
    define  CCP4_REG     0
    DEFINE  CCP4_BIT     0
    define  CCP5_REG     0              ' Must clear unused CCP pins or else unpredictable results
    DEFINE  CCP5_BIT     0
    
    RA4PPS = 0                          ' Disable CCP5
    RB0PPS = 0                          ' Disable CCP4
    RB5PPS = 0                          ' Disable CCP3
    RC1PPS = 0                          ' Disable CCP2
    RC2PPS = 0                          ' Disable CCP1
    
    ANSELA = %00000000
    ANSELB = %00000000
    ANSELC = %00000000
    ANSELD = %00000000
    ANSELE = %00000000
    
    ;--- Setup Port directions -----------------------------------------------------
    
    TRISA = %00000000                        
    TRISB = %00000000                      
    TRISC = %00000000                       
    TRISD = %00000000                      
    TRISE = %00001000
    
    INCLUDE "Elapsed_DN_Timer3_32MHz.bas"   ' Elapsed Timer Routines
    'Include "ASM_INTS_FSR0.bas"             ' Required in folder to compile
    
    Days = 0                  ' set initial time
    Hours = 0
    Minutes = 1
    Seconds = 0
    
      LatB.0 = 0            ' Set interrupt trace low
      LatB.1 = 0            ' Set heartbeat trace low
        GOSUB StartTimer
      LatB.0 = 1            ' Beginning of interrupt
    
    Main:
      LatB.1 = 1            ' Pulse heartbeat
        IF Ticks > 100 THEN  
            LatB.0 = 0      ' End of interrupt
        ENDIF
      LatB.1 = 0            ' Reset heartbeat trace
      GOTO Main
    end

    Elapsed_DN_Timer3_32MHz.bas, modified for Timer3 and 32MHz:

    Code:
    '****************************************************************
    '*  Name    : ELAPSED.PBP                                       *
    '*  Author  : Darrel Taylor                                     *
    '*  Notice  : Copyright (c) 2003                                *
    '*  Date    : 12/16/2003                                        *
    '*  Notes   :                                                   *
    '****************************************************************
    '*  Name    : Elapsed_DN_Timer3_32MHz.bas                       *
    '*  Author  : Robert H                                          *
    '*  Date    : 2024-10-05                                        *
    '*  Notes   : Added support for 16F18877:                       *
    '             a) Added 32MHz                                    *
    '             b) Used Timer3 instead of Timer1:                 *
    '                  - changed Timer1 to Timer3                   *
    '                  - changed T1 to T3                           *
    '                  - changed TMR1 to TMR3                       *
    '                  - changed PIR1 to PIR4                       *
    '                  - changed PIE1 to PIE4                       *
    '             c) Changed T3CON,TMR3ON to T3CON,ON               *
    '             d) Used FSR0 in ASM_INTS_FSR0.bas                 *
    '****************************************************************
    
    Define  INTHAND _ClockCount    ' Tell PBP Where the code starts on an interrupt
    Include "ASM_INTS_FSR0.bas"    ' ASM Interrupt Stubs
    
    Ticks    VAR BYTE   ' 1/100th of a second
    Seconds  VAR BYTE
    Minutes  VAR BYTE
    Hours    VAR BYTE
    Days     VAR WORD
    R0save   VAR WORD
    R1save   VAR WORD
    
    ZERO             VAR BIT
    CountDown        VAR BIT
    SecondsChanged   VAR BIT
    MinutesChanged   VAR BIT
    HoursChanged     VAR BIT
    DaysChanged      VAR BIT
    
    CountDown = 0
    SecondsChanged = 1
    MinutesChanged = 1
    
    Goto OverElapsed
    
    ' ------------------------------------------------------------------------------
    Asm
      IF OSC == 4                       ; Constants for 100hz interrupt from Timer3
    TimerConst = 0D8F7h                 ; Executed at compile time only
      EndIF
      If OSC == 8
    TimerConst = 0B1E7h
      EndIF
      If OSC == 10
    TimerConst = 09E5Fh
      EndIF
      If OSC == 20
    TimerConst = 03CB7h
      EndIF
      If OSC == 32			     ; T3CON
    TimerConst = 063C7h		     ;   TMR3CS bit 1,   0  = FOSC/4
      EndIF				     ;   T3CKPS bit 5-4, 01 = 1:2 Prescale value
      
    ; -----------------  ADD TimerConst to TMR3H:TMR3L
    ADD2_TIMER   macro
        CHK?RP  T3CON
        BCF     T3CON,TMR3ON           ; Turn off timer
        MOVLW   LOW(TimerConst)        ;  1
        ADDWF   TMR3L,F                ;  1    ; reload timer with correct value
        BTFSC   STATUS,C               ;  1/2
        INCF    TMR3H,F                ;  1
        MOVLW   HIGH(TimerConst)       ;  1
        ADDWF   TMR3H,F                ;  1
        endm
    
    ; -----------------  ADD TimerConst to TMR3H:TMR3L and restart Timer3 
    RELOAD_TIMER  macro
        ADD2_TIMER
        BSF     T3CON,TMR3ON           ;  1    ; Turn Timer3 back on
        CHK?RP  PIR4
        bcf     PIR4, TMR3IF           ; Clear Timer3 Interrupt Flag
        endm
    
    ; -----------------  Load TimerConst into TMR3H:TMR3L 
    LOAD_TIMER  macro
    EndAsm
        T3CON.0 = 0                    ; Turn OFF Timer3
        TMR3L = 0
        TMR3H = 0
    Asm
        ADD2_TIMER
        endm
    EndAsm
    
    ' ------[ This is the Interrupt Handler ]---------------------------------------
    ClockCount:   ' Note: this is being handled as an ASM interrupt
    @  INT_START                    
    @  RELOAD_TIMER                    ; Reload Timer3
       R0save = R0                     ; Save 2 PBP system vars that are used during
       R1save = R1                     ; the interrupt
       Ticks = Ticks + 1
       if Ticks = 100 then
          Ticks = 0
          IF CountDown THEN
             IF Seconds > 0 THEN
                Seconds = Seconds - 1
                SecondsChanged = 1
                IF Seconds = 0 THEN
                   IF Days = 0 THEN
                      IF Hours = 0 THEN
                         IF Minutes = 0 THEN
                            GOSUB StopTimer    ; Zero reached
                            ZERO = 1
                         ENDIF
                      ENDIF
                   ENDIF
                ENDIF
             ELSE
                IF Minutes > 0 THEN
                   Minutes = Minutes - 1
                   Seconds = 59
                   SecondsChanged = 1
                   MinutesChanged = 1
                ELSE
                   IF Hours > 0 THEN
                      Hours = Hours - 1
                      Minutes = 59
                      Seconds = 59
                      SecondsChanged = 1
                      MinutesChanged = 1
                      HoursChanged = 1
                   ELSE
                      IF Days > 0 THEN
                         Days = Days - 1
                         Hours = 23
                         Minutes = 59
                         Seconds = 59
                         SecondsChanged = 1
                         MinutesChanged = 1
                         HoursChanged = 1
                         DaysChanged = 1
                      ELSE                     ; Zero already reached, shouldn't get here
                         GOSUB StopTimer
                         ZERO = 1
                      ENDIF
                   ENDIF
                ENDIF
             ENDIF
          ELSE                                ; Counting Up
             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
          endif
       ENDIF
       R1 = R1save                     ; Restore the PBP system vars
       R0 = R0save
    @ INT_RETURN                      ; Restore context and return from interrupt
    
    '-----====[ END OF TMR3 Interrupt Handler ]====---------------------------------
    
    StartTimer:
      IF NOT ZERO THEN
        T3CON.1 = 0                   ; (TMR3CS) Select FOSC/4 Clock Source
        T3CON.3 = 0                   ; (T3OSCEN) Disable External Oscillator
        PIR4.0  = 0                   ; (TMR3IF) Clear Timer3 Interrupt Flag
        PIE4.0  = 1                   ; (TMR3IE) Enable TMR3 overflow interrupt
        INTCON.6 = 1                  ; (PEIE) Enable peripheral interrupts
        INTCON.7 = 1                  ; (GIE) Enable global interrupts
        T3CON.0 = 1                   ; (TMR3ON) Start Timer3
      ENDIF
    return
    
    ; -----------------
    StopTimer:
        T3CON.0 = 0                   ; Turn OFF Timer3
    return
    
    ; -----------------
    ResetTime:
        ZERO = 0
        R0save = T3CON.0              ; Save TMR3ON bit
        T3CON.0 = 0                   ; Turn OFF Timer3
        TMR3L = 0
        TMR3H = 0
    @   LOAD_TIMER                    ; Load TimerConst
        T3CON.0 = R0save              ; Restore TMR3ON bit
        Ticks = 0
        Seconds = 0
        Minutes = 0
        Hours = 0
        Days = 0
        SecondsChanged = 1
    return
    
    OverElapsed:

    ASM_INTS_FSR0.bas, modified for FSR0:

    Code:
    '****************************************************************
    '*  Name    : ASM_INTS.PBP                                      *
    '*  Author  : Darrel Taylor                                     *
    '*  Notice  : Copyright (c) 2003                                *
    '*  Date    : JAN 4, 2003                                       *
    '*  Notes   :                                                   *
    '****************************************************************
    '*  Name    : ASM_INTS_FSR0.bas                                 *
    '*  Author  : Robert H                                          *
    '*  Date    : 2024-10-05                                        *
    '*  Notes   : Added support for 16F18877:                       *
    '             a) Changed FSR to FSR0                            *
    '****************************************************************
    
    wsave       var byte    $20     SYSTEM          ' location for W if in bank0
    
    ' --- IF any of these three lines cause an error ??  Simply Comment them out to fix the problem ----
    wsave1      var byte    $A0     SYSTEM          ' location for W if in bank1
    wsave2      var byte    $120    SYSTEM          ' location for W if in bank2
    wsave3      var byte    $1A0    SYSTEM          ' location for W if in bank3
    ' ------------------------------------------------------------------------------
    
    ssave       var byte    BANK0   SYSTEM          ' location for STATUS register
    psave       var byte    BANK0   SYSTEM          ' location for PCLATH register
    fsave       var byte    BANK0   SYSTEM          ' location for FSR0 register
    
    Asm
    INT_START  macro
        IF (CODE_SIZE <= 2)
            movwf   wsave            ; copy W to wsave register
            swapf   STATUS,W         ; swap status reg to be saved into W
            clrf    STATUS           ; change to bank 0 regardless of current bank
            movwf   ssave            ; save status reg to a bank 0 register
            movf    PCLATH,w         ; move PCLATH reg to be saved into W reg
            movwf   psave            ; save PCLATH reg to a bank 0 register
    	EndIF
        movf      FSR0,W              ; move FSR0 reg to be saved into W reg
        movwf     fsave              ; save FSR0 reg to a bank 0 register
        endm
    EndAsm
    
    Asm
    INT_RETURN   macro
        MOVF    fsave,W              ; Restore the FSR0 reg 
        MOVWF   FSR0
        Movf    psave,w              ; Restore the PCLATH reg
        Movwf   PCLATH
        swapf   ssave,w              ; Restore the STATUS reg			
        movwf   STATUS
        swapf   wsave,f
        swapf   wsave,w              ; Restore W reg
        Retfie                       ; Exit the interrupt routine	
        endm
    EndAsm

    I used 18F4450 as an example of "default" settings.

    18F4450, bit 0 is called TMR1ON in the datasheet.
    16F18877, bit 0 is called ON.

    If I rename the bit to ON, I get Symbol not previously defined (ON).


    I must have missed something.
    Last edited by Demon; - 5th October 2024 at 23:33.
    My Creality Ender 3 S1 Plus is a giant paperweight that can't even be used as a boat anchor, cause I'd be fined for polluting our waterways with electronic devices.

    Not as dumb as yesterday, but stupider than tomorrow!

  6. #6


    Did you find this post helpful? Yes | No

    Default Re: Symbol not prev defined FSR - Elapsed Timer

    I would start off with interrupt and in routine just add to a counter then in Basic do the math to get seconds, minutes etc. Otherwise that is a lot of code to fumble through.

  7. #7
    Join Date
    May 2013
    Location
    australia
    Posts
    2,515


    Did you find this post helpful? Yes | No

    Default Re: Symbol not prev defined FSR - Elapsed Timer

    there are more problems here than i can count

    1, timer3 has no clock source
    2, how can ticks ever get beyond 100
    Code:
    main:  LatB.1 = 1            ' Pulse heartbeat
        IF Ticks > 100 THEN  
            LatB.0 = 0      ' End of interrupt
        ENDIF
      LatB.1 = 0            ' Reset heartbeat trace
      GOTO Main
    when
    Code:
    ClockCount:   ' Note: this is being handled as an ASM interrupt
    @  INT_START                    
    @  RELOAD_TIMER                    ; Reload Timer3
       R0save = R0                     ; Save 2 PBP system vars that are used during
       R1save = R1                     ; the interrupt
       Ticks = Ticks + 1
       if Ticks = 100 then
          Ticks = 0
          IF CountDown THEN
    3, a 16f18877 like all enhanced core pic16's has Auto context save
    the entire int_start / int_return macros are inappropriate

    4, you need to rethink that, that is for timer1 not 3
    Code:
    StartTimer:
      IF NOT ZERO THEN
        T3CON.1 = 0                   ; (TMR3CS) Select FOSC/4 Clock Source
        T3CON.3 = 0                   ; (T3OSCEN) Disable External Oscillator
        PIR4.0  = 0                   ; (TMR3IF) Clear Timer3 Interrupt Flag
        PIE4.0  = 1                   ; (TMR3IE) Enable TMR3 overflow interrupt
        INTCON.6 = 1                  ; (PEIE) Enable peripheral interrupts
        INTCON.7 = 1                  ; (GIE) Enable global interrupts
        T3CON.0 = 1                   ; (TMR3ON) Start Timer3
      ENDIF
    return
    Warning I'm not a teacher

  8. #8
    Join Date
    Jan 2005
    Location
    Montreal, Quebec, Canada
    Posts
    2,980


    Did you find this post helpful? Yes | No

    Default Re: Symbol not prev defined FSR - Elapsed Timer

    I'm already using Timer1, hence why I hoped to use Timer3.

    I'll swap what I'm doing, so I can use DT's routine without changing Timer1.

    (At the restaurant, so can't post elaborate reply)
    My Creality Ender 3 S1 Plus is a giant paperweight that can't even be used as a boat anchor, cause I'd be fined for polluting our waterways with electronic devices.

    Not as dumb as yesterday, but stupider than tomorrow!

  9. #9
    Join Date
    Jan 2005
    Location
    Montreal, Quebec, Canada
    Posts
    2,980


    Did you find this post helpful? Yes | No

    Default Re: Symbol not prev defined FSR - Elapsed Timer

    Quote Originally Posted by richard View Post
    ... how can ticks ever get beyond 100 ...
    I only wanted 1 interval, so I'd know the mods were working with the 16F18877.
    My Creality Ender 3 S1 Plus is a giant paperweight that can't even be used as a boat anchor, cause I'd be fined for polluting our waterways with electronic devices.

    Not as dumb as yesterday, but stupider than tomorrow!

  10. #10
    Join Date
    May 2013
    Location
    australia
    Posts
    2,515


    Did you find this post helpful? Yes | No

    Default Re: Symbol not prev defined FSR - Elapsed Timer

    how big would Ticks have to be to make this true ?


    IF Ticks > 100 THEN
    Warning I'm not a teacher

  11. #11
    Join Date
    Jan 2005
    Location
    Montreal, Quebec, Canada
    Posts
    2,980


    Did you find this post helpful? Yes | No

    Default Re: Symbol not prev defined FSR - Elapsed Timer

    Quote Originally Posted by richard View Post
    how big would Ticks have to be to make this true ?

    IF Ticks > 100 THEN
    I have a feeling I'll be waiting a while for that to happen. I've brought that down to Ticks > 1.

    I've started again with the original includes, and:
    - added 32MHz
    - changed PIE1 to PIE4
    - changed PIR1 to PIR4
    - changed FSR to FSR0


    ...I'm adding T1CON and T1CLK now...


    I'm still puzzled by T1CON,TMR1ON. The datasheet doesn't have TMR1ON, it's just ON.


    EDIT: Confirmed, it works once I added T1CON and T1CLK. I was blindly following the instructions on the Book of Interrupts and forgetting that this PIC is different.

    a) I'm still puzzled why TMR1ON works though; seems contradictory to me.

    b) so 1 Tick is 66.4ms on a 16F18877.


    Blissful ignorance is a wonderful thing...
    Last edited by Demon; - 6th October 2024 at 04:55.
    My Creality Ender 3 S1 Plus is a giant paperweight that can't even be used as a boat anchor, cause I'd be fined for polluting our waterways with electronic devices.

    Not as dumb as yesterday, but stupider than tomorrow!

  12. #12
    Join Date
    May 2013
    Location
    australia
    Posts
    2,515


    Did you find this post helpful? Yes | No

    Default Re: Symbol not prev defined FSR - Elapsed Timer

    all bit definitions are in the mpasmx folder *.inc files. the datasheet refers to any timer1 type timer for that chip, ie tmr1 tmr3 tmr5

    eg
    Name:  Untitled.jpg
Views: 378
Size:  81.4 KB
    Last edited by richard; - 6th October 2024 at 05:35.
    Warning I'm not a teacher

  13. #13
    Join Date
    Jan 2005
    Location
    Montreal, Quebec, Canada
    Posts
    2,980


    Did you find this post helpful? Yes | No

    Default Re: Symbol not prev defined FSR - Elapsed Timer

    I want to post my code in Code Examples.

    What would be a good label for new PICs like the 16F18877 that need modified includes?
    My Creality Ender 3 S1 Plus is a giant paperweight that can't even be used as a boat anchor, cause I'd be fined for polluting our waterways with electronic devices.

    Not as dumb as yesterday, but stupider than tomorrow!

  14. #14
    Join Date
    Jan 2005
    Location
    Montreal, Quebec, Canada
    Posts
    2,980


    Did you find this post helpful? Yes | No

    Default Re: Symbol not prev defined FSR - Elapsed Timer

    Quote Originally Posted by richard View Post
    all bit definitions are in the mpasmx folder *.inc files.
    Should we edit those includes to match the names In the datasheet?

    Or is that opening another can of worms?
    My Creality Ender 3 S1 Plus is a giant paperweight that can't even be used as a boat anchor, cause I'd be fined for polluting our waterways with electronic devices.

    Not as dumb as yesterday, but stupider than tomorrow!

  15. #15
    Join Date
    May 2013
    Location
    australia
    Posts
    2,515


    Did you find this post helpful? Yes | No

    Default Re: Symbol not prev defined FSR - Elapsed Timer

    Should we edit those includes to match the names In the datasheet?
    absolutely not, there is no problem to solve

    if you want to use mpasm bit names in your code then use the bit names that microchip have created for them
    there is zero point in inventing names that mpasmx will not recognize.
    the proper and correct names are in the mpasmx picxxxxx.inc files
    Warning I'm not a teacher

  16. #16
    Join Date
    Jan 2005
    Location
    Montreal, Quebec, Canada
    Posts
    2,980


    Did you find this post helpful? Yes | No

    Default Re: Symbol not prev defined FSR - Elapsed Timer

    I have no clue why the elapsed timer worked once before I went to bed. I get up today, and I can't get it to repeat the same results.


    Quote Originally Posted by richard View Post
    ... a 16f18877 like all enhanced core pic16's has Auto context save the entire int_start / int_return macros are inappropriate...
    I didn't comprehend the depth of this statement, until now. I thought I was just forced to accept using Timer1 in the routines, and adapt my main code to use other timers.


    Quote Originally Posted by amgen View Post
    I would start off with interrupt and in routine just add to a counter. ..
    As they say, this is the way. I already have Timer1 running in 50ms intervals, I can easily repeat the same process with Timer3 and maintain a counter (I'm only after 100-200ms intervals anyways, this is just to avoid checking ADC every MainLoop).


    I really thought Elapsed Timer could work with the 16F18877. I didn't understand that the assembler code just doesn't work with the newer PICs.


    (Hopefully I haven't misunderstood anything this time )
    My Creality Ender 3 S1 Plus is a giant paperweight that can't even be used as a boat anchor, cause I'd be fined for polluting our waterways with electronic devices.

    Not as dumb as yesterday, but stupider than tomorrow!

  17. #17
    Join Date
    Jan 2005
    Location
    Montreal, Quebec, Canada
    Posts
    2,980


    Did you find this post helpful? Yes | No

    Default Re: Symbol not prev defined FSR - Elapsed Timer

    PIC 16F18877

    Timer1 at 50ms intervals
    Timer3 at 150ms intervals

    Code:

    Code:
    '***************************************************************************************************
    '                                                                                                  *
    '                         Generate trace on Interrupt on Logic Probe                               *
    '                                                                                                  *
    '                                       PIC 16F18877                                               *
    '                                                                                                  *
    '***************************************************************************************************
    #CONFIG
        __config _CONFIG1, _FEXTOSC_OFF & _RSTOSC_HFINT32 & _CLKOUTEN_OFF & _CSWEN_OFF & _FCMEN_ON
        __config _CONFIG2, _MCLRE_ON & _PWRTE_OFF & _LPBOREN_OFF & _BOREN_ON & _BORV_LO & _ZCD_OFF & _PPS1WAY_OFF & _STVREN_ON & _DEBUG_OFF
        __config _CONFIG3, _WDTCPS_WDTCPS_11 & _WDTE_OFF & _WDTCWS_WDTCWS_7 & _WDTCCS_LFINTOSC
        __config _CONFIG4, _WRT_OFF & _SCANE_available & _LVP_OFF
        __config _CONFIG5, _CP_OFF & _CPD_OFF
    #ENDCONFIG
    
    ;--- Interrupts ----------------------------------------------------------------
    
    include "I:\Project_v2\PBP\PBP_Includes\DT_INTS-14_16F18877.bas"
    include "I:\Project_v2\PBP\PBP_Includes\ReEnterPBP.bas"
    
    ASM
    INT_LIST  macro    ; IntSource,        Label,  Type, ResetFlag?
            INT_Handler    TMR1_INT,  _Timer1Interrupt,   PBP,  yes
            INT_Handler    TMR3_INT,  _Timer3Interrupt,   PBP,  yes
        endm
        INT_CREATE               ; Creates the interrupt processor
        INT_ENABLE    TMR1_INT   ;enables TMR1 interrupts
        INT_ENABLE    TMR3_INT   ;enables TMR3 interrupts
    ENDASM
    
    DEFINE OSC 32
    
    define  CCP1_REG     0
    DEFINE  CCP1_BIT     0
    define  CCP2_REG     0
    DEFINE  CCP2_BIT     0
    DEFINE  CCP3_REG     0
    DEFINE  CCP3_BIT     0
    define  CCP4_REG     0
    DEFINE  CCP4_BIT     0
    define  CCP5_REG     0              ' Must clear unused CCP pins or else unpredictable results
    DEFINE  CCP5_BIT     0
    
    RA4PPS = 0                          ' Disable CCP5
    RB0PPS = 0                          ' Disable CCP4
    RB5PPS = 0                          ' Disable CCP3
    RC1PPS = 0                          ' Disable CCP2
    RC2PPS = 0                          ' Disable CCP1
    
    T1CON = %00110001                                   ' 1:8 Prescale, Enables Timer1
    T3CON = %00110001                                   ' 1:8 Prescale, Enables Timer3
    '   bit 7-6 Unimplemented: Read as ‘0’
    '   bit 5-4 CKPS<1:0>: Timer1 Input Clock Prescale Select bits
    '        ---->  11 = 1:8 Prescale value
    '               10 = 1:4 Prescale value
    '               01 = 1:2 Prescale value
    '               00 = 1:1 Prescale value
    '   bit 3   Unimplemented: Read as ‘0’
    '   bit 2   SYNC: Timer1 Synchronization Control bit
    '                   When TMR1CLK = FOSC or FOSC/4
    '                       This bit is ignored. The timer uses the internal clock and no
    '                       additional synchronization is performed.
    '                   When TMR1CS<1:0> = (any setting other than FOSC or FOSC/4)
    '               1 = Do not synchronize external clock input
    '               0 = Synchronized external clock input with system clock
    '   bit 1   RD16: Timer1 On bit
    '               1 = All 16 bits of Timer1 can be read simultaneously (TMR1H is buffered)
    '               0 = 16-bit reads of Timer1 are disabled (TMR1H is not buffered)
    '   bit 0   ON: Timer1 On bit
    '        ---->  1 = Enables Timer1
    '               0 = Stops Timer1 and clears Timer1 gate flip-flop
    
    T1CLK = %00000001                                   ' FOSC/4 Timer1 Clock
    T3CLK = %00000001                                   ' FOSC/4 Timer1 Clock
    '   bit 7-4 Unimplemented: Read as ‘0’
    '   bit 3-0 TxCS<3:0>: Timer1/3/5 Clock Select bits
    '               1111 = LC4_out
    '               1110 = LC3_out
    '               1101 = LC2_out
    '               1100 = LC1_out
    '               1011 = TMR5 overflow output
    '               1010 = TMR3 overflow output
    '               1001 = TMR1 overflow output
    '               1000 = TMR0 overflow output
    '               0111 = CLKR output clock
    '               0110 = SOSC
    '               0101 = MFINTOSC                     ' 1.05msec @ 32MHz with no preload
    '               0100 = LFINTOSC                     ' n/a
    '               0011 = HFINTOSC                     ' 16.56msec @ 32MHz with no preload
    '               0010 = FOSC                         ' 16.54msec @ 32MHz with no preload
    '        ---->  0001 = FOSC/4                       ' 66.18msec @ 32MHz with no preload
    '               0000 = TxCKIPPS
    
    ANSELA = %00000000
    ANSELB = %00000000
    ANSELC = %00000000
    ANSELD = %00000000
    ANSELE = %00000000
    
    TRISA = %00000000                        
    TRISB = %00000000                      
    TRISC = %00000000                       
    TRISD = %00000000                      
    TRISE = %00001000
    
    Timer1Ended             var byte
    Timer3Ended             var byte
    Timer3Counter           var byte
    
      LatB.2 = 0            ' Set Timer1 trace low
      LatB.0 = 0            ' Set Timer3 trace low
      LatB.1 = 0                                            ' Set heartbeat trace low
    
        pause 1
    
        goto Start
    
    ;--- Interrupts ----------------------------------------------------------------
    
    Timer1Interrupt:
        T1CON.0 = 0                                 ' Stops Timer1
        Timer1Ended = 1                             ' Set flag
    @ INT_RETURN
    
    Timer3Interrupt:
        T3CON.0 = 0                                 ' Stops Timer3
        Timer3Ended = 1                             ' Set flag
    @ INT_RETURN
    
    ;--- Subroutines ---------------------------------------------------------------
    
    StartTimer1:
    @ INT_CLEAR TMR1_INT -- clear flags
        TMR1H = 62 : TMR1L = 95                    ' 50msec interval (32MHz, 16bit, 1:8)
        T1CON.0 = 1                                 ' Starts Timer1
        Timer1Ended = 0                             ' Set flag
      return
    
    StartTimer3:
    @ INT_CLEAR TMR1_INT -- clear flags
        TMR3H = 62 : TMR3L = 95                    ' 50msec interval (32MHz, 16bit, 1:8)
        T3CON.0 = 1                                 ' Starts Timer3
        Timer3Ended = 0                             ' Set flag
      return
    
    Start:
    
        GOSUB StartTimer1
      LatB.2 = 1            ' Start Timer1 trace
        Timer3Counter = 0
        GOSUB StartTimer3
      LatB.0 = 1            ' Start Timer3 trace
    
    Main:
      LatB.1 = 1                                            ' Pulse heartbeat
    
        IF Timer1Ended = 1 THEN  
      LatB.2 = 0            ' Stop Timer1 trace
            GOSUB StartTimer1
      LatB.2 = 1            ' Start Timer1 trace
        ENDIF
    
        IF Timer3Ended = 1 THEN  
            Timer3Counter = Timer3Counter + 1
            if Timer3Counter = 3 then
                Timer3Counter = 0
      LatB.0 = 0            ' Stop Timer3 trace
            endif
            GOSUB StartTimer3
      LatB.0 = 1            ' Start Timer3 trace
        ENDIF
    
      LatB.1 = 0                                            ' Reset heartbeat trace
      GOTO Main
    end
    Name:  Elapsed timer solution.png
Views: 166
Size:  19.4 KB
    My Creality Ender 3 S1 Plus is a giant paperweight that can't even be used as a boat anchor, cause I'd be fined for polluting our waterways with electronic devices.

    Not as dumb as yesterday, but stupider than tomorrow!

  18. #18
    Join Date
    Jan 2005
    Location
    Montreal, Quebec, Canada
    Posts
    2,980


    Did you find this post helpful? Yes | No

    Default Re: Symbol not prev defined FSR - Elapsed Timer

    In case someone needs it.

    DT_INTS-14_16F18877.bas, supports on 16F18877:

    - IOC
    - Timer1
    - Timer3
    - RX
    - CCP1
    - CCP2
    - CCP3
    - CCP4
    - CCP5

    Code:
    '***************************************************************************
    '*  Name    : DT_INTS-14_16F18877.bas                                      *
    '*  Author  : Darrel Taylor (modified by Demon)                            *
    '*  Version : 1.15 (8/29/2024)                                             *
    '*  Date    : OCT 13, 2009                                                 *
    '***************************************************************************
    '* REV 1.15  Customized for 16F1885xx-7x (IOC, USART-RX, CCPx)             *
    '* REV 1.10  Fixes Duplicate label error when Handlers cross page boundary *
    '*           Fixes error with 16F1's and MPLAB 8.53 (high)                 *
    '* REV 1.00  Completely re-written, with optimization and F1 chips in mind *
    '* REV 0.93  Fixed CMIF and EEIF problem with older PIC's                  *
    '*           that have the Flags in PIR1 instead of PIR2                   *
    '* Rev 0.92  solves a "Missed Interrupt" and                               *
    '*           banking switching problem                                     *
    '***************************************************************************
    DEFINE  DT_INTS_VERSION  110
    DEFINE  INTHAND  INT_ENTRY
    
    ;-- Place a copy of these variables in your Main program -------------------
    ;--   The compiler will tell you which lines to un-comment                --
    ;--   Do Not un-comment these lines                                       --
    ;---------------------------------------------------------------------------
    ;wsave   VAR BYTE    $20     SYSTEM      ' location for W if in bank0
    ;wsave   VAR BYTE    $70     SYSTEM      ' alternate save location for W 
                                             ' if using $70, comment wsave1-3
    
    ' --- IF any of these three lines cause an error ?? ------------------------
    '       Comment them out to fix the problem ----
    ' -- Which variables are needed, depends on the Chip you are using -- 
    ;wsave1  VAR BYTE    $A0     SYSTEM      ' location for W if in bank1
    ;wsave2  VAR BYTE    $120    SYSTEM      ' location for W if in bank2
    ;wsave3  VAR BYTE    $1A0    SYSTEM      ' location for W if in bank3
    ' --------------------------------------------------------------------------
    
    ssave       VAR BYTE    BANK0   SYSTEM      ' location for STATUS register
    psave       VAR BYTE    BANK0   SYSTEM      ' location for PCLATH register
    fsave       VAR BYTE    BANK0   SYSTEM      ' location for FSR register
    RetAddr     VAR WORD    BANK0   
    INT_Bits    VAR BYTE    BANK0
      Serviced  VAR INT_Bits.0
      Vars_Saved VAR INT_Bits.1
    
    GIE         VAR INTCON.7 
    PEIE        VAR INTCON.6
    
    ASM
      ifdef PM_USED                             ; verify MPASM is the assembler
        "ERROR: DT_INTS does not support the PM assembler, USE MPASM"
      endif
    
    ;---------------------------------------------------------------------------
      ifdef ReEnterUsed
        ifdef ReEnterVersion
          if (ReEnterVersion < 34)
            error "Wrong version of ReEnterPBP.bas - Ver 3.4 or higher required
          endif
        else
          error "Wrong version of ReEnterPBP.bas - Ver 3.4 or higher required
        endif
      endif
    
    ;---------------------------------------------------------------------------
        if (BANK0_END == 0x7F)
          ifdef BANK1_END
            if (BANK1_END == 0xEF)   ; doesn't find 12F683
              variable ACCESSRAM = 1
            else
              variable ACCESSRAM = 0    
            endif
          else
              variable ACCESSRAM = 0
          endif
        else
          variable ACCESSRAM = 0
        endif
        
    ;---------------------------------------------------------------------------
    #define OrChange Or change to   wsave BYTE $70 SYSTEM
    AddWsave macro B
      if (B == 0)
        if (ACCESSRAM == 1)
          error   "                     Add:"       wsave VAR BYTE $70 SYSTEM
        else
          error   "                     Add:"       wsave VAR BYTE $20 SYSTEM
        endif
      endif
      if (B == 1)
        if (ACCESSRAM == 1)
          error   "   Add:"       wsave1 VAR BYTE $A0 SYSTEM, OrChange
        else
          error   "                     Add:"       wsave1 VAR BYTE $A0 SYSTEM
        endif
      endif
      if (B == 2)
        if (ACCESSRAM == 1)
          error   "   Add:"       wsave2 VAR BYTE $120 SYSTEM, OrChange
        else
          error   "                     Add:"       wsave2 VAR BYTE $120 SYSTEM
        endif
      endif
      if (B == 3)
        if (ACCESSRAM == 1)
          error   "   Add:"       wsave3 VAR BYTE $1A0 SYSTEM, OrChange
        else
          error   "                     Add:"       wsave3 VAR BYTE $1A0 SYSTEM
        endif
      endif
      endm
      
    #define WsaveE1(B) Chip has RAM in BANK#v(B), but wsave#v(B) was not found.
    ;#define WsaveE2(B) Uncomment wsave#v(B) in the DT_INTS-14.bas file.
    #define WsaveCouldBe This chip has access RAM at $70
      
    #define WsaveError(B) error  WsaveE1(B)
      ifndef FSR0L     ; not a 16F1
        ifndef wsave
    ;      if (ACCESSRAM == 1)
            error wsave variable not found,
            AddWsave(0)
            variable wsave = 0 ; stop further wsave errors
    ;      else
            
    ;      endif
        else
          if (wsave == 0x70)
            if (ACCESSRAM == 0)
              error This chip does not have AccessRAM at $70, change to   wsave VAR BYTE $20 SYSTEM
            endif
          else
              if (wsave != 0x20)
                error wsave must be either $20 or $70
              endif
          endif
        endif
        ifdef BANK1_START
          ifndef wsave1
            ifdef wsave
              if (wsave != 0x70)
                WsaveError(1)
                AddWsave(1)
              endif
            else
              if (ACCESSRAM == 1)
                if (wsave != 0x70)
                  WsaveCouldBe 
                endif
              endif
            endif
          endif
        endif
        ifdef BANK2_START
          ifndef wsave2
            ifdef wsave
              if (wsave != 0x70)
                WsaveError(2)
                AddWsave(2)
              endif
            endif
          endif
        endif
        ifdef BANK3_START
          ifndef wsave3
            ifdef wsave
              if (wsave != 0x70)
                WsaveError(3)
                AddWsave(3)
              endif
            endif
          endif
        endif
      
            
      endif
    ENDASM
    
    ASM
    asm = 0
    Asm = 0
    ASM = 0
    pbp = 1
    Pbp = 1
    PBP = 1
    yes = 1
    Yes = 1
    YES = 1
    no  = 0
    No  = 0
    NO  = 0
    
    
    ;---[Original DEFINES]------------------------------------------------------
      #define ALL_INT      INTCON,GIE, INTCON,GIE      ;-- Global Interrupts   *
    ;  #define IOC_INT      INTCON,IOCIF, INTCON,IOCIE  ;-- Int On Change
    ;  #define RX_INT       PIR1,RCIF, PIE1,RCIE        ;-- USART Receive
    ;  #define CCP1_INT     PIR1,CCP1IF, PIE1,CCP1IE    ;-- CCP1
    ;  #define CCP2_INT     PIR2,CCP2IF, PIE2,CCP2IE    ;-- CCP2
    ;  #define CCP3_INT     PIR3,CCP3IF, PIE3,CCP3IE    ;-- CCP3
    ;  #define CCP4_INT     PIR3,CCP4IF, PIE3,CCP4IE    ;-- CCP4
    ;  #define CCP5_INT     PIR3,CCP5IF, PIE3,CCP5IE    ;-- CCP5
      #define IOC_INT      PIR0,IOCIF, PIE0,IOCIE      ;-- Int On Change
      #define TMR1_INT     PIR4,TMR1IF, PIE4,TMR1IE    ;-- Timer1
      #define TMR3_INT     PIR4,TMR3IF, PIE4,TMR3IE    ;-- Timer3
      #define RX_INT       PIR3,RCIF, PIE3,RCIE        ;-- USART Receive
      #define CCP1_INT     PIR6,CCP1IF, PIE6,CCP1IE    ;-- CCP1
      #define CCP2_INT     PIR6,CCP2IF, PIE6,CCP2IE    ;-- CCP2
      #define CCP3_INT     PIR6,CCP3IF, PIE6,CCP3IE    ;-- CCP3
      #define CCP4_INT     PIR6,CCP4IF, PIE6,CCP4IE    ;-- CCP4
      #define CCP5_INT     PIR6,CCP5IF, PIE6,CCP5IE    ;-- CCP5
    ENDASM
    
    
    ASM
    ;---[Returns the Address of a Label as a Word]------------------------------
    GetAddress macro Label, Wout
        CHK?RP Wout
        movlw low Label          ; get low byte
        movwf Wout
    ;    movlw High Label         ; get high byte  MPLAB 8.53 killed high
        movlw Label >> 8         ; get high byte
        movwf Wout + 1
      endm
    
    ;---[find correct bank for a BIT variable]----------------------------------
    CHKRP?T  macro reg, bit
        CHK?RP  reg
      endm
        
    ;---[This creates the main Interrupt Service Routine (ISR)]-----------------
    INT_CREATE  macro
      local OverCREATE
        L?GOTO OverCREATE
    
    INT_ENTRY
        ifndef FSR0L  
          if (CODE_SIZE <= 2)
              movwf   wsave       ; 1 copy W to wsave register
              swapf   STATUS,W    ; 2 swap status reg to be saved into W
              clrf    STATUS      ; 3 change to bank 0
              movwf   ssave       ; 4 save status reg to a bank 0 register
              movf    PCLATH,W    ; 5 move PCLATH reg to be saved into W reg
              movwf   psave       ; 6 save PCLATH reg to a bank 0 register
          endIF
          movf      FSR,W         ; 7 move FSR reg to be saved into W reg
          movwf     fsave         ; 8 save FSR reg to a bank 0 register
        else
          banksel 0               ; BANK 0 for F1 chips
        endif  
        variable  PREV_BANK = 0
        MOVE?CT  0, _Vars_Saved
        
    List_Start
        ifdef LoopWhenServiced
          MOVE?CT  0, _Serviced   ; indicate nothing has been serviced
        endif
    
        INT_LIST                  ; Expand the users list of interrupt handlers
                                ; INT_LIST macro must be defined in main program
        
        ifdef LoopWhenServiced
          BIT?GOTO  1, _Serviced, List_Start
        endif
    
        ifdef ReEnterUsed         ; if ReEnterPBP.bas was included
            CHKRP?T  _Vars_Saved
            btfss    _Vars_Saved  ; if PBP system vars have been saved 
            goto     INT_EXIT
            L?GOTO   _RestorePBP  ; Restore PBP system Vars
        endif
        
    INT_EXIT
        variable  PREV_BANK = 0
        ifndef FSR0L              ; if chip is not an F1 - restore context
          clrf    STATUS          ; BANK 0
          movf    fsave,W         ; Restore the FSR reg
          movwf   FSR
          movf    psave,w         ; Restore the PCLATH reg
          movwf   PCLATH
          swapf   ssave,w         ; Restore the STATUS reg
          movwf   STATUS
          swapf   wsave,f
          swapf   wsave,w         ; Restore W reg
        endif
        retfie                    ; Exit the interrupt routine
    ;-----------------------------
      LABEL?L OverCREATE
        bsf      INTCON, 6      ; Enable Peripheral interrupts
        bsf      INTCON, 7      ; Enable Global interrupts
        endm
        
    ENDASM
    
    ASM
    ;---[Add an Interrupt Source to the user's list of INT Handlers]------------
    #INT_HANDLER  macro  FlagReg,FlagBit, EnableReg,EnableBit, Label, Type,Reset
      list
        local AfterSave, AfterUserRoutine, NoInt
          ifdef FlagBit
            CHK?RP   EnableReg
            btfss    EnableReg, EnableBit        ; if the INT is enabled
            goto     NoInt
            CHK?RP   FlagReg                    
            btfss    FlagReg, FlagBit            ; and the Flag set?
            goto     NoInt
            ifdef LoopWhenServiced
              MOVE?CT  1, _Serviced
            endif
                
            if (Type == PBP)                     ; If INT handler is PBP
              ifdef ReEnterUsed
                btfsc  _Vars_Saved
                goto   AfterSave
                GetAddress  AfterSave, _RetAddr  
                L?GOTO  _SavePBP                 ; Save PBP system Vars
                LABEL?L  AfterSave
              else
                error ReEnterPBP must be INCLUDEd to use PBP type interrupts
              endif
            endif
            GetAddress  AfterUserRoutine, _RetAddr   ; save return address
            L?GOTO   Label                       ; goto the users INT handler
            LABEL?L AfterUserRoutine
    
            if (Reset == YES)
              CHK?RP   FlagReg
              bcf      FlagReg, FlagBit        ; reset flag (if specified)
            endif
          else
            INT_ERROR  "INT_Handler"
          endif
    NoInt
          banksel  0
    PREV_BANK = 0        
        endm
    ;-----------------------------------
    #define INT_HANDLER(FlagReg,FlagBit, EnableReg,EnableBit, Label, Type,Reset)  #INT_HANDLER FlagReg,FlagBit, EnableReg,EnableBit, Label, Type,Reset
      ifndef INT_Handler
    #define INT_Handler(FlagReg,FlagBit, EnableReg,EnableBit, Label, Type,Reset)  #INT_HANDLER FlagReg,FlagBit, EnableReg,EnableBit, Label, Type,Reset
    #define int_handler(FlagReg,FlagBit, EnableReg,EnableBit, Label, Type,Reset)  #INT_HANDLER FlagReg,FlagBit, EnableReg,EnableBit, Label, Type,Reset
    #define Int_Handler(FlagReg,FlagBit, EnableReg,EnableBit, Label, Type,Reset)  #INT_HANDLER FlagReg,FlagBit, EnableReg,EnableBit, Label, Type,Reset
    #define Int_handler(FlagReg,FlagBit, EnableReg,EnableBit, Label, Type,Reset)  #INT_HANDLER FlagReg,FlagBit, EnableReg,EnableBit, Label, Type,Reset
    #define int_Handler(FlagReg,FlagBit, EnableReg,EnableBit, Label, Type,Reset)  #INT_HANDLER FlagReg,FlagBit, EnableReg,EnableBit, Label, Type,Reset
      endif
      
    ;---[Returns from a "goto" subroutine]--------(RetAddr must be set first)---
    #INT_RETURN  macro
          CHK?RP  _RetAddr
          movf    _RetAddr + 1, W  ; Set PCLATH with top byte of return address
          movwf   PCLATH
          movf    _RetAddr, W      ; Go back to where we were
          movwf   PCL
        endm    
    ;_____________________________
    #define INT_RETURN  #INT_RETURN
      ifndef INT_Return
    #define INT_Return  #INT_RETURN 
    #define int_return  #INT_RETURN 
    #define Int_Return  #INT_RETURN 
    #define Int_return  #INT_RETURN 
    #define int_Return  #INT_RETURN 
      endif
    
    ;----[Display not found error]----------------------------------------------
    INT_ERROR macro From
        error From -  Interrupt Flag ( FlagReg,FlagBit ) not found.
      endm
    
    ;---[Enable an interrupt source]--------------------------------------------
      ifndef INT_ENABLECLEARFIRST
        #define INT_ENABLECLEARFIRST 1             ; default to Clear First
      endif          ; use DEFINE INT_ENABLECLEARFIRST 0 to NOT clear First
      
    #INT_ENABLE  macro  FlagReg, FlagBit, EnableReg, EnableBit
          ifdef FlagBit
            ifdef INT_ENABLECLEARFIRST
              if (INT_ENABLECLEARFIRST == 1)       ; if specified
                MOVE?CT 0, FlagReg, FlagBit        ;   clear the flag first
              endif
            endif
            MOVE?CT  1, EnableReg, EnableBit       ; enable the INT source
          else
            INT_ERROR  "INT_ENABLE"
          endif
        endm    
    ;_____________________________
    #define INT_ENABLE(FlagReg, FlagBit, EnableReg, EnableBit)  #INT_ENABLE FlagReg, FlagBit, EnableReg, EnableBit
      ifndef INT_Enable
    #define INT_Enable(FlagReg, FlagBit, EnableReg, EnableBit)  #INT_ENABLE FlagReg, FlagBit, EnableReg, EnableBit
    #define int_enable(FlagReg, FlagBit, EnableReg, EnableBit)  #INT_ENABLE FlagReg, FlagBit, EnableReg, EnableBit
    #define Int_Enable(FlagReg, FlagBit, EnableReg, EnableBit)  #INT_ENABLE FlagReg, FlagBit, EnableReg, EnableBit
    #define Int_enable(FlagReg, FlagBit, EnableReg, EnableBit)  #INT_ENABLE FlagReg, FlagBit, EnableReg, EnableBit
    #define int_Enable(FlagReg, FlagBit, EnableReg, EnableBit)  #INT_ENABLE FlagReg, FlagBit, EnableReg, EnableBit
      endif
    
    ;---[Disable an interrupt source]-------------------------------------------
    #INT_DISABLE  macro  FlagReg, FlagBit, EnableReg, EnableBit
          ifdef FlagBit
            MOVE?CT  0, EnableReg, EnableBit       ; disable the INT source  
          else
            INT_ERROR  "INT_DISABLE"
          endif
        endm    
    ;_____________________________
    #define INT_DISABLE(FlagReg, FlagBit, EnableReg, EnableBit)  #INT_DISABLE FlagReg, FlagBit, EnableReg, EnableBit
      ifndef INT_Disable
    #define INT_Disable(FlagReg, FlagBit, EnableReg, EnableBit)  #INT_DISABLE FlagReg, FlagBit, EnableReg, EnableBit
    #define int_disable(FlagReg, FlagBit, EnableReg, EnableBit)  #INT_DISABLE FlagReg, FlagBit, EnableReg, EnableBit
    #define Int_Disable(FlagReg, FlagBit, EnableReg, EnableBit)  #INT_DISABLE FlagReg, FlagBit, EnableReg, EnableBit
    #define Int_disable(FlagReg, FlagBit, EnableReg, EnableBit)  #INT_DISABLE FlagReg, FlagBit, EnableReg, EnableBit
    #define int_Disable(FlagReg, FlagBit, EnableReg, EnableBit)  #INT_DISABLE FlagReg, FlagBit, EnableReg, EnableBit
      endif
    
    ;---[Clear an interrupt Flag]-----------------------------------------------
    #INT_CLEAR  macro  FlagReg, FlagBit, EnableReg, EnableBit
          ifdef FlagBit
            MOVE?CT  0, FlagReg, FlagBit           ; clear the flag
          else
            INT_ERROR "INT_CLEAR" 
          endif
        endm
    ;_____________________________
    #define INT_CLEAR(FlagReg, FlagBit, EnableReg, EnableBit)  #INT_CLEAR FlagReg, FlagBit, EnableReg, EnableBit
      ifndef INT_Clear
    #define INT_Clear(FlagReg, FlagBit, EnableReg, EnableBit)  #INT_CLEAR FlagReg, FlagBit, EnableReg, EnableBit
    #define int_clear(FlagReg, FlagBit, EnableReg, EnableBit)  #INT_CLEAR FlagReg, FlagBit, EnableReg, EnableBit
    #define Int_Clear(FlagReg, FlagBit, EnableReg, EnableBit)  #INT_CLEAR FlagReg, FlagBit, EnableReg, EnableBit
    #define Int_clear(FlagReg, FlagBit, EnableReg, EnableBit)  #INT_CLEAR FlagReg, FlagBit, EnableReg, EnableBit
    #define int_Clear(FlagReg, FlagBit, EnableReg, EnableBit)  #INT_CLEAR FlagReg, FlagBit, EnableReg, EnableBit
      endif
    ENDASM
    My Creality Ender 3 S1 Plus is a giant paperweight that can't even be used as a boat anchor, cause I'd be fined for polluting our waterways with electronic devices.

    Not as dumb as yesterday, but stupider than tomorrow!

  19. #19
    Join Date
    May 2013
    Location
    australia
    Posts
    2,515


    Did you find this post helpful? Yes | No

    Default Re: Symbol not prev defined FSR - Elapsed Timer

    I didn't comprehend the depth of this statement, until now. I thought I was just forced to accept using Timer1 in the routines, and adapt my main code to use other timers.
    i doubt i will understand how you came to that conclusion. you will need a different strategy if you plan additional interrupt usage as there can only be one interrupt handler, dt's elapsed timer takes it over entirely


    by the way the newer chips are easier to use

    i called this dlapsed.pbp,
    Code:
    '****************************************************************
    '*  Name    : ELAPSED.PBP                                       *
    '*  Author  : Darrel Taylor                                     *
    '*  Notice  : Copyright (c) 2003                                *
    '*  Date    : 12/16/2003                                        *
    '*  Notes   : its based on this                                 *
    '****************************************************************
    '*  Name    : DLAPSED.PBP                                       *
    '*  Author  : Richard                                           *
    '*  Date    : 2024-10-05                                        *
    '*  Notes   :  for 16F18877 or similar                          *
    '             a) @32MHz                                         *
    '             b) Used Timer3                                    *
    '****************************************************************
    
    
    Define  INTHAND _ClockCount    ' Tell PBP Where the code starts on an interrupt
    
    
    
    
    Ticks    VAR BYTE   ' 1/100th of a second
    Seconds  VAR BYTE
    Minutes  VAR BYTE
    Hours    VAR BYTE
    Days     VAR WORD
    R0save   VAR WORD
    R1save   VAR WORD
    
    
    ZERO             VAR BIT
    CountDown        VAR BIT
    SecondsChanged   VAR BIT
    MinutesChanged   VAR BIT
    HoursChanged     VAR BIT
    DaysChanged      VAR BIT
    
    
    CountDown = 0
    SecondsChanged = 1
    MinutesChanged = 1
    
    
    Goto OverElapsed
    
    
    ' ------------------------------------------------------------------------------
    Asm
    
    
    TimerConst = 45537		     ; 100Hz 
      
      
    ; -----------------  ADD TimerConst to TMR3H:TMR3L
    ADD2_TIMER   macro
        CHK?RP  T3CON
        BCF     T3CON,TMR3ON           ; Turn off timer  
        MOVLW   LOW(TimerConst)        ;  1
        ADDWF   TMR3L,F                ;  1    ; reload timer with correct value
        BTFSC   STATUS,C               ;  1/2
        INCF    TMR3H,F                ;  1
        MOVLW   HIGH(TimerConst)       ;  1
        ADDWF   TMR3H,F                ;  1
        endm
    
    
    ; -----------------  ADD TimerConst to TMR3H:TMR3L and restart Timer3 
    RELOAD_TIMER  macro
        ADD2_TIMER
        BSF     T3CON,TMR3ON           ;  1    ; Turn Timer3 back on
        CHK?RP  PIR4
        bcf     PIR4, TMR3IF           ; Clear Timer3 Interrupt Flag
        endm
    
    
    ; -----------------  Load TimerConst into TMR3H:TMR3L 
    LOAD_TIMER  macro
    EndAsm
        T3CON.0 = 0                    ; Turn OFF Timer3
        TMR3L = 0
        TMR3H = 0
    Asm
        ADD2_TIMER
        endm
    EndAsm
    
    
    ' ------[ This is the Interrupt Handler ]---------------------------------------
    ClockCount:   ' Note: this is being handled as an ASM interrupt
                       
    @  RELOAD_TIMER                    ; Reload Timer3
       R0save = R0                     ; Save 2 PBP system vars that are used during
       R1save = R1                     ; the interrupt
       Ticks = Ticks + 1
       if Ticks = 100 then
          Ticks = 0
          IF CountDown THEN
             IF Seconds > 0 THEN
                Seconds = Seconds - 1
                SecondsChanged = 1
                IF Seconds = 0 THEN
                   IF Days = 0 THEN
                      IF Hours = 0 THEN
                         IF Minutes = 0 THEN
                            GOSUB StopTimer    ; Zero reached
                            ZERO = 1
                         ENDIF
                      ENDIF
                   ENDIF
                ENDIF
             ELSE
                IF Minutes > 0 THEN
                   Minutes = Minutes - 1
                   Seconds = 59
                   SecondsChanged = 1
                   MinutesChanged = 1
                ELSE
                   IF Hours > 0 THEN
                      Hours = Hours - 1
                      Minutes = 59
                      Seconds = 59
                      SecondsChanged = 1
                      MinutesChanged = 1
                      HoursChanged = 1
                   ELSE
                      IF Days > 0 THEN
                         Days = Days - 1
                         Hours = 23
                         Minutes = 59
                         Seconds = 59
                         SecondsChanged = 1
                         MinutesChanged = 1
                         HoursChanged = 1
                         DaysChanged = 1
                      ELSE                     ; Zero already reached, shouldn't get here
                         GOSUB StopTimer
                         ZERO = 1
                      ENDIF
                   ENDIF
                ENDIF
             ENDIF
          ELSE                                ; Counting Up
             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
          endif
       ENDIF
       R1 = R1save                     ; Restore the PBP system vars
       R0 = R0save
    @  RETFIE                      ; Restore context and return from interrupt
    
    
    '-----====[ END OF TMR3 Interrupt Handler ]====---------------------------------
    
    
    StartTimer:
      IF NOT ZERO THEN
        T3CLK   = 1                   ;  clock source
        t3con = $20                   ;  prescaler
        PIR4.2  = 0                   ; (TMR3IF) Clear Timer3 Interrupt Flag
        PIE4.2  = 1                   ; (TMR3IE) Enable TMR3 overflow interrupt
        INTCON.6 = 1                  ; (PEIE) Enable peripheral interrupts
        INTCON.7 = 1                  ; (GIE) Enable global interrupts
        T3CON.0 = 1                   ; (TMR3ON) Start Timer3
      ENDIF
    return
    
    
    ; -----------------
    StopTimer:
        T3CON.0 = 0                   ; Turn OFF Timer3
    return
    
    
    ; -----------------
    ResetTime:
        ZERO = 0
        R0save = T3CON.0              ; Save TMR3ON bit
        T3CON.0 = 0                   ; Turn OFF Timer3
        TMR3L = 0
        TMR3H = 0
    @   LOAD_TIMER                    ; Load TimerConst
        T3CON.0 = R0save              ; Restore TMR3ON bit
        Ticks = 0
        Seconds = 0
        Minutes = 0
        Hours = 0
        Days = 0
        SecondsChanged = 1
    return
    
    
    OverElapsed:
    usage demo


    Code:
    #CONFIG
        __config _CONFIG1, _FEXTOSC_OFF & _RSTOSC_HFINT32 & _CLKOUTEN_OFF & _CSWEN_OFF & _FCMEN_ON
        __config _CONFIG2, _MCLRE_ON & _PWRTE_OFF & _LPBOREN_OFF & _BOREN_ON & _BORV_LO & _ZCD_OFF & _PPS1WAY_OFF & _STVREN_ON & _DEBUG_OFF
        __config _CONFIG3, _WDTCPS_WDTCPS_11 & _WDTE_ON & _WDTCWS_WDTCWS_7 & _WDTCCS_LFINTOSC
        __config _CONFIG4, _WRT_OFF & _SCANE_available & _LVP_ON
        __config _CONFIG5, _CP_OFF & _CPD_OFF
    #ENDCONFIG
    
    
    DEFINE OSC 32
    
    
    ANSELA = 0
    TRISA = %11101111
    
    
    INCLUDE "DLAPSED.PBP "   ' Elapsed Timer Routines
    Days = 0                  ' set initial time
    Hours = 0
    Minutes = 1
    Seconds = 0
    ZERO = 0
    GOSUB StartTimer 
    
    
    Main:
        IF SecondsChanged THEN  
            Lata.4 = !Lata.4   ' flash led on porta.4
            SecondsChanged = 0
        ENDIF
    GOTO Main
    end
    Warning I'm not a teacher

Similar Threads

  1. Replies: 11
    Last Post: - 23rd August 2024, 03:13
  2. Replies: 7
    Last Post: - 2nd January 2018, 05:17
  3. Symbol not previously defined - lib file
    By Scampy in forum mel PIC BASIC Pro
    Replies: 13
    Last Post: - 2nd November 2015, 01:33
  4. symbol not prev. def. _INTRC_OSC 16F88
    By MarkR in forum mel PIC BASIC Pro
    Replies: 4
    Last Post: - 29th July 2011, 23:33
  5. Symbol not previously defined
    By Archangel in forum Code Examples
    Replies: 2
    Last Post: - 27th December 2008, 10:52

Members who have read this thread : 9

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