News:

PROTON pic BASIC Compilers for PIC, PIC24, dsPIC33

Main Menu

Value overflow

Started by midali, Mar 01, 2022, 12:59 PM

Previous topic - Next topic

midali

Thank you David ! I use only analogic servoes for the moment , but is good to know .

The complete time for bytes reception with HRSIN is 4,1ms .  A simple way can be using pulsout :

chloop:
HRSIn Wait($20,$40),Ch1,Ch2,Ch3,Ch4,Ch5,Ch6,Ch7,Ch8    ',Ch9,Ch10
high porta.0 :delayus ch1 :low porta.0
high porta.1 :delayus ch2 :low porta.1

'...next channels
delayms 12
goto chloop

Using timer1 all channels start in the same time ; using pulsout the channels start one after another .
Which way is the best ? using timer 1 or pulsout  ?

david

Hi,
If you only want about 6-7 channels then sequential outputs are fine and will fit in a 20mS frame rate. You could use Pulsout for this.   If you want more than 8 channels I think you have to use simultaneous outputs (using Timer1) or tolerate a frame rate greater than 20mS which may not be acceptable for some applications.
The iBus frame rate is around 7mS and includes both the control data (14 channels) and telemetry data, when available.
 
Cheers,
David

top204

If it is servos that are being controlled, they can operate within an interrupt, thus operate in the background.

See the demo program "Servo_Demo.bas". Located at "C:\Users\User ID\PDS\Samples\New Samples\Multi_Servo_Controller"

It allows up to 8 servos to operate in the background.

It is written for a PIC18F25K20 device, but can be altered for any device type.


david

Thanks for posting Les.
I was aware of the servo code examples but hadn't taken the time to fully understand the Servos_Inc operation. 
Unlike midali I don't have a current need for the code but I'm now curious if it would help to eliminate the last few uS of channel crosstalk in the simple code previously posted.

Cheers,
David

midali

#24
Thank you for remember Les !

Quote from: top204 on Mar 03, 2022, 05:42 PMIf it is servos that are being controlled, they can operate within an interrupt, thus operate in the background.

I use 18F26k20 for servo controll. If I change in inc file another 16 bit timer instead TMR1 , will it work ?
I have to use Pulsin f or pulses reading and Timer3 for servoes controll , its possible ?

tumbleweed

With the 18F26K20 you can set CCP1 to use either TMR1 or TMR3.

The selection is done using the T3CON T3CCP<2:1> bits.

top204

If I remember, the interrupt uses the CCP peripheral to give a certain time period for it, so any timer can be used to generate the interrupt, as long is its period rate is correct. I think it was set so the servos were updated every 20ms, or so...

It's been so long since I wrote the code, I cannot remember all the details of it. :-)

midali

Hi Les ,

Pulsin use TMR1 and CCP1 for capture and measuring the pulse, right ? if is needed to drive some servos, must use TMR3 and CCP2 or TMR3 must use with CCP1 ?
My question is if I can read a pulse with Pulsin and drive some servos with the 26k20 ? File Servos.inc can be modified for that  ?


tumbleweed

I don't know what pulsin uses, but if TMR1 and CCP1 are already being used then you can use TMR3 and CCP2... you just need to set the registers to do that.

top204

PulseIn in purely software based, and uses no peripherals.

The servo code is for any device, but the peripheral SFRs will need to be tweaked.

midali

PulseIn and servo.inc file can't work togheter,which I think because both use timer1 .After tests I saw signals on servo outputs are chaotic. I thought that if I change in the example file for timer 3 I will solve the problem, but I didn't succeed because its hard to understand the code and I have no more experience with interrupts.

Les, please, the effort is great to modify that servo.inc file to work with timer3? ... or a solution to use PulseIn with servo in the background? This is very useful for all those who work with servos. I promise a box of beers straight to the door ..

tumbleweed

Since Les stated that PulseIn doesn't use any peripherals, changing servo.inc to use TMR3 won't "fix" anything.

Post the code you're using that doesn't appear to work.

midali

The code is :


Device 18F26K20
Declare Xtal = 4

set_reg()
Dim ada As Byte

'------------------------------------------------------------
    $define Servo_NumberOfServos 8              ' Amount of servos attached
    $define Servo_Priority ipHigh               ' Choose a high priority interrupt
    Include "Servos.inc"                        ' Load the Servo routines into the program

'------------------------------------------------------------
    Dim CountVar As Word
'------------------------------------------------------------
Main:
    Servo_On()                                  ' Start sending servo control pulses

    Do
     ada =   PulseIn PORTA.4, 1
     CountVar = ada *10
            Servo1_Position(CountVar)
            Servo2_Position(CountVar)
            Servo3_Position(CountVar)
            Servo4_Position(CountVar)
            Servo5_Position(CountVar)
            Servo6_Position(CountVar)
            Servo7_Position(CountVar)
            Servo8_Position(CountVar)
            DelayUS 512
        'Next
   ' DelayMS 1000
 
    Loop
 '-------------------------Set registry----------------------------
Proc set_reg()
 Config_Start
'   FOSC = HS ; HS oscillator
'   FOSC = HSPLL ; HS oscillator, PLL enabled (Clock Frequency = 4 x FOSC1)
   FOSC = INTIO67 ; INTERNAL OSCILLATOR .PORTA.6 AND 7 I/O's
   FCMEN = OFF ; Fail-Safe Clock Monitor disabled
   IESO = OFF ; Oscillator Switchover mode disabled
   PWRT = OFF ; PWRT enabled
   BOREN = SBORDIS ; Brown-out Reset enabled and controlled by software (SBOREN is enabled)
   BORV = 18 ; VBOR set to 2.7 V nominal
   WDTEN = OFF ; WDT is controlled by SWDTEN bit of the WDTCON register
   MCLRE = OFF ; MCLR pin enabled, RE3 input pin disabled
   HFOFST = OFF ; The system clock is held off until the HF-INTOSC is stable.
   LPT1OSC = OFF ; Disabled, T1 operates in standard power mode.
   PBADEN = OFF ; PORTB<4:0> pins are configured as digital I/O on Reset
   STVREN = On ; Stack full/underflow will cause Reset
   LVP = OFF ; Single-Supply ICSP disabled
   XINST = OFF ; Instruction set extension and Indexed Addressing mode disabled (Legacy mode)
   Debug = OFF ; Background debugger disabled, RB6 and RB7 configured as general purpose I/O pins
   Cp0 = On ; Block 0 (000800-003FFFh) not code-protected
   CP1 = On ; Block 1 (004000-007FFFh) not code-protected
   CP2 = On ; Block 2 (008000-00BFFFh) not code-protected
   CP3 = On ; Block 3 (00C000-00FFFFh) not code-protected
   CPB = On ; Boot block (000000-0007FFh) not code-protected
   CPD = On ; Data EEPROM not code-protected
   WRT0 = OFF ; Block 0 (000800-003FFFh) not write-protected
   WRT1 = OFF ; Block 1 (004000-007FFFh) not write-protected
   WRT2 = OFF ; Block 2 (008000-00BFFFh) not write-protected
   WRT3 = OFF ; Block 3 (00C000-00FFFFh) not write-protected
   WRTB = OFF ; Boot block (000000-0007FFh) not write-protected
   WRTC = OFF ; Configuration registers (300000-3000FFh) not write-protected
   WRTD = OFF ; Data EEPROM not write-protected
   EBTR0 = OFF ; Block 0 (000800-003FFFh) not protected from table reads executed in other blocks
   EBTR1 = OFF ; Block 1 (004000-007FFFh) not protected from table reads executed in other blocks
   EBTR2 = OFF ; Block 2 (008000-00BFFFh) not protected from table reads executed in other blocks
   EBTR3 = OFF ; Block 3 (00C000-00FFFFh) not protected from table reads executed in other blocks
   EBTRB = OFF ; Boot block (000000-0007FFh) not protected from table reads executed in other blocks
Config_End

OSCCON = %01010110  'INTERNAL OSCILLATOR

EndProc


...and servos.inc


$ifndef _SERVOS_INC_
$define _SERVOS_INC_
(*
 Controls 1 to 8 hobby servos connected to pins of PortB:
 Servo 0 connects to PortB.0, Servo 1 connects to PortB.1, etc.

 Servos are positioned by sending pulses between 600uS and 2400uS long every 20mS.
 Pulse length of 1500uS = approximate halfway point.

 Set servo positions by loading the desired pulse length (in uS) into the wServo_Position array:-
 wServo_Position[3] = 2400 sets servo 3 to its maximum point.

 Use Servo_On() to enable Interrupt and start sending pulses to servos.
 Use Servo_Off() to stop Interrupt firing and stop sending pulses to servos.

 Flag tServo_InterruptComplete is set to true when the Interrupt code has just finished.
 The main program may poll this flag to know when it is safe to run timing-sensitive code.

 Uses the Timer1 and Compare peripherals to trigger an interrupt at the correct intervals for servo pulses.
 Works with clock speeds of 4, 8, 16, and 32MHz.
*)
'
' Written by Les Johnson for the Positron8 BASIC compiler.
' https://sites.google.com/view/rosetta-tech/home
'

$ifndef ipHigh
    $define ipHigh 1
$endif
$ifndef ipLow
    $define ipLow 0
$endif

$ifndef False
    $define False 0
$endif
$ifndef True
    $define True 1
$endif

$ifndef Servo_NumberOfServos
    $define Servo_NumberOfServos 8              ' Default to 8 servos
$endif

$ifndef Servo_Priority
    $define Servo_Priority ipHigh               ' Default to Servo interrupt priority high
$endif

$if Servo_Priority = ipHigh
    On_Hardware_Interrupt GoTo OnTimer_ISR
$else
    On_Low_Interrupt GoTo OnTimer_ISR
$endif
'===============================================================================
' Variable and Alias Declarations
'-------------------------------------------------------------------------------

$if (Servo_NumberOfServos > 0) And (Servo_NumberOfServos < 9)
    $if Servo_NumberOfServos = 1                    ' \
        $define cOffMask %11111110                  ' |
    $elseif Servo_NumberOfServos = 2                ' |
        $define cOffMask %11111100                  ' |
    $elseif Servo_NumberOfServos = 3                ' | According to how many
        $define cOffMask %11111000                  ' | servos are connected, set
    $elseif Servo_NumberOfServos = 4                ' | the mask which is AND'd
        $define cOffMask %11110000                  ' | with PortB to turn off the
    $elseif Servo_NumberOfServos = 5                ' | servo pins.
        $define cOffMask %11100000                  ' |
    $elseif Servo_NumberOfServos = 6                ' |
        $define cOffMask %11000000                  ' |
    $elseif Servo_NumberOfServos = 7                ' |
        $define cOffMask %10000000                  ' |
    $else                                           ' |
        $define cOffMask %00000000                  ' /
    $endif
$else
     $error "Servo_NumberOfServos $define value must be in the range of 1 to 8"
$endif

$if _xtal = 4                                       ' \
    $define cTimer1Config %00000000                 ' |
$elseif _xtal = 8                                   ' | According to clock speed,
    $define cTimer1Config %00010000                 ' | set Timer1 pre-scaler to
$elseif _xtal = 16                                  ' | give 1 tick every 1 uS.
    $define cTimer1Config %00100000                 ' |
$elseif _xtal = 32                                  ' |
    $define cTimer1Config %00110000                 ' /
$else
    $define cTimer1Config %00000000
    $error "Servo code only works correctly with a clock of 4, 8, 16 or 32MHz"
$endif
'
' Aliases for Timer1 & CCP Module Registers
'
    Dim wServo_Timer1 As TMR1L.Word
    Dim wServo_CompareValue As CCPR1L.Word
    Dim wServo_FSR0 As FSR0L.Word

    Symbol tServo_Timer1On          = T1CONbits_TMR1ON
    Symbol tCompare_InterruptFlag   = PIR1bits_CCP1IF
    Symbol tCompare_InterruptEnable = PIE1bits_CCP1IE
    Symbol tCompare_UsingTimer3     = T3CONbits_T3CCP1
'
' Variables
'
    Dim wFSR0_Save As Word System                       ' Container for FSR0L\H within the interrupt
    Dim bServo_Flags As Byte System
    Dim tServo_InterruptComplete As bServo_Flags.0      ' Flag to indicate that the interrupt has finished
    Dim wServo_DelayTime As Word System                 ' Delay (in uS) between end of last servo
                                                        ' Pulse and start of first (set so servos are refreshed at 50Hz)
    Dim bServo_OnMask As Byte System                    ' OR'd with PortB to turn on current servo pin
    Dim bServo_Index As Byte System                     ' Holds index number of current servo
    Dim wServo_Position[Servo_NumberOfServos] As Word   ' Holds pulse length in uS for servos
'
' Create context saving variable if a low priority interrupt is used
'
$if Servo_Priority <> ipHigh
    Dim Wreg_Save As Byte System
    Dim Status_Save As Byte System
    Dim BSR_Save As Byte System
$endif

'----------------------------------------------------------------------------------
    GoTo _Servo_Main                                    ' Jump over the subroutines to the initialising code
'----------------------------------------------------------------------------------
' Interrupt triggered when Timer1 reaches CCPR1 register value (wServo_CompareValue).
' Input     : None
' Output    : tServo_InterruptComplete is true when compare interrupt has finished (must be reset in the main code)
' Notes:    : Puts servo pin high and then sets CCPR1 to desired pulse length for that servo.
'             Next time through interrupt, next servo pin is set high and CCPR1 is set to new pulse length.
'             Process repeats until all servo pins have been pulsed.
'             Then all pins off and CCPR1 set to time required to wait before starting again to give 50Hz refresh.
'
OnTimer_ISR:
$if Servo_Priority <> ipHigh                                ' Are we using a low priority interrupt?
    Status_Save = STATUS                                    ' \
    Wreg_Save = WREG                                        ' | Yes. So save the STATUS, WREG and BSR registers
    BSR_Save = BSR                                          ' /
$endif
    If tCompare_InterruptFlag = True Then                   ' Is it a CCP1 compare that has triggered the interrupt?
        wFSR0_Save = wServo_FSR0                            ' Yes. So save registers FSR0L\H
        LATB = PORTB & cOffMask                             ' Turn off all servo pins
        If bServo_Index >= Servo_NumberOfServos Then        ' Have all servo pulses been accomplished ?
            wServo_CompareValue = wServo_DelayTime          ' Time until next interrupt = time between cycles
            wServo_DelayTime = 20000                        ' \
            bServo_Index = 0                                ' | Reset all variables for next cycle
            bServo_OnMask = %00000001                       ' /
        Else                                                ' Otherwise. Not all servo pulses have been sent
            LATB = PORTB | bServo_OnMask                    ' Turn on the next servo pin
            wServo_CompareValue = wServo_Position[bServo_Index]         ' Time until next interrupt = pulse length of servo
            wServo_DelayTime = wServo_DelayTime - wServo_CompareValue   ' Update time between cycles to maintain 50Hz refresh
            Inc bServo_Index                                ' Ready for next servo
            bServo_OnMask = bServo_OnMask << 1              ' Move to the next bit of PortB
        EndIf
        tCompare_InterruptFlag = False                      ' Clear the compare interrupt flag
        tServo_InterruptComplete = True                     ' Set flag to let main program know interrupt has finished
        wServo_FSR0 = wFSR0_Save                            ' Restore registers FSR0L\H
    EndIf
'
' *** Other Interrupt routines can be placed here ***
'
$if Servo_Priority <> ipHigh                                ' Are we using a low priority interrupt?
    BSR = BSR_Save                                          ' \
    WREG = Wreg_Save                                        ' | Yes. So restore the STATUS, WREG And BSR registers and exit the interrupt
    STATUS = Status_Save                                    ' |
    Retfie                                                  ' /
$else                                                       ' Otherwise...
    Retfie Fast                                             ' Exit the interrupt, auto restoring the STATUS, WREG and BSR registers
$endif

'----------------------------------------------------------------------------------
' Start sending servo control pulses
' Input     : None
' Output    : None
' Notes     : Resets Timer1 and enables it, allowing it to trigger the Interrupt
'
Proc Servo_On()
    LATB = PORTB & cOffMask                 ' Turn off all servo pins
    wServo_DelayTime = 20000                ' \
    bServo_Index = 0                        ' | Set initial values for variables
    bServo_OnMask = %00000001               ' /
    wServo_CompareValue = wServo_DelayTime  ' Set time in uS before interrupt fires
    wServo_Timer1 = 0                       ' Reset Timer1
    tServo_Timer1On = True                  ' Start Timer1
EndProc

'----------------------------------------------------------------------------------
' Stop sending servo control pulses
' Input     : None
' Output    : None
' Notes     : Turns off Timer1, preventing Interrupt from firing.
'           : Turns off all servo pins
'
$define Servo_Off()         '
    tServo_Timer1On = False '
    LATB = PORTB & cOffMask

'----------------------------------------------------------------------------------
' Adjust the position value for Servo 1
' Input     : wServo_Position[0] holds the position value
' Output    : None
' Notes     : None
'
$define Servo1_Position(pPosition) '
$if (Servo_NumberOfServos >= 1)    '
    wServo_Position[0] = pPosition '
$endif

'----------------------------------------------------------------------------------
' Adjust the position value for Servo 2 (if available)
' Input     : wServo_Position[1] holds the position value
' Output    : None
' Notes     : None
'
$define Servo2_Position(pPosition) '
$if (Servo_NumberOfServos >= 2)    '
    wServo_Position[1] = pPosition '
$endif

'----------------------------------------------------------------------------------
' Adjust the position value for Servo 3 (if available)
' Input     : wServo_Position[2] holds the position value
' Output    : None
' Notes     : None
'
$define Servo3_Position(pPosition) '
$if (Servo_NumberOfServos >= 3)    '
    wServo_Position[2] = pPosition '
$endif

'----------------------------------------------------------------------------------
' Adjust the position value for Servo 4 (if available)
' Input     : wServo_Position[3] holds the position value
' Output    : None
' Notes     : None
'
$define Servo4_Position(pPosition) '
$if (Servo_NumberOfServos >= 4)    '
    wServo_Position[3] = pPosition '
$endif

'----------------------------------------------------------------------------------
' Adjust the position value for Servo 5 (if available)
' Input     : wServo_Position[4] holds the position value
' Output    : None
' Notes     : None
'
$define Servo5_Position(pPosition) '
$if (Servo_NumberOfServos >= 5)    '
    wServo_Position[4] = pPosition '
$endif

'----------------------------------------------------------------------------------
' Adjust the position value for Servo 6 (if available)
' Input     : wServo_Position[5] holds the position value
' Output    : None
' Notes     : None
'
$define Servo6_Position(pPosition) '
$if (Servo_NumberOfServos >= 6)    '
    wServo_Position[5] = pPosition '
$endif

'----------------------------------------------------------------------------------
' Adjust the position value for Servo 7 (if available)
' Input     : wServo_Position[6] holds the position value
' Output    : None
' Notes     : None
'
$define Servo7_Position(pPosition) '
$if (Servo_NumberOfServos >= 7)    '
    wServo_Position[6] = pPosition '
$endif

'----------------------------------------------------------------------------------
' Adjust the position value for Servo 8 (if available)
' Input     : wServo_Position[7] holds the position value
' Output    : None
' Notes     : None
'
$define Servo8_Position(pPosition) '
$if (Servo_NumberOfServos >= 8)    '
    wServo_Position[7] = pPosition '
$endif

'----------------------------------------------------------------------------------
' Code Initialisation
'
_Servo_Main:
    bServo_Index = Servo_NumberOfServos         ' \
    Repeat                                      ' |
        Dec bServo_Index                        ' | Set all servos to mid-point (pulse length = 1500uS)
        wServo_Position[bServo_Index] = 1500    ' |
    Until bServo_Index = 0                      ' /
    TRISB = TRISB & cOffMask                    ' Set used servo pins to outputs
'
' Initialise CCP and Timer1 peripherals:
'
    tCompare_UsingTimer3 = False                ' Compare peripheral uses Timer1
    T1CON = cTimer1Config                       ' Set pre-scaler, Timer1 off
    CCP1CON = %00001011                         ' Set special event trigger
                                                ' (Resets Timer1 and triggers interrupt when Timer1 value reaches CCPR1 value)
    tCompare_InterruptEnable = True             ' Enable interrupt on Timer1 = CCPR1
'
' Enable interrupts
'
$if Servo_Priority = ipHigh                     ' Are we using a high priority interrupt?
    IPR1bits_TMR2IP = 1                         ' Yes. So set compare peripheral to high priority
    RCONbits_IPEN = 0                           ' Disable priority levels on interrupts
$else                                           ' Otherwise...
    IPR1bits_TMR2IP = 0                         ' Set compare peripheral to low priority
    RCONbits_IPEN = 1                           ' Enable priority levels on interrupts
$endif
    INTCONbits_GIEL = 1                         ' Enable peripheral and priority interrupts
    INTCONbits_GIE = 1                          ' Enable global interrupts

$endif

Thank you tumbleweed for trying to help me..!