DDS (generating sine waves) with onboard DAC using latest PIC 16F chips?


Closed Thread
Results 1 to 40 of 77

Hybrid View

  1. #1
    Join Date
    Aug 2010
    Location
    Maryland, USA
    Posts
    869


    Did you find this post helpful? Yes | No

    Default Re: DDS (generating sine waves) with onboard DAC using latest PIC 16F chips?

    Ok, so I am now up to speed with you who is up to speed with me. We can now plod along blindly together - LOL. I was thinking of doing this all with software so as not to be dependent on HPWM. Chasing the single low cost PIC for 1 purpose, I was assuming HPWM may not be available.

    Quick question, what is the fastest time needed? ie, 5,000hz has a time of .2mS, but 5,000.01 has a time of .199999mS. so you want .1uS, .01uS,1uS,bla bla bla. on the other hand 100hz is 10mS while 100.01Hz is 9.9999mS.

    As you can see, I am having conceptual trouble here with the .01Hz spec.
    -Bert

    The glass is not half full or half empty, Its twice as big as needed for the job!

    http://foamcasualty.com/ - Warbird R/C scratch building with foam!

  2. #2
    Join Date
    Mar 2009
    Posts
    653


    Did you find this post helpful? Yes | No

    Default Re: DDS (generating sine waves) with onboard DAC using latest PIC 16F chips?

    Quote Originally Posted by cncmachineguy View Post
    Ok, so I am now up to speed with you who is up to speed with me. We can now plod along blindly together - LOL. I was thinking of doing this all with software so as not to be dependent on HPWM. Chasing the single low cost PIC for 1 purpose, I was assuming HPWM may not be available.

    Quick question, what is the fastest time needed? ie, 5,000hz has a time of .2mS, but 5,000.01 has a time of .199999mS. so you want .1uS, .01uS,1uS,bla bla bla. on the other hand 100hz is 10mS while 100.01Hz is 9.9999mS.

    As you can see, I am having conceptual trouble here with the .01Hz spec.
    Maybe I'm too ambitious with the .01Hz accuracy, maybe .1hz is more achievable (initially)....as it goes, I actually only need that accuracy at the lower end of the 60hz-5,000Hz frequency range (where obviously 0.1Hz error of say 60hz is a whole lot more in percentage terms than .1Hz for 5khz) but with DDS you have to decide on the acceptable resolution then be stuck with it across the frequency band. so yes, say 50.01Hz, 50.02Hz, 50.3Hz thru 5,000Hz is what I hope to achieve here.

    I've read that DDS 'interrupt rate' should be at least twice the targetted/required highest freqency, which since I want 5Khz, should mean a minimum interrupt of 10khz...but I thought 20Khz might be better. So with a 16 bit accumulator, we get....

    audio ouput frequency granularity = 20,000/65536 or 0.31hz (which is not enough) ...even dropping the interrupt rate to 10khz means granularity of 0.15Hz)

    That said, for proof of concept, maybe I just go with that initially ....ie 10,000 interrupts per second and a simple 16 bit accumulator - once that's been proven, then we can stride out a bit!
    Last edited by HankMcSpank; - 27th August 2011 at 00:30.

  3. #3
    Join Date
    Aug 2010
    Location
    Maryland, USA
    Posts
    869


    Did you find this post helpful? Yes | No

    Default Re: DDS (generating sine waves) with onboard DAC using latest PIC 16F chips?

    hank, your PM is full
    -Bert

    The glass is not half full or half empty, Its twice as big as needed for the job!

    http://foamcasualty.com/ - Warbird R/C scratch building with foam!

  4. #4
    Join Date
    Mar 2009
    Posts
    653


    Did you find this post helpful? Yes | No

    Default Re: DDS (generating sine waves) with onboard DAC using latest PIC 16F chips?

    HenrikOlsson, kindly offered up this code he put together as a solution how to get an accumulator large than 16 bit (see this thread http://www.picbasic.co.uk/forum/show...943#post106943 ) ...

    Code:
    LSW  VAR WORD              ' Least significat word of accumulator
    MSW  VAR WORD              ' Most significatn word of accumulator
     
    ADDL VAR WORD              ' Least significant work of value to add
    ADDH VAR WORD              ' Most significant word of value to add 
     
    Out VAR BYTE                    ' This is the actual output from the lookup table
     
    Temp VAR WORD
     
    OverFlow VAR BIT             ' Gets set when 32bit accumulator overflows.
     
    i VAR WORD
     
    Init:
      LSW = 0 
      MSW = 0
      AddL = 500
      AddH = 2000   ' 50*256+500=768500
     
    Pause 3000
     
    Main:
    For i = 1 to 1000
      OverFlow = 0
      TMR1H = 0
      TMR1L = 0
     
      Gosub Add
      Gosub GetValue
     
      HSEROUT["Count: ", DEC4 i, "  MSW: ", DEC5 MSW, "   LSW: ", DEC5 LSW, "   Overflow: ", BIN Overflow, "  Out: ", DEC Out, "  Ticks: ", DEC5 TMR1H*256+TMR1L, 13]
      Pause 5
    NEXT
     
    END
     
    Add:
      T1CON = 1             ' This is just used to measure the execution time
     
      Temp = LSW            ' Remember least significant word
      LSW = LSW + ADDL      ' Add low word 
     
      If LSW < Temp Then ' Did we wrap around/overflow?
        MSW = MSW + 1       ' Increment high word
        If MSW = 0 Then OverFlow = 1  ' Did we overflow high word?
      ENDIF
     
      Temp = MSW            ' Remember high word
      MSW = MSW + ADDH      ' Add high word 
     
      If MSW < Temp Then ' Did we wrap around/overflow?
        OverFlow = 1     ' Set flag
      ENDIF
     
    T1CON = 0
    RETURN
     
    GetValue:
    Lookup MSW.HighBYTE, [$80,$83,$86,$89,$8C,$8F,$92,$95,$98,$9C,$9F,$A2,$A5,$A8,$AB,$AE,$B0,$B3,$B6,$B9,$BC,$BF,$C1,$C4,_
    $C7,$C9,$CC,$CE,$D1,$D3,$D5,$D8,$DA,$DC,$DE,$E0,$E2,$E4,$E6,$E8,$EA,$EC,$ED,$EF,$F0,$F2,$F3,$F5,$F6,$F7,$F8,$F9,$FA,$FB,$FC,$FC, _
    $FD,$FE,$FE,$FF,$FF,$FF,$FF,$FF,$FF,$FF,$FF,$FF,$FF,$FF,$FE,$FE,$FD,$FC,$FC,$FB,$FA,$F9,$F8,$F7,$F6,$F5,$F3,$F2,$F0,$EF,$ED,$EC, _
    $EA,$E8,$E6,$E4,$E2,$E0,$DE,$DC,$DA,$D8,$D5,$D3,$D1,$CE,$CC,$C9,$C7,$C4,$C1,$BF,$BC,$B9,$B6,$B3,$B0,$AE,$AB,$A8,$A5,$A2,$9F,$9C, _
    $98,$95,$92,$8F,$8C,$89,$86,$83,$7F,$7C,$79,$76,$73,$70,$6D,$6A,$67,$63,$60,$5D,$5A,$57,$54,$51,$4F,$4C,$49,$46,$43,$40,$3E,$3B, _
    $38,$36,$33,$31,$2E,$2C,$2A,$27,$25,$23,$21,$1F,$1D,$1B,$19,$17,$15,$13,$12,$10,$0F,$0D,$0C,$0A,$09,$08,$07,$06,$05,$04,$03,$03, _
    $02,$01,$01,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$01,$01,$02,$03,$03,$04,$05,$06,$07,$08,$09,$0A,$0C,$0D,$0F,$10,$12,$13, _
    $15,$17,$19,$1B,$1D,$1F,$21,$23,$25,$27,$2A,$2C,$2E,$31,$33,$36,$38,$3B,$3E,$40,$43,$46,$49,$4C,$4F,$51,$54,$57,$5A,$5D,$60,$63, _
    $67,$6A,$6D,$70,$73,$76,$79,$7C],Out
    RETURN
    Not sure I'll get time over this weekend, but intend trying it soon.

    If it works (& I've no doubt it will!), then that just leaves on issue-ette - how to get a PIC to convert the required frequency (say arriving in from a serial port from a human or other pic), into the 'tuning word'.

    required frequency/interrupt rate * accumulator size

    so for a required frequency of 4971.21Hz involving a 32 bit accumulator & and say an interupt rate of 20,000Hz

    (4971.21/20000) * 4294967296

    the first part of the equation results in a decimal & then multiplying the decimal by a 32 bit number....woah! (can this even be done?!)
    Last edited by HankMcSpank; - 27th August 2011 at 11:53.

  5. #5
    Join Date
    Oct 2005
    Location
    Sweden
    Posts
    3,612


    Did you find this post helpful? Yes | No

    Default Re: DDS (generating sine waves) with onboard DAC using latest PIC 16F chips?

    Hi Hank,
    Starting with your last question in the other thread. Yes, that's basically the code that would go into your ISR. But you can remove the TMR1 stuff and the whole overflow flag business, that was just a debug aid.

    Here's it is repackaged:
    Code:
    Add:
        Lookup MSW.HighBYTE, [$80,$83,$86,$89,$8C,$8F,$92,$95,$98,$9C,$9F,$A2,$A5,$A8,$AB,$AE,$B0,$B3,$B6,$B9,$BC,$BF,$C1,$C4,_
        $C7,$C9,$CC,$CE,$D1,$D3,$D5,$D8,$DA,$DC,$DE,$E0,$E2,$E4,$E6,$E8,$EA,$EC,$ED,$EF,$F0,$F2,$F3,$F5,$F6,$F7,$F8,$F9,$FA,$FB,$FC,$FC, _
        $FD,$FE,$FE,$FF,$FF,$FF,$FF,$FF,$FF,$FF,$FF,$FF,$FF,$FF,$FE,$FE,$FD,$FC,$FC,$FB,$FA,$F9,$F8,$F7,$F6,$F5,$F3,$F2,$F0,$EF,$ED,$EC, _
        $EA,$E8,$E6,$E4,$E2,$E0,$DE,$DC,$DA,$D8,$D5,$D3,$D1,$CE,$CC,$C9,$C7,$C4,$C1,$BF,$BC,$B9,$B6,$B3,$B0,$AE,$AB,$A8,$A5,$A2,$9F,$9C, _
        $98,$95,$92,$8F,$8C,$89,$86,$83,$7F,$7C,$79,$76,$73,$70,$6D,$6A,$67,$63,$60,$5D,$5A,$57,$54,$51,$4F,$4C,$49,$46,$43,$40,$3E,$3B, _
        $38,$36,$33,$31,$2E,$2C,$2A,$27,$25,$23,$21,$1F,$1D,$1B,$19,$17,$15,$13,$12,$10,$0F,$0D,$0C,$0A,$09,$08,$07,$06,$05,$04,$03,$03, _
        $02,$01,$01,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$01,$01,$02,$03,$03,$04,$05,$06,$07,$08,$09,$0A,$0C,$0D,$0F,$10,$12,$13, _
        $15,$17,$19,$1B,$1D,$1F,$21,$23,$25,$27,$2A,$2C,$2E,$31,$33,$36,$38,$3B,$3E,$40,$43,$46,$49,$4C,$4F,$51,$54,$57,$5A,$5D,$60,$63, _
        $67,$6A,$6D,$70,$73,$76,$79,$7C],Out
     
    ' Here you should move the value to where it should be, DAC, PWM, R2R now.
     
        Temp = LSW            ' Remember least significant word
        LSW = LSW + ADDL      ' Add low word 
     
        If LSW < Temp Then    ' Did we wrap around/overflow?
            MSW = MSW + 1     ' Increment high word
        ENDIF
     
        Temp = MSW            ' Remember high word
        MSW = MSW + ADDH      ' Add high word 
    RETURN
    This thing, including the lookup table runs in about 75 cycles which I think is pretty good. It's not near the 35 cycles quoted in the doc you linked to but I think it's plenty for your needs.


    I played around a bit and I'm not sure this is going to work for you (due to the high resoultion of 2 decimal places you need) but it might be worth a try.
    Your formula: 4971.21 / 20000 * 2^32 = 1067559218 can be reorganised so it reads 4971.21 * (2^32/20000) or 4971.21 * 214748.36.

    Since your maximum frequency is 5000Hz we can multiply that side of the equation by 10 and still have it fit in a WORD, when we do that we can divide the other side of the equation by 10 which makes IT TOO fit in a WORD so now we have 49712 * 21475 = 1067565200 which obviosuly won't fit.....

    I then tried to extract the 32bit intermediate result of that 16 by 16 bit multiplication and it seems like it might work. If I'm not mistaken the high word is stored in system variable R0 and the low word in R2 so if we could extract those immediately after doing the multiplication we're pretty much good to go:

    Code:
    Frequency VAR WORD
    Temp VAR WORD
     
    Frequency = 49712   ' 4971.2Hz
    Temp = Frequency * 21475    ' Produce the 32bit intermediate result
    AddH = R0                           ' Get high word from R0
    AddL = R2                           ' and low word from R2
    Gosub PrintIt                       ' Display it
     
    Pause 100
    END
     
    PrintIt:
      HSEROUT["Frequency: ", DEC Frequency/10, ".", DEC Frequency//10, "   AddValue: ", DEC AddH, " , ", DEC AddL,13] 
    RETURN
    The above shows AddH as 15699 and AddL as 60536. That's 15699 * 65536 + 60536 = 1028910200 when it "should" be 1028902365, not perfect but close.


    Play with it, see if it works. If not you might want to look into Darrels N-Bit math routines, they should be pretty straight forward for this I think.

    /Henrik.
    Last edited by HenrikOlsson; - 27th August 2011 at 13:46.

  6. #6
    Join Date
    Mar 2009
    Posts
    653


    Did you find this post helpful? Yes | No

    Default Re: DDS (generating sine waves) with onboard DAC using latest PIC 16F chips?

    Thanks once again Henrik...I definitely *will* use what you've done here (though if I'm blunt, there's some digesting to do!), but for the first run, I'm scaling everything back (just to get all my HPWM config/timers/program sorted before bringing in the larger number!) ...ie 16 bit accumulator for the first run!

  7. #7
    Join Date
    Nov 2003
    Location
    Greece
    Posts
    4,139


    Did you find this post helpful? Yes | No

    Default Re: DDS (generating sine waves) with onboard DAC using latest PIC 16F chips?

    Quote Originally Posted by HenrikOlsson View Post
    Code:
    Frequency VAR WORD
    Temp VAR WORD
    
    Frequency = 49712 ' 4971.2Hz
    Temp = Frequency * 21475 ' Produce the 32bit intermediate result
    AddH = R0 ' Get high word from R0
    AddL = R2 ' and low word from R2
    Gosub PrintIt ' Display it
    
    Pause 100
    END
    
    PrintIt:
    HSEROUT["Frequency: ", DEC Frequency/10, ".", DEC Frequency//10, " AddValue: ", DEC AddH, " , ", DEC AddL,13] 
    RETURN
    If there are interrups involved, maybe it is a good idea to disable just before the routine, so R0 and R2 are not messed up.

    Ioannis

  8. #8
    Join Date
    Mar 2009
    Posts
    653


    Did you find this post helpful? Yes | No

    Default Re: DDS (generating sine waves) with onboard DAC using latest PIC 16F chips?

    Quote Originally Posted by Ioannis View Post
    If there are interrups involved, maybe it is a good idea to disable just before the routine, so R0 and R2 are not messed up.

    Ioannis
    From my limited understanding...the whole premise of generating waveforms via DDS is to get in & get out the interrupt routine as fast as possible before the next interrupt arrives (else it all fails badly)...in such an instance, I'd say it'd be better to keep the timer interrupt running all the time (since they're be overhead, however small wrt stopping the interrupts)

    ok, I slapped the most basic (1 pole) filter with a corner frequency set at about 10khz on the HPWM pin, here's 500Hz...



    a bit of noise (could probably do with another filter pole).

    Need to have a bit more play

    Code to date...
    Code:
    @ __CONFIG _CONFIG1, _FCMEN_OFF & _FOSC_INTOSC & _WDTE_OFF & _MCLRE_OFF & _CP_OFF & _IESO_OFF & _BOREN_OFF & _PWRTE_OFF & _LVP_OFF
    @ __CONFIG _CONFIG2, _LVP_OFF
    INCLUDE "DT_INTS-14.bas" ' Base Interrupt System
    Osccon = %01111010   'sets the internal oscillator to 16Mhz
    DEFINE  OSC 16
    TrisC.5 = 0     'Pin2 (HPWM) an output     
    CM1CON0 = 0   ' COMPARATORS OFF
    CM2CON0 = 0   ' COMPARATORS OFF
    tuning_word         VAR word
    accumulator         VAR WORD
    out                 VAR BYTE
    'HPWM SETTINGS uses timer 2
    CCP1CON  = %00001100     'Turn HPWM on on CCP1
    CCPR1L.6 = 0             'only using 8 bit PWM so clear the top two bits 
    CCPR1L.7 = 0             'only using 8 bit PWM so clear the top two bits
    PR2 = 79                'this PWM frequency of  50khzKHz allows a maximum of 320 values
    T2CON = %00000100        'TIMER2 ON 1:1 PRESCALER 1:1 POSTSCALER
     
    ' setsup an interrupt based on Timer4 overflowing (timer4 will overflow at 20,000 times per second, see further)
    ASM
    INT_LIST  macro ; IntSource,    Label,         Type, ResetFlag?
        INT_Handler  TMR4_INT,  _DDS,  asm,  YES
        endm
        INT_CREATE       ; Creates the interrupt processor
    ENDASM
    T4CON.2 = 1     ' Timer4 on
    PR4 =  199      ' this should yield an exact 'interrupt rate of 20khz' at 16Mhz.
    ACCUMULATOR = 0          ' clear down the accumulator before starting.
    @ INT_ENABLE TMR4_INT
    TUNING_WORD = 1638 ' this sets the required output frequency (tuning_word value = req_freq/20,000 * 65536)  1638 = 500hz
    'CCP1CON.4 = Test.0       'Bit 0
    'CCP1CON.5 = Test.1       'Bit 1
    'CCPR1L    = Test >> 2    'Bit 2-7
    Main:
        pause 1
        goto main
    END
    '+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
    DDS:
    'toggle PortA.5
    ACCUMULATOR = ACCUMULATOR + tuning_word
    ' ok, lookup the high byte of the accumulator....
    Lookup Accumulator.HighBYTE, [$80,$83,$86,$89,$8C,$8F,$92,$95,$98,$9C,$9F,$A2,$A5,$A8,$AB,$AE,$B0,$B3,$B6,$B9,$BC,$BF,$C1,$C4,_
    $C7,$C9,$CC,$CE,$D1,$D3,$D5,$D8,$DA,$DC,$DE,$E0,$E2,$E4,$E6,$E8,$EA,$EC,$ED,$EF,$F0,$F2,$F3,$F5,$F6,$F7,$F8,$F9,$FA,$FB,$FC,$FC, _
    $FD,$FE,$FE,$FF,$FF,$FF,$FF,$FF,$FF,$FF,$FF,$FF,$FF,$FF,$FE,$FE,$FD,$FC,$FC,$FB,$FA,$F9,$F8,$F7,$F6,$F5,$F3,$F2,$F0,$EF,$ED,$EC, _
    $EA,$E8,$E6,$E4,$E2,$E0,$DE,$DC,$DA,$D8,$D5,$D3,$D1,$CE,$CC,$C9,$C7,$C4,$C1,$BF,$BC,$B9,$B6,$B3,$B0,$AE,$AB,$A8,$A5,$A2,$9F,$9C, _
    $98,$95,$92,$8F,$8C,$89,$86,$83,$7F,$7C,$79,$76,$73,$70,$6D,$6A,$67,$63,$60,$5D,$5A,$57,$54,$51,$4F,$4C,$49,$46,$43,$40,$3E,$3B, _
    $38,$36,$33,$31,$2E,$2C,$2A,$27,$25,$23,$21,$1F,$1D,$1B,$19,$17,$15,$13,$12,$10,$0F,$0D,$0C,$0A,$09,$08,$07,$06,$05,$04,$03,$03, _
    $02,$01,$01,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$00,$01,$01,$02,$03,$03,$04,$05,$06,$07,$08,$09,$0A,$0C,$0D,$0F,$10,$12,$13, _
    $15,$17,$19,$1B,$1D,$1F,$21,$23,$25,$27,$2A,$2C,$2E,$31,$33,$36,$38,$3B,$3E,$40,$43,$46,$49,$4C,$4F,$51,$54,$57,$5A,$5D,$60,$63, _
    $67,$6A,$6D,$70,$73,$76,$79,$7C],Out
    ' now use that 'Out' value to change HPWM. duty cycle...
    CCP1CON.4 = Out.0       'Bit 0
    CCP1CON.5 = Out.1       'Bit 1
    CCPR1L    = Out >> 2    'Bit 2-7
    @ INT_RETURN
    Last edited by HankMcSpank; - 27th August 2011 at 15:03.

Members who have read this thread : 1

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