News:

PROTON pic BASIC Compilers for PIC, PIC24, dsPIC33

Main Menu

I want to change this code to positron

Started by Maxi, Oct 05, 2022, 10:30 AM

Previous topic - Next topic

Maxi

The picbasic gru Darrel Taylor`s code (Rip)
everybody know him.

here is darrel code, pic running 4mhz and pwm out 16hz
you can look this link, "slow speed pwm"
http://dt.picbasic.co.uk/CODEX/SSPWM

zip file link
http://dt.picbasic.co.uk/uploads/CODEX/SSPWM.zip

can we change this code to positron?
Just tested and it working good in picbasic



TestSSPWM.pbp
'This pretty much covers all the frequencies that the HPWM misses.  Unless you
'need less than 16hz, which is also possible, but I didn't think there would be
'a need for that low of freq.

'Here is a simple test program

'****************************************************************
'*  Name    : TestSSPWM.PBP                                     *
'*  Author  : Darrel Taylor                                     *
'*  Date    : 5/12/2003                                         *
'*  Version : 1.0                                               *
'****************************************************************
define LOADER_USED 1
define OSC 4

clear
' ---- SPWM  Slow Software Pulse Width Modulation --------------
SPWMpin       var PORTB.0         ' Output Pin for SSPWM
Include "SSPWM.INC"               ' Output Pin must be Defined before Include
file
                                  ' Include file must be after the Clear
statement

'8MHZ 16 TO 600
Freq = 16                         ' Set Frequency of SSPWM (word)
DutyCycle = 50                    ' Set Duty Cycle of SSPWM (byte) 0-100
gosub StartSPWM                   ' Start SSPWM @ Freq/DutyCycle

Loop1:
   pause 100
goto Loop1

'Freq = 30                         ' Set Frequency of SSPWM (word)
'DutyCycle = 50                    ' Set Duty Cycle of SSPWM (byte) 0-100
'gosub SetSPWM                     ' Change SSPWM @ Freq/DutyCycle

end
'****************************************************************


sspwm.inc
'****************************************************************
'*  Name    : SSPWM.INC          Slow Software PWM              *
'*  Author  : Darrel Taylor                                     *
'*  Date    : 5/1/2003                                          *
'*  Version : 1.0                                               *
'*  Notes   :                                                   *
'*          :                                                   *
'****************************************************************

DEFINE INTHAND INT_CODE                 ' Tell PBP Where the code starts on an interrupt

wsave       VAR BYTE    $20     SYSTEM          '$20 Save location for the W register if in bank0
wsave1      VAR BYTE    $A0     SYSTEM          ' Save location for the W register if in bank1
wsave2      VAR BYTE    $120    SYSTEM          ' Save location for the W register if in bank2
wsave3      VAR BYTE    $1A0    SYSTEM          ' Save location for the W register if in bank3
ssave       VAR BYTE    Bank0   SYSTEM          ' Save location for the STATUS register
psave       VAR BYTE    Bank0   SYSTEM          ' Save location for the PCLATH register

Freq                var word                    ' SPWM Frequency
W1                  var word                    ' Temporary variable
W2                  var word                    ' Temporary variable
TP                  var word                    ' Temporary variable
y                   var TP.lowbyte              ' Temporary variable shared
uS                  var word                    ' Time for 1 cycle in MicroSeconds
uSdec               var byte                    ' .1us digit
ActuS               var word                    ' Actual cycle time after integer math
ActuSdec            var byte                    ' Actual cycle time .1us digit
Ticks               var word                    ' # of Timer Ticks to = us
PicOSC              var byte Bank0              ' OSC value, Usable in PBP
Prescaler           var byte                    ' Timer1 Prescale value
DutyCycle           var byte   ' As %, 0 - 100   0 = Always Off   100 = Always On
TMR1_ON_TICKS       var word Bank0    ' # of Tmr ticks for On Time
TMR1_OFF_TICKS      var word Bank0    ' # of Tmr ticks for Off Time
TMR1_ON_VAL         var word Bank0    ' # to load TMR1 for On Time
TMR1_OFF_VAL        var word Bank0    ' # to load TMR1 for Off Time

DataFlags           var byte Bank0
Valid               var DataFlags.0   ' 1 if Freq is valid - Set by CalcSPWM:
SPWMenabled         var DataFlags.1   ' shows if SPWM is running or not
SPWMstate           var DataFlags.2   ' Current state of SPWM output high or low

GIE                 var INTCON.7
PEIE                var INTCON.6
TMR1IE              var PIE1.0
TMR1ON              var T1CON.0

goto GetOsc

' ------------------------------------------------------------------------
asm
INT_CODE
      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       ;6     ; save PCLATH reg to a bank 0 register
      endif
       
        btfss   PIR1, TMR1IF       ; is TMR1IF set?   Timer1 Interrupt Flag
        GOTO  NoTimerInt           ; No.  Bypass timer load
        btfss   _Valid             ; Is Freq valid?
        GOTO  NoSPWM               ; No.  Halt SPWM
        btfss   _SPWMenabled       ; is Software PWM enabled?
        GOTO  NoSPWM               ; No.  Halt SPWM
                                   ; Yes, then Set output and reload Timer1
        btfss   _SPWMstate         ; Is Output High?
        GOTO  TurnON      ;9/15    ; No.

TurnOFF
        bcf     _SPWMpin            ; Set SPWMpin Low
        bcf     _SPWMstate          ;
        BCF     T1CON,TMR1ON        ; Turn off timer
        MOVF    _TMR1_OFF_VAL,W     ;  1
        ADDWF   TMR1L,F             ;  1    ; reload timer with correct value
        BTFSC   STATUS,C            ;  1/2
        INCF    TMR1H,F             ;  1
        MOVF    _TMR1_OFF_VAL+1,W   ;  1
        ADDWF   TMR1H,F             ;  1
        BSF     T1CON,TMR1ON        ;  1    ; Turn it back on
        GOTO  TimerDone   ;12/27

TurnON 
        bsf     _SPWMpin            ; Set on SPWMpin High
        bsf     _SPWMstate          ;
        bcf     T1CON,TMR1ON        ; Turn off timer
        MOVF    _TMR1_ON_VAL,W      ;  1
        ADDWF   TMR1L,F             ;  1    ; reload timer with correct value
        BTFSC   STATUS,C            ;  1/2
        INCF    TMR1H,F             ;  1
        MOVF    _TMR1_ON_VAL+1,W    ;  1
        ADDWF   TMR1H,F             ;  1
        bsf     T1CON,TMR1ON        ;  1    ; Turn it back on
        GOTO  TimerDone
NoSPWM
        bcf     T1CON,TMR1ON        ; Turn off timer
        bcf     _SPWMpin            ; Idle SPWMpin Low
TimerDone       
        bcf     PIR1, TMR1IF ; 1/28         ; Clear Timer1 Interrupt Flag
NoTimerInt   
        Movf    psave,w             ; Restore the PCLATH reg
        Movwf   PCLATH
        swapf   ssave,w             ; Restore the STATUS reg
        movwf   STATUS
        swapf   wsave,f
        swapf   wsave,w    ; 6/34   ; Restore W reg
       
    Retfie                          ; Exit the interrupt routine

endasm
' ------------------------------------------------------------------------

StartSPWM:  ' Set Freq and DutyCycle before calling
    low SPWMpin     ' Set SPWMpin to Output and idle Low
    GIE = 1
    PEIE = 1
    TMR1H = 255    ' Load TMR1 with 65535, First tick will cause
    TMR1L = 255    ' an interrupt that will load TMR1_???_VAL

SetSPWM:   ' Set Freq and DutyCycle before calling
    if DutyCycle = 0 then StopSPWM
    if DutyCycle >= 100 then IdleHigh
    gosub CalcSPWM
    if Valid = 1 then
      SPWMenabled = 1
      lookdown Prescaler,[1,2,4,8],y
      lookup y,[0,1,2,3],y
      y = (y << 4) + 1
      TMR1_ON_VAL = 65535 - TMR1_ON_TICKS + 8
      TMR1_OFF_VAL = 65535 - TMR1_OFF_TICKS + 8
      TMR1IE = 1
      T1CON = y     ; Set Timer1 prescaler and turn Timer1 on
    else
      goto StopSPWM
    endif
return

StopSPWM
    TMR1IE = 0
    TMR1ON = 0
    low SPWMpin             ' Idle output Low
    SPWMstate = 0
    SPWMenabled = 0
return

IdleHigh:                   ' Idle output High
    gosub StopSPWM          ' First, stop the timer
    high  SPWMpin           ' Set output High
return

CalcSPWM:
    Prescaler = 1
    Valid = 1
    TMR1_ON_TICKS = 0
    TMR1_OFF_TICKS = 0

    W2 = 1000   
    W1 = W2 * W2           ' Load internal registers with 1,000,000
    uS = Div32 Freq        ' solves (1/Freq)*1000000  Full Cycle time in uS
    if uS = 65535 then
        Valid = 0
        goto CalcDone
    endif
    uSdec = 0
    if uS < 6550 then      ' get .1uS value
       W1 = 10000
       W1 = W1 * W2        ' 10,000,000
       W1 = Div32 Freq
       uSdec = W1 dig 0
    endif

TryPrescaler:
    if uS < 6550 then
       W1 = uS * 10 + uSdec
       TP = Prescaler * 100
    else
       W1 = uS
       TP = Prescaler * 10
    endif   
    if (PicOsc = 4) and (uSdec > 5) then W1 = W1 + 10
    W2 = PicOSC * 10 / 4
    Ticks = W1 * W2
    Ticks = div32 TP

    TP = TP * 100
    W1 = W1 * W2
    W1 = div32 TP
    if Ticks /100 <> W1 then
      Prescaler = Prescaler * 2
      if Prescaler > 8 then
        Valid = 0
        goto CalcDone
      endif
      goto TryPrescaler
    endif
   

    W1 = Ticks * DutyCycle          ' Calc # of Ticks for ON and OFF periods
    TMR1_ON_TICKS = div32 100
    TMR1_OFF_TICKS = Ticks - TMR1_ON_TICKS
  CalcDone:
return

GetOsc:                  ' Retreive defined OSC value on Reset
  asm
    ifdef OSC
       MOVE?CB   OSC, _PicOSC
    else
       MOVE?CB   4, _PicOSC
    endif
  endasm




top204

There is no need to convert the above code Maxi. The compiler has a similar demo program in its "Samples" folder: "C:\Users\User Name\PDS\Samples\New Samples\Slow_PWM_Interrupt_Driven.bas". It has been in there for quite a few years now, and was written for the Amicus18 board back in 2011. :-)

They both implement a software PWM waveform using an interrupt, but the compiler's demo is more suitable for newer devices and more easily altered for different devices, because the original code by Darrel was written back in 2003. Even Darrel's code will need changing for the timers used and the interrupt methodology on different standard 14-bit core devices, because microchip cannot leave things alone and keep changing how peripherals work, even when they have the same functionality as previous devices on the same family of devices. :-( Also, the code listing above will not work on 18F devices or enhanced 14-bit core devices at all, because they differ so much from the, long outdated, standard 14-bit core devices, and a lot of the code is written in assembler and aimed purely at the devices of the time. i.e. Standard 14-bit core types such as the PIC16F877.

I have just tweaked the original Positron demo code that is installed with the compilers and it is listed below:
'
'   /\\\\\\\\\
'  /\\\///////\\\
'  \/\\\     \/\\\                                                 /\\\          /\\\
'   \/\\\\\\\\\\\/        /\\\\\     /\\\\\\\\\\     /\\\\\\\\   /\\\\\\\\\\\  /\\\\\\\\\\\  /\\\\\\\\\
'    \/\\\//////\\\      /\\\///\\\  \/\\\//////    /\\\/////\\\ \////\\\////  \////\\\////  \////////\\\
'     \/\\\    \//\\\    /\\\  \//\\\ \/\\\\\\\\\\  /\\\\\\\\\\\     \/\\\         \/\\\        /\\\\\\\\\\
'      \/\\\     \//\\\  \//\\\  /\\\  \////////\\\ \//\\///////      \/\\\ /\\     \/\\\ /\\   /\\\/////\\\
'       \/\\\      \//\\\  \///\\\\\/    /\\\\\\\\\\  \//\\\\\\\\\\    \//\\\\\      \//\\\\\   \//\\\\\\\\/\\
'        \///        \///     \/////     \//////////    \//////////      \/////        \/////     \////////\//
'                                  Let's find out together what makes a PIC Tick!
'
' Within an interrupt, create a simple software PWM routine with variable frequency and duty cycle
' The 8-bit relative frequency of the PWM can be altered by changing the value held in PWM_bRelFrequency
' The 8-bit duty cycle of the PWM can be altered by changing the value held in PWM_bDutyCycle
' The duty cycle is not duly effected by relative frequency
'
' Uses a Compare Interrupt using the Special Event mechanism
' Compares the 16-bit value of Timer3 with the contents of 16-bit registers CCPR2L\H
' Triggers the interrupt when Timer3 reaches the value held in CCPR2L\H
' Timer3 is automatically reset in hardware
' The rate of the interrupt can be altered by changing the constant value held in cMicroSeconds
'
' Written by Les Johnson for the Positron8 BASIC compiler.
' https://sites.google.com/view/rosetta-tech/home
'
    Device = 18F25K20                                   ' Tell the compiler what device to compile for
    Declare Xtal = 64                                   ' Tell the compiler what frequency the device is operating at (in MHz)
    On_Hardware_Interrupt GoTo ISR_Handler              ' Point the interrupt to the handler routine

    Symbol PWM_Pin = PORTB.0                            ' The designated pin for PWM output
'
' Timer3 configuration masks to be 'anded' together for the Timer3_Open procedure
'
$define T3_INT_OFF      0b01111111                      ' Interrupts disabled
$define T3_INT_ON       0b11111111                      ' Interrupts enabled

$define T3_8BIT_RW      0b11111110                      ' 8-bit mode
$define T3_16BIT_RW     0b11111111                      ' 16-bit mode

$define T3_PS_1_1       0b11001111                      ' 1:1 prescale value
$define T3_PS_1_2       0b11011111                      ' 1:2 prescale value
$define T3_PS_1_4       0b11101111                      ' 1:4 prescale value
$define T3_PS_1_8       0b11111111                      ' 1:8 prescale value

$define T3_SYNC_EXT_ON  0b11111011                      ' Synchronise external clock input
$define T3_SYNC_EXT_OFF 0b11111111                      ' Do not synchronise external clock input

$define T3_SOURCE_INT   0b11111101                      ' Internal clock source
$define T3_SOURCE_EXT   0b11111111                      ' External clock source

$define T3_SOURCE_CCP   0b11111111                      ' T3 is source for CCP
$define T1_CCP1_T3_CCP2 0b10111111                      ' T1 is source for CCP1 and T3 is source for CCP2
$define T1_SOURCE_CCP   0b10110111                      ' T1 is source for CCP
'
' Create some variables
'
    Dim PWM_bFreqAccum As Byte Access                   ' Frequency accumulator for the interrupt handler
    Dim PWM_bDutyAccum As Byte Access                   ' Duty Cycle accumulator for the interrupt handler

    Dim PWM_bDutyCycle As Byte Access                   ' PWM Duty Cycle variable
    Dim PWM_bRelFrequency As Byte Access                ' PWM relative frequency variable

    Dim wCCPR2 As CCPR2L.Word                           ' Combine CCPR2L\H into a 16-bit register

'--------------------------------------------------------------------------------------------------
' The main program starts here
'
Main:
    PWM_Init()                                          ' Initialise the software PWM and its interrupt
'
' Create a loop to alter the relative frequency of the PWM signal
' The higher the value of PWM_bRelFrequency, the lower the relative frequency
'
    PWM_bDutyCycle = 127                                ' 50% duty cycle

    For PWM_bRelFrequency = 0 To 255                    ' Decrease the frequency
        DelayMS 100                                     ' Create a delay slower than the rate of change
    Next
'
' Create a loop to alter the duty cycle of the PWM signal
' The higher the value of PWM_bDutyCycle, the higher the duty cycle
'
    PWM_bRelFrequency = 10                              ' Choose a relative frequency

    Do                                                  ' Create an infinite loop
        For PWM_bDutyCycle = 0 To 255                   ' Increase the duty cycle
            DelayMS 100                                 ' Create a delay slower than the rate of change
        Next
    Loop                                                ' Do it forever

'--------------------------------------------------------------------------------------------------
' Initialise the CCP2 Special Event interrupt and the PWM variables
' Input     : None
' Output    : None
' Notes     : None
'
Proc PWM_Init()
    PWM_bFreqAccum = 1                                  ' Reset the ISR relative frequency accumulator
    PWM_bDutyAccum = 0                                  ' Reset the ISR duty cycle accumulator
    PWM_bDutyCycle = 0                                  ' Reset the duty cycle
    PWM_bRelFrequency = 0                               ' Reset the relative frequency
    PinLow PWM_Pin                                      ' Make the pin output low

    CCP2CON = %00001011                                 ' Compare mode: trigger special event, reset timer, start A/D conversion on CCP2 match (CCP2IF bit is set)

    Timer3_Open(T3_INT_OFF & T3_16BIT_RW & T3_PS_1_8 & T3_SYNC_EXT_OFF & T3_SOURCE_INT & T3_SOURCE_CCP)
    $define cPrescalerValue 8                           ' Alter this to match the prescaler parameter above. i.e. 4 for T3_PS_1_4, 8 for T3_PS_1_8
    $define cMicroSeconds 50                            ' Interrupt rate (in uS)
'
' Calculate the value to place into the CCPRx register in order to achieve a certain interrupt rate (in us)
'
    $define cCCPR_Value $eval (cMicroSeconds / cPrescalerValue) * (_xtal / 4)

$if cCCPR_Value > 65535
    $error "Value too large for interrupt duration"
$elseif cCCPR_Value = 0
    $error "Value too small for interrupt duration"
$endif

    wCCPR2 = cCCPR_Value                                ' Load CCPR2L\H with the value to trigger an interrupt at a certain duration
    PIE2bits_CCP2IE = 1                                 ' Enable the Special Event Interrupt on CCP2
    INTCONbits_PEIE = 1                                 ' Enable Peripheral Interrupts
    INTCONbits_GIE = 1                                  ' Enable Global Interrupts
EndProc

'---------------------------------------------------------------------------------
' Configure Timer3
' Input         : pConfig holds the bit definitions to configure Timer3
' Output        : None
' Notes         : This routine first resets the Timer3 regs to the POR state and then configures the interrupt, clock source.
'               : The bit definitions for pConfig can be found at the top of this code listing
'
Proc Timer3_Open(pConfig As Byte)
    T3CON = pConfig & 0b01111110                        ' Clear and set the bits required
    TMR3H = 0                                           ' \ Clear the Timer3 registers
    TMR3L = 0                                           ' /
    PIR2bits_TMR3IF = 0                                 ' Clear the interrupt flag
    PIE2bits_TMR3IE = pConfig.7                         ' Enable/Disable Timer3 interrupt
    T1CONbits_T1OSCEN = pConfig.1                       ' Enable/Disable Timer1 oscillator
    T3CONbits_T3RD16 = ~pConfig.0                       ' Select between 8-bit and 16-bit modes
    T3CONbits_TMR3ON = 1                                ' Turn on Timer3
EndProc

'--------------------------------------------------------------------------------------------------
' Interrupt Handler
' Input     : PWM_bDutyCycle holds the duty cycle of the PWM waveform (0 to 255)
'           : PWM_bRelFrequency holds the relative frequency of the PWM waveform
' Output    : None
' Notes     : Creates a very slow PWM signal with variable frequency and duty capabilities
'
ISR_Handler:
    Context Save

    If PIR2bits_CCP2IF = 1 Then                         ' Was it a Compare Special Event on CCP2 that triggered the interrupt?
        Inc PWM_bFreqAccum                              ' Yes. So increase the relative frequency accumulator
        If PWM_bFreqAccum = PWM_bRelFrequency Then      ' Has the relative frequency reached the desired value?
            PWM_bFreqAccum = 0                          ' Yes. So reset the relative frequency accumulator
            Inc PWM_bDutyAccum                          ' Increment the PWM duty cycle accumulator
            If PWM_bDutyAccum >= PWM_bDutyCycle Then    ' Has the duty cycle accumulator reached the required duty cycle?
                PinClear PWM_Pin                        ' Yes. So make the pin low
            Else                                        ' Otherwise...
                PinSet PWM_Pin                          ' Make the pin high
            EndIf
        EndIf
        PIR2bits_CCP2IF = 0                             ' Clear the interrupt flag
    EndIf
'
' << More Interrupt Conditions and Code Here >>
'
    Context Restore                                     ' Exit the interrupt

'-------------------------------------------------------------
' Setup the config fuses for 4x PLL with an external crystal on a PIC18F25K20 device
'
Config_Start
    FOSC = HSPLL        ' HS oscillator, PLL enabled and under software control
    HFOFST = Off        ' The system clock is held Off until the HF-INTOSC is stable
    FCMEN = Off         ' Fail-Safe Clock Monitor disabled
    IESO = Off          ' Two-Speed Start-up disabled
    WDTPS = 128         ' Watchdog is 1:128
    BOREN = Off         ' Brown-out Reset disabled in hardware and software
    BORV = 18           ' VBOR set to 1.8 V nominal
    MCLRE = On          ' MCLR pin enabled, RE3 input pin disabled
    LPT1OSC = Off       ' T1 operates in standard power mode
    PBADEN = Off        ' PORTB<4:0> pins are configured as digital I/O on Reset
    CCP2MX = PORTC      ' CCP2 input/output is multiplexed with RC1
    STVREN = Off        ' Reset on stack overflow/underflow disabled
    WDTEN = Off         ' WDT disabled (control is placed on SWDTEN bit)
    Debug = Off         ' Background debugger disabled' RB6 and RB7 configured as general purpose I/O pins
    XINST = Off         ' Instruction set extension and Indexed Addressing mode disabled (Legacy mode)
    LVP = Off           ' Single-Supply ICSP disabled
    Cp0 = Off           ' Block 0 (000800-001FFF) not code-protected
    CP1 = Off           ' Block 1 (002000-003FFF) not code-protected
    CPB = Off           ' Boot block (000000-0007FF) not code-protected
    CPD = Off           ' Data EEPROM not code-protected
    WRT0 = Off          ' Block 0 (000800-001FFF) not write-protected
    WRT1 = Off          ' Block 1 (002000-003FFF) not write-protected
    WRTB = Off          ' Boot block (000000-0007FF) not write-protected
    WRTC = Off          ' Configuration registers (300000-3000FF) not write-protected
    WRTD = Off          ' Data EEPROM not write-protected
    EBTR0 = Off         ' Block 0 (000800-001FFF) not protected from table reads executed in other blocks
    EBTR1 = Off         ' Block 1 (002000-003FFF) not protected from table reads executed in other blocks
    EBTRB = Off         ' Boot block (000000-0007FF) not protected from table reads executed in other blocks
Config_End  

To use it on different devices, change the SFRs and their bits used for Timer3 and CCP2 within their procedures. Or change to a different Timer that will create a Special Event interrupt with CCP1 or CCP2, or a TimerX overflow interrupt if the CCP peripherals are already in use. Any timer overflow interrupt will work for the software PWM waveform generator, as long as it is of a fixed time period.

Maxi

#2
hi les, I know your code
I want use cheap pics, like 12F1822, 12F1840, 16F1847 etc
18F25xx 18F26xx pics extreme expensive now (after the pandemic)

also your code not work like darrel`s
darrels code write 16, out 16hz
write 312 out is 312

yours relative, not same input to out pwm freq
also I need low osc like 4mhz or 8mhz (need to read low frequency input from ccp1 port)
yes I know, I wanting a lot ;D

*Do not me understand wrong, my english not perfect