12 bit A2D on 18F46K80, need a bit of help for figuring TAD and getting correct value


Closed Thread
Results 1 to 18 of 18

Hybrid View

  1. #1
    Join Date
    Sep 2007
    Location
    Waco, Texas
    Posts
    151


    Did you find this post helpful? Yes | No

    Default Re: 12 bit A2D on 18F46K80, need a bit of help for figuring TAD and getting correct v

    Thanks Mark-
    Yup, you found the stupid mistake, been looking at it too long.
    Listed below and for all to see is what is working.
    However, I can't seem to figure out how to normalize the A2D result which is accurate into the real world value.
    Example: The result from the 12 A2D is 3272 and my meter says it is 3235 (actually 3.235). So, if I multiply 3272 by 1.547 I would get the correct real-world value of 5061.784. Then I would need to strip off some digits and add the decimal in the correct place.
    All not too easy in PBP3 without real numbers..... Need to figure out how to get from 3272 to 5.06!

    I can't seem to wrap my head around a solution, any ideas?

    Updated code below so others might use what is working so far:
    'Set for using PIC18F46K80
    'Programmed using PicBasic Pro 3.0.7.4
    'Environment MCSP 5.0.0.5

    'Define configuration
    #CONFIG
    CONFIG RETEN = ON ;Ultra-low regulator ON
    CONFIG FOSC = EC3 ;External HS oscillator, port function on RA6
    CONFIG INTOSCSEL = LOW ;LF-INTOSC in Low-power mode during Sleep
    CONFIG SOSCSEL = DIG ;Digital (SCLKI) mode
    ;FCMEM doesn't seem to work here.....
    ; CONFIG FCMEM = OFF ;Fail Safe CLock Monitor is OFF
    CONFIG IESO = OFF ;Internal/External oscillator switchover is OFF
    CONFIG PWRTEN = ON ;Power Up timer is ON
    CONFIG BOREN = OFF ;Brown Out Reset is OFF - for now
    CONFIG BORV = 0 ;Brown Out level is 4.6v
    CONFIG WDTEN = OFF ;Watchdog is OFF - for now
    CONFIG MCLRE = ON ;MCLR pin is ENABLED
    CONFIG STVREN = ON ;Stack FULL/UNDERFLOW reset is ENABLED
    CONFIG BBSIZ = BB1K ;Boot Block size - 1K?
    CONFIG XINST = OFF ;Extended Instructgion set is DISABLED
    #ENDCONFIG

    '---------------------------------------------------------------------------------------
    'Define the oscillator and setup the INCLUDE files
    DEFINE OSC 64 '64 MHz oscillator, external
    INCLUDE "DT_INTS-18.bas" 'Base Interrupt System
    INCLUDE "ReEnterPBP-18.bas" 'Include if using PBP interrupts

    '---------------------------------------------------------------------------------------
    'OKAY, Lets set up the registers.....
    OSCCON= %00001000 'Device enters SLEEP mode when SLEEP is executed
    OSCCON2= %00000000 'System clock comes from other osc than internal
    REFOCON.7=0 'Refrence oscillator is DISABLED
    WPUB= %00000000 'PORTB pullups DISABLED
    PADCFG1= %00000000 'ALL pull up resistors DISABLED on ports D,E
    ANCON0= %00000001 'Selects AN1-AN7 as DIGITAL, AN0 as ANALOG
    ANCON1= %00000000 'Selects remaining analog/digital inputs as DIGITAL
    ADCON0= %00000000 'Turns OFF ADC - REMEMBER TO TURN IT BACK ON AFTER DEBUG-, selects AD0 as input
    ADCON1= %10110000 'Vref is INTERNAL 4.1v and AVss
    ADCON2= %10010110 'RIGHT justified, 4 TAD A2D aq time select, Fosc/64
    T0CON.7=0 'DISABLES TMR0
    CM1CON= %00000000 'Turns OFF CM1 comparator
    CM2CON= %00000000 'Turns OFF CM2 comparator
    CVRCON.7=0 'Comparator voltage ref is powered DOWN
    HLVDCON.4=0 'High Low Voltage Detect is DISABLED
    CCP1CON=%00000000 'Turns OFF capture, compare, pwm
    CCP2CON=%00000000 'Turns OFF capture, compare, pwm
    CCP3CON=%00000000 'Turns OFF capture, compare, pwm
    CCP4CON=%00000000 'Turns OFF capture, compare, pwm
    CCP5CON=%00000000 'Turns OFF capture, compare, pwm
    CANCON=%00100000 'CAN disabled
    CTMUCONH.7=0 'CTMU disabled
    INTCON= %00000000 'INT0 and POIRTB change external interrupt is DISABLED
    INTCON2= %01111100 'PORTB pullups enabled by TRIS, int are RISING edge, TMR0 hi and rest low priority
    INTCON3.3=0 'Disables INT1 external interupt
    IOCB= %00000000 'PORTB interrupt on change all bits DISABLED
    SLRCON=%00000000 'Slew rate for all ports is STANDARD
    SSPCON1.5=0 'MSSP port is DISABLED
    ODCON=%00000000 'Open Drain capability is DISABLED
    PSTR1CON= %00000000
    ' MDCON=%00000000 'Modulation Control is DISABLED
    '---------------------------------------------------------------------------------------
    'Direction registers
    TRISA = %10001011 'Set PORTA for bit7 is clk in, 2 led out, 1 temp in, 1 A/D in, ext Vref
    TRISB = %11001111 'PORTB is ICSP, 2 pins for LCD, low nibble for 4 button inputs
    TRISC = %10001111 'Set RC7 (RX), rest are outputs, low 4 bits used as inputs for addressing
    TRISD = %10000000 'Set PORTD for serial, 1 LED, 4 LCD data
    TRISE = %00001000 'Set PORTE for MCLR, low 3 bits for addressing - high order not used
    '----------------------------------------------------------------------------------------
    'Constants here
    sync con $54
    Line1 CON 128 'Point to beginning of line 1 ($2)
    Line2 CON 192 'Point to beginning of line 2 ($C0)
    Line3 con 148 'Point to beginning of line 3 ($94)
    line4 con 212 'Point to beginning of line 4 ($D4)
    HystLevel CON 7 ' 7 = .7 of the Least Significant Digit
    ' Valid HystLevel is from 6 to 13
    AvgCount CON 16 ' = Number of samples to average. For best response
    ' times, keep AvgCount as small as you can
    FAspread CON 50 ' = Fast Average threshold +/-
    ' FAspread should be larger than the worst possible
    ' noise in the A/D conversion.

    '----------------------------------------------------------------------------------------

    ADCval var word 'Result of 12 bit ADC
    ADCavg var word 'Running ADC average
    k var byte
    AVGchanged VAR BIT ' 1 indicates that the Average Value has changed
    ' you have to clear this bit after using it
    ADavg VAR WORD ' Stores the current Average
    ADhyst VAR WORD ' Stores the current Value for Hysterisis
    Value VAR WORD ' Input / Output variable to be averaged
    spread CON FAspread * 10 ' adjust spread *10 for Hyst.

    '################################################# ################################################## ######################
    '# We go around the rest of the subroutines
    '################################################# ################################################## ######################
    Initialize:
    goto startmain 'Jumps around subroutines
    '################################################# ################################################## ######################
    '# Subroutines
    '################################################# ################################################## ######################

    Volt:
    ADCON0=%00000011 'Select channel AN0, and start sampling then after 4 TADs - convert
    while ADCON0.1 = 1 :wend 'Wait for ADC DONE
    ADCval.highbyte = ADRESH 'Move HIGH byte of result to adcVAL
    ADCval.lowbyte = ADRESL 'Move LOW byte of result to adcVAL
    ' adcval=(adcval*1.567) '1.567 will convert voltage divider into real voltage
    ' Just don't know HOW to do it.........
    'I have taken the ((ADCavg/1000)*1547)/1000 which works on the calculator, but here without REAL numbers????
    'THEN add a decimal so ADCavg ends up being 5.06 given ADCavg of 3272.....
    value=ADCval
    gosub average
    ADCavg=value
    return

    Average:'Thanks Darrel...via PBP forum.
    Value = Value * 10 ' Scale value up for hysterisis
    IF Value = ADavg Then NoChange ' if they're the same, nothing to do
    IF ABS (Value - ADavg) > spread OR Value < AvgCount Then FastAvg
    IF ABS (Value - ADavg) < AvgCount Then RealClose
    ADavg = ADavg - (ADavg/AvgCount) ' Subtract 1 samples worth
    ADavg = ADavg + (Value/AvgCount) ' Add in the new sample portion
    GoTo AVGok
    FastAvg: ' Catch up to the changing value
    ADavg = Value ' Set Average to the current value
    GoTo AVGok
    RealClose: ' Reduce the sample size when
    ADavg = ADavg - (ADavg/(AvgCount/4)) ' the average and the sample are
    ADavg = ADavg + (Value/(AvgCount/4)) ' "Real Close"
    AVGok:
    IF ABS (ADavg - ADhyst) > HystLevel then ' If it changed > HystLevel +/-
    ADhyst = ((ADavg + 5) / 10) * 10 ' Round ADavg to get new Value
    AVGchanged = 1 ' Indicate that Average changed
    ENDIF
    NoChange:
    Value = ADhyst / 10 ' Scale the result down
    Return

    '################################################# ################################################## ######################
    '# Startmain - where the MAGIC starts!
    '################################################# ################################################## ######################
    startmain:
    lcdout $FE,1
    lcdout $FE,line3," @ startmain " 'Display code version
    lcdout $FE,line4,"SMODE address= ",dec3 address," "'Display our ADDRESS
    pause 2000 'Display for a while
    PB:
    'Get PBs to work and print to LCD
    gosub volt
    if PB1=1 then lcdout $FE,line1,"5 volt= ", dec ADCavg," ", dec ADCval
    ' if PB1=1 then lcdout $FE,line1,"5 volt= ", dec ADCavg," ", [#(ADCval/10,".",#(ADCval//10)]
    lcdout $FE,line2," "
    lcdout $FE,line3,DEC (temperature / 100), ".", DEC2 temperature, " F "
    ' lcdout $FE,line4," " 'Display done with init
    pause 100 'Display for a while
    goto PB
    "If we knew what we were doing, it wouldn't be called research"
    - Albert Einstein

  2. #2
    Join Date
    Sep 2007
    Location
    Waco, Texas
    Posts
    151


    Did you find this post helpful? Yes | No

    Default Re: 12 bit A2D on 18F46K80, need a bit of help for figuring TAD and getting correct v

    Ha!
    I am a DUMMY! It was SO easy...... just have to play with the forum software.
    Ahem, here is the code in better formatted style:
    Code:
    'Set for using PIC18F46K80
    'Programmed using PicBasic Pro 3.0.7.4
    'Environment MCSP 5.0.0.5
    'Program using the USB MELABS programmer - not yet
    
    
    'Define configuration 
    #CONFIG
            CONFIG  RETEN = ON      ;Ultra-low regulator ON
            CONFIG  FOSC = EC3      ;External HS oscillator, port function on RA6
            CONFIG INTOSCSEL = LOW	;LF-INTOSC in Low-power mode during Sleep
            CONFIG SOSCSEL = DIG	;Digital (SCLKI) mode
    ;FCMEM doesn't seem to work here.....
    ;        CONFIG  FCMEM = OFF     ;Fail Safe CLock Monitor is OFF
            CONFIG  IESO = OFF      ;Internal/External oscillator switchover is OFF
            CONFIG  PWRTEN = ON     ;Power Up timer is ON
            CONFIG  BOREN = OFF     ;Brown Out Reset is OFF - for now
            CONFIG  BORV = 0        ;Brown Out level is 4.6v
            CONFIG  WDTEN = OFF     ;Watchdog is OFF - for now
            CONFIG  MCLRE = ON      ;MCLR pin is ENABLED
            CONFIG  STVREN = ON     ;Stack FULL/UNDERFLOW reset is ENABLED
            CONFIG  BBSIZ = BB1K    ;Boot Block size - 1K?
            CONFIG  XINST = OFF     ;Extended Instructgion set is DISABLED
    #ENDCONFIG
    
    '---------------------------------------------------------------------------------------
    'Define the oscillator and setup the INCLUDE files
    	DEFINE	OSC	64						                '64 MHz oscillator, external  
        INCLUDE "DT_INTS-18.bas"                            'Base Interrupt System
        INCLUDE "ReEnterPBP-18.bas"                         'Include if using PBP interrupts
    
    '---------------------------------------------------------------------------------------
    'OKAY, Lets set up the registers.....
        OSCCON= %00001000                                    'Device enters SLEEP mode when SLEEP is executed
        OSCCON2= %00000000                                   'System clock comes from other osc than internal
        REFOCON.7=0                                        'Refrence oscillator is DISABLED
        WPUB= %00000000                                      'PORTB pullups DISABLED
        PADCFG1= %00000000                                   'ALL pull up resistors DISABLED on ports D,E
        ANCON0= %00000001                                     'Selects AN1-AN7 as DIGITAL, AN0 as ANALOG
        ANCON1= %00000000                                     'Selects remaining analog/digital inputs as DIGITAL
        ADCON0= %00000000                                    'Turns OFF ADC - REMEMBER TO TURN IT BACK ON AFTER DEBUG-, selects AD0 as input
        ADCON1= %10110000                                    'Vref is INTERNAL 4.1v and AVss
        ADCON2= %10010110                                    'RIGHT justified, 4 TAD A2D aq time select, Fosc/64 
        T0CON.7=0                                           'DISABLES TMR0
        CM1CON= %00000000                                    'Turns OFF CM1 comparator 
        CM2CON= %00000000                                    'Turns OFF CM2 comparator 
        CVRCON.7=0                                          'Comparator voltage ref is powered DOWN
        HLVDCON.4=0                                         'High Low Voltage Detect is DISABLED
        CCP1CON=%00000000                                   'Turns OFF capture, compare, pwm
        CCP2CON=%00000000                                   'Turns OFF capture, compare, pwm    
        CCP3CON=%00000000                                   'Turns OFF capture, compare, pwm
        CCP4CON=%00000000                                   'Turns OFF capture, compare, pwm
        CCP5CON=%00000000                                   'Turns OFF capture, compare, pwm
        CANCON=%00100000                                    'CAN disabled
        CTMUCONH.7=0                                        'CTMU disabled
        INTCON= %00000000                                    'INT0 and POIRTB change external interrupt is DISABLED
        INTCON2= %01111100                                  'PORTB pullups enabled by TRIS, int are RISING edge, TMR0 hi and rest low priority
        INTCON3.3=0                                         'Disables INT1 external interupt
        IOCB= %00000000                                     'PORTB interrupt on change all bits DISABLED
        SLRCON=%00000000                                    'Slew rate for all ports is STANDARD
        SSPCON1.5=0                                         'MSSP port is DISABLED
        ODCON=%00000000                                     'Open Drain capability is DISABLED
        PSTR1CON= %00000000
    '    MDCON=%00000000                                    'Modulation Control is DISABLED
    '---------------------------------------------------------------------------------------
    'Direction registers
        TRISA = %10001011                                   'Set PORTA for bit7 is clk in, 2 led out, 1 temp in, 1 A/D in, ext Vref
        TRISB = %11001111                                   'PORTB is ICSP, 2 pins for LCD, low nibble for 4 button inputs 
        TRISC = %10001111                                   'Set RC7 (RX), rest are outputs, low 4 bits used as inputs for addressing 
        TRISD = %10000000                                   'Set PORTD for serial, 1 LED, 4 LCD data
        TRISE = %00001000                                   'Set PORTE for MCLR, low 3 bits for addressing - high order not used
    '---------------------------------------------------------------------------------------- 
    'Constants here
        sync        con $54
        Line1       CON 128                                 'Point to beginning of line 1 ($2) 
        Line2       CON 192                                 'Point to beginning of line 2 ($C0)
        Line3       con 148                                 'Point to beginning of line 3 ($94)   
        line4       con 212                                 'Point to beginning of line 4 ($D4)
        HystLevel   CON  7                                  ' 7 = .7 of the Least Significant Digit
                                                            '    Valid HystLevel is from 6 to 13
        AvgCount    CON  16                                 ' = Number of samples to average. For best response 
                                                            '    times, keep AvgCount as small as you can
        FAspread    CON  50                                 ' = Fast Average threshold +/-
                                                            '  FAspread should be larger than the worst possible
                                                            '  noise in the A/D conversion.
    
    '------------------------------------------------------------------------------------------
    'Variable List
        ADCval          var word                        'Result of 12 bit ADC
        ADCavg          var word                        'Running ADC average
        k               var byte
        AVGchanged      VAR  BIT                        ' 1 indicates that the Average Value has changed
                                                        ' you have to clear this bit after using it
        ADavg           VAR  WORD                       ' Stores the current Average
        ADhyst          VAR  WORD                       ' Stores the current Value for Hysterisis
        Value           VAR  WORD                       ' Input / Output variable to be averaged
        spread           CON  FAspread * 10             ' adjust spread *10 for Hyst.
    
    
    '---------------------------------------------------------------------------------------------
    '#########################################################################################################################
    '# 	We go around the rest of the subroutines
    '#########################################################################################################################
    Initialize:
             goto startmain	    				            'Jumps around subroutines
    '#########################################################################################################################
    '#	Subroutines
    '#########################################################################################################################
    
    Volt:   
            ADCON0=%00000011                                'Select channel AN0, and start sampling then after 4 TADs - convert
            while ADCON0.1 = 1 :wend                        'Wait for ADC DONE
            ADCval.highbyte = ADRESH                        'Move HIGH byte of result to adcVAL
            ADCval.lowbyte = ADRESL                         'Move LOW byte of result to adcVAL
    '        adcval=(adcval*1.567)                          '1.567 will convert voltage divider into real voltage
    ' Just don't know HOW to do it.........
    'I have taken the ((ADCavg/1000)*1547)/1000 which works on the calculator, but here without REAL numbers????
    'THEN add a decimal so ADCavg ends up being 5.06 given ADCavg of 3272.....
            value=ADCval
            gosub average
            ADCavg=value
            return
    
    Average:'Thanks Darrel...via PBP forum.
            Value = Value * 10                              ' Scale value up for hysterisis
            IF Value = ADavg Then NoChange                  ' if they're the same, nothing to do 
            IF ABS (Value - ADavg) > spread OR Value < AvgCount Then FastAvg
            IF ABS (Value - ADavg) < AvgCount Then RealClose
            ADavg = ADavg - (ADavg/AvgCount)                ' Subtract 1 samples worth
            ADavg = ADavg + (Value/AvgCount)                ' Add in the new sample portion 
            GoTo AVGok
        FastAvg:                                            ' Catch up to the changing value
            ADavg = Value                                   ' Set Average to the current value
            GoTo AVGok
        RealClose:                                          ' Reduce the sample size when
            ADavg = ADavg - (ADavg/(AvgCount/4))            ' the average and the sample are
            ADavg = ADavg + (Value/(AvgCount/4))            ' "Real Close"
        AVGok:
            IF ABS (ADavg - ADhyst) > HystLevel then        ' If it changed > HystLevel +/-
                ADhyst = ((ADavg + 5) / 10) * 10            ' Round ADavg to get new Value
                AVGchanged = 1                              ' Indicate that Average changed
            ENDIF   
            NoChange:
            Value = ADhyst / 10                             ' Scale the result down
            Return
    '#########################################################################################################################
    '#	Startmain - where the MAGIC starts!
    '#########################################################################################################################
    startmain:
        lcdout $FE,1
        lcdout $FE,line3," @ startmain        "             'Display code version
        lcdout $FE,line4,"SMODE address= ",dec3 address,"  "'Display our ADDRESS
        pause 2000                                          'Display for a while
    PB:
    'Get PBs to work and print to LCD
        gosub volt
        if PB1=1 then lcdout $FE,line1,"5 volt= ", dec ADCavg," ", dec ADCval
    '    if PB1=1 then lcdout $FE,line1,"5 volt= ", dec ADCavg," ", [#(ADCval/10,".",#(ADCval//10)]
        lcdout $FE,line2,"                    "
        lcdout $FE,line3,DEC (temperature / 100), ".", DEC2 temperature, " F            "
    '    lcdout $FE,line4,"                    "             'Display done with init
        pause 100                                            'Display for a while
        goto PB
    "If we knew what we were doing, it wouldn't be called research"
    - Albert Einstein

  3. #3
    Join Date
    Sep 2007
    Location
    Waco, Texas
    Posts
    151


    Did you find this post helpful? Yes | No

    Default Re: 12 bit A2D on 18F46K80, need a bit of help for figuring TAD and getting correct v

    I do have a solution, I can read the ADC, strip off 1 digit, multiply the ADC value by a constant needed for the resistor (voltage) divider, strip off 2 LSBs and format the result for the LCD.
    Seems to be accurate down as low as 4.55 - didn't want to go any lower!
    Posted the module's final code here:
    Thanks for the wealth of info on this forum, as well as the responses.
    Regards.

    Code:
    'Set for using PIC18F46K80
    'Programmed using PicBasic Pro 3.0.7.4
    'Environment MCSP 5.0.0.5
    
    'Define configuration 
    #CONFIG
            CONFIG  RETEN = ON      ;Ultra-low regulator ON
            CONFIG  FOSC = EC3      ;External HS oscillator, port function on RA6
            CONFIG INTOSCSEL = LOW	;LF-INTOSC in Low-power mode during Sleep
            CONFIG SOSCSEL = DIG	;Digital (SCLKI) mode
    ;FCMEM doesn't seem to work here.....
    ;        CONFIG  FCMEM = OFF     ;Fail Safe CLock Monitor is OFF
            CONFIG  IESO = OFF      ;Internal/External oscillator switchover is OFF
            CONFIG  PWRTEN = ON     ;Power Up timer is ON
            CONFIG  BOREN = OFF     ;Brown Out Reset is OFF - for now
            CONFIG  BORV = 0        ;Brown Out level is 4.6v
            CONFIG  WDTEN = OFF     ;Watchdog is OFF - for now
            CONFIG  MCLRE = ON      ;MCLR pin is ENABLED
            CONFIG  STVREN = ON     ;Stack FULL/UNDERFLOW reset is ENABLED
            CONFIG  BBSIZ = BB1K    ;Boot Block size - 1K?
            CONFIG  XINST = OFF     ;Extended Instructgion set is DISABLED
    #ENDCONFIG
    
    '---------------------------------------------------------------------------------------
    'Define the oscillator and setup the INCLUDE files
    	DEFINE	OSC	64						                '64 MHz oscillator, external  
        INCLUDE "DT_INTS-18.bas"                            'Base Interrupt System
        INCLUDE "ReEnterPBP-18.bas"                         'Include if using PBP interrupts
    
    '---------------------------------------------------------------------------------------
    'OKAY, Lets set up the registers.....
        OSCCON= %00001000                                    'Device enters SLEEP mode when SLEEP is executed
        OSCCON2= %00000000                                   'System clock comes from other osc than internal
        REFOCON.7=0                                        'Refrence oscillator is DISABLED
        WPUB= %00000000                                      'PORTB pullups DISABLED
        PADCFG1= %00000000                                   'ALL pull up resistors DISABLED on ports D,E
        ANCON0= %00000001                                     'Selects AN1-AN7 as DIGITAL, AN0 as ANALOG
        ANCON1= %00000000                                     'Selects remaining analog/digital inputs as DIGITAL
        ADCON0= %00000000                                    'Turns OFF ADC - REMEMBER TO TURN IT BACK ON AFTER DEBUG-, selects AD0 as input
        ADCON1= %10110000                                    'Vref is INTERNAL 4.1v and AVss
        ADCON2= %10010110                                    'RIGHT justified, 4 TAD A2D aq time select, Fosc/64 
        T0CON.7=0                                           'DISABLES TMR0
        CM1CON= %00000000                                    'Turns OFF CM1 comparator 
        CM2CON= %00000000                                    'Turns OFF CM2 comparator 
        CVRCON.7=0                                          'Comparator voltage ref is powered DOWN
        HLVDCON.4=0                                         'High Low Voltage Detect is DISABLED
        CCP1CON=%00000000                                   'Turns OFF capture, compare, pwm
        CCP2CON=%00000000                                   'Turns OFF capture, compare, pwm    
        CCP3CON=%00000000                                   'Turns OFF capture, compare, pwm
        CCP4CON=%00000000                                   'Turns OFF capture, compare, pwm
        CCP5CON=%00000000                                   'Turns OFF capture, compare, pwm
        CANCON=%00100000                                    'CAN disabled
        CTMUCONH.7=0                                        'CTMU disabled
        INTCON= %00000000                                    'INT0 and POIRTB change external interrupt is DISABLED
        INTCON2= %01111100                                  'PORTB pullups enabled by TRIS, int are RISING edge, TMR0 hi and rest low priority
        INTCON3.3=0                                         'Disables INT1 external interupt
        IOCB= %00000000                                     'PORTB interrupt on change all bits DISABLED
        SLRCON=%00000000                                    'Slew rate for all ports is STANDARD
        SSPCON1.5=0                                         'MSSP port is DISABLED
        ODCON=%00000000                                     'Open Drain capability is DISABLED
        PSTR1CON= %00000000
    '    MDCON=%00000000                                    'Modulation Control is DISABLED
    '---------------------------------------------------------------------------------------
    'Direction registers
        TRISA = %10001011                                   'Set PORTA for bit7 is clk in, 2 led out, 1 temp in, 1 A/D in, ext Vref
        TRISB = %11001111                                   'PORTB is ICSP, 2 pins for LCD, low nibble for 4 button inputs 
        TRISC = %10001111                                   'Set RC7 (RX), rest are outputs, low 4 bits used as inputs for addressing 
        TRISD = %10000000                                   'Set PORTD for serial, 1 LED, 4 LCD data
        TRISE = %00001000                                   'Set PORTE for MCLR, low 3 bits for addressing - high order not used
    '---------------------------------------------------------------------------------------- 
    'Constants here
        sync        con $54
        Line1       CON 128                                 'Point to beginning of line 1 ($2) 
        Line2       CON 192                                 'Point to beginning of line 2 ($C0)
        Line3       con 148                                 'Point to beginning of line 3 ($94)   
        line4       con 212                                 'Point to beginning of line 4 ($D4)
        HystLevel   CON  7                                  ' 7 = .7 of the Least Significant Digit
                                                            '    Valid HystLevel is from 6 to 13
        AvgCount    CON  16                                 ' = Number of samples to average. For best response 
                                                            '    times, keep AvgCount as small as you can
        FAspread    CON  50                                 ' = Fast Average threshold +/-
                                                            '  FAspread should be larger than the worst possible
                                                            '  noise in the A/D conversion.
    
    '----------------------------------------------------------------------------------------
    'Additional I/O Definitions
        error           var PORTA.5                         'ERROR output, ACTIVE HIGH 
        heart           var PORTA.6                         'Heartbeat to know we are online - ACTIVE HIGH
        warn            var PORTD.4                         'WARNING output, ACTIVE HIGH 
        status1         var PORTC.4                         'STATUS output, ACTIVE HIGH 
        NCTS            Var PORTC.5                         'Goes high to xmit on COMMAND RS485
        SCTS            VAR PORTD.5                         'Goes high to xmit on STUB RS485
        PB1             var PORTB.3                         'Pushbutton1 (far left)
        PB2             var PORTB.2                         'Pushbutton2
        PB3             var PORTB.1                         'Pushbutton3
        PB4             var PORTB.0                         'Pushbutton4 (on far right)
        addr_dig1       var PORTE.0                         'LSB of address
        addr_dig2       var PORTE.1                         'Digit 2 of address
        addr_dig3       var PORTE.2                         'MSB of address
        DQ              Var PORTA.1                         'One-wire data pin 
    
    '------------------------------------------------------------------------------------------
    'Variable List
        i               var byte                            'Loop counter var
        j               var byte                            'Loop counter var
        Node_rxbyte     var byte                            'NODE serial receive byte
        Stub_rxbyte     var byte                            'STUB serial receive byte
        temperature     Var Word                            'Temperature storage
        count_remain    Var Byte                            'Count remaining
        count_per_c     Var Byte                            'Count per degree C 
        In_Count        VAR BYTE                            'Where we are in the 8 byte packet
        Buff            VAR BYTE[4]                         'Array for the data
        CMD_PORT        VAR Buff[0]                         '2nd byte (after sync byte ($54) contains the 4 bits for STATUS/ 4 bits for PORT
        BOARD           VAR Buff[1]                         'Board number on STUB network
        SUMCHK          VAR Buff[2]                         'Simple sumcheck to see if payload is good
        SyncRcvd        VAR BIT                             'Flag set when we get a proper sync byte
        PacketRcvd      VAR BIT                             'Flag set when we get a whole packet
        address         var word                            'Address variable
        bcd1            VAR BYTE                                'lsb of BCD address
        bcd10           var byte                                '10's of BCD address
        bcd100          var byte                                'MSB of BCD address
        ADCval          var word                            'Result of 12 bit ADC
        ADCavg          var word                            'Running ADC average
        k               var byte
        AVGchanged      VAR  BIT                            ' 1 indicates that the Average Value has changed
                                                            ' you have to clear this bit after using it
        ADavg           VAR  WORD                           ' Stores the current Average
        ADhyst          VAR  WORD                           ' Stores the current Value for Hysterisis
        Value           VAR  WORD                           ' Input / Output variable to be averaged
        spread           CON  FAspread * 10                 ' adjust spread *10 for Hyst.
    
    
    '---------------------------------------------------------------------------------------------
    '#########################################################################################################################
    '#	We are going to start this Pig!
    '#########################################################################################################################
    init:                                                   
        heart=0                                             'Turns off HEARTBEAT led
        warn=0                                              'Turns off WARNING led
        error=0                                             'Turns off ERROR led
        status1=0                                           'Turns off STATUS1 led    
        heart=1 : warn=1 : error=1 : status1=1              'Turns ON leds
        pause 20                                            'Hold here for a bit while things IPL......
        gosub initlcd                                       'Initializes the lcd
        pause 2000                                          'Display for a while
        heart=0 : warn=0 : error=0 : status1=0              'Turns OFF leds
    '#########################################################################################################################
    '# 	We go around the rest of the subroutines
    '#########################################################################################################################
    Initialize:
            heart=0                                         'Turns off HEARTBEAT led
            warn=0                                          'Turns off WARNING led
            error=0                                         'Turns off ERROR led
            status1=0                                       'Turns off STATUS1 led    
            ncts=0                                          'NODE network 485 in receive mode
            scts=0                                          'STUB network 485 in receive mode
            temperature=0                                   'Zeros var
            bcd1=0 : bcd10=0 : bcd100=0                     'Zeros the address vars
            gosub chirp                                     'Flashed ERROR before we start
            goto startmain	    				            'Jumps around subroutines
    '#########################################################################################################################
    '#	Subroutines
    '#########################################################################################################################
    
    initlcd:lcdout	$fe,1          	     	                'Inits the lcd
    		return
    
    get_addr:       
    'Get the address and perform functions to get the digit data
    'this is code for the use of rotary hex switches - 3 of them
        addr_dig1=0 : addr_dig2=0 : addr_dig3=0             'Set all commons LOW
        status1=1                                           'Turns ON the StATUS1 led
        addr_dig1=1                                         'Set LSB HIGH in order to read
        bcd1=PORTC & $0F                                    'Reads port and strips off high nibble, puts in bcd1
        pause 5
        addr_dig1=0                                         'Resets digit 1 common
        pause 5
        addr_dig2=1                                         'Sets digit 2 common
        bcd10=PORTC & $0F                                   'Reads port and strips off high nibble, puts in bcd10
        pause 5
        addr_dig2=0                                         'Resets digit 2 common
        pause 5
        addr_dig3=1                                         'Sets digit 3 common
        bcd100=PORTC & $0F                                  'Reads port and strips off high nibble, puts in bcd100
        pause 5
        addr_dig3=0                                         'Resets digit 3 common
        address=(bcd100*100)+(bcd10*10)+bcd1                'Builds the address from the 3 digits
        status1=0                                           'Turns OFF STATUS2 led
        return
    
    h2d:    ' Convert Hex coded data -> decimal data
            	K = (K & $F )+((K>>4)*10)
            	Return
    d2h:  ' Convert Decimal -> Hex coded data
           		K = (K DIG 1) * $10 + (K DIG 0)
            	Return   
                      
    chirp:  for i=1 to 3
            high error
            pause 50
            low error
            pause 50
            next i
            return
    
    get_temp:                                               'Gets temperature from DS1820, puts in degrees F
            OWOut DQ, 1, [$CC, $44]                         'Start temperature conversion
            pause 1000
            OWIn DQ, 4, [count_remain]                      'Check for still busy converting
            If count_remain = 0 Then 
                OWOut DQ, 1, [$CC, $BE]                     'Read the temperature
                OWIn DQ, 0, [temperature.LOWBYTE, temperature.HIGHBYTE, Skip 4, count_remain, count_per_c]
            endif
            temperature = (temperature */ 461) + 3200
            return
    
    Volt:   
            ADCON0=%00000011                                'Select channel AN0, and start sampling then after 4 TADs - convert
            while ADCON0.1 = 1 :wend                        'Wait for ADC DONE
            ADCval.highbyte = ADRESH                        'Move HIGH byte of result to adcVAL
            ADCval.lowbyte = ADRESL                         'Move LOW byte of result to adcVAL
            value=ADCval
            gosub average
            ADCavg=value
    'Here we 'normalize' the ADC reading to real-world voltage
            ADCavg=ADCavg/10                                'Leaves us with 3 digits
            ADCavg=ADCavg*155                               'Our normalizing junk-yard constant
            ADCavg=ADCavg/100                               'Leaves us with 3 digits
            return
    
    Average:'Thanks Darrel...via PBP forum.
            Value = Value * 10                              ' Scale value up for hysterisis
            IF Value = ADavg Then NoChange                  ' if they're the same, nothing to do 
            IF ABS (Value - ADavg) > spread OR Value < AvgCount Then FastAvg
            IF ABS (Value - ADavg) < AvgCount Then RealClose
            ADavg = ADavg - (ADavg/AvgCount)                ' Subtract 1 samples worth
            ADavg = ADavg + (Value/AvgCount)                ' Add in the new sample portion 
            GoTo AVGok
        FastAvg:                                            ' Catch up to the changing value
            ADavg = Value                                   ' Set Average to the current value
            GoTo AVGok
        RealClose:                                          ' Reduce the sample size when
            ADavg = ADavg - (ADavg/(AvgCount/4))            ' the average and the sample are
            ADavg = ADavg + (Value/(AvgCount/4))            ' "Real Close"
        AVGok:
            IF ABS (ADavg - ADhyst) > HystLevel then        ' If it changed > HystLevel +/-
                ADhyst = ((ADavg + 5) / 10) * 10            ' Round ADavg to get new Value
                AVGchanged = 1                              ' Indicate that Average changed
            ENDIF   
            NoChange:
            Value = ADhyst / 10                             ' Scale the result down
            Return
    
    
    '#########################################################################################################################
    '#	Startmain - where the MAGIC starts!
    '#########################################################################################################################
    startmain:
        gosub initlcd                                       'Initializes the lcd
        gosub get_addr                                      'Gets board address
        gosub get_temp                                      'Gets temp from DS18S20 - not quite working
        gosub volt                                          'Gets the +5 volt rail voltage
        pause 200
        lcdout $FE,1
        lcdout $FE,line1," CLUSTER CONTROLLER "             'Display who we are
        lcdout $FE,line2,"SMODE address= ",dec3 address,"  "'Display our address
        lcdout $FE,line3,"5 volt= ", DEC ADCavg/100,".",DEC2 ADCavg//100 'Display +5 volt rail
        lcdout $FE,line4,DEC (temperature / 100), ".", DEC2 temperature, " F            " 'Display our temp
        pause 2000                                          'Display for a while
        goto startmain
    "If we knew what we were doing, it wouldn't be called research"
    - Albert Einstein

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


    Did you find this post helpful? Yes | No

    Default Re: 12 bit A2D on 18F46K80, need a bit of help for figuring TAD and getting correct v

    Hi,
    Need to figure out how to get from 3272 to 5.06!
    Couple of ideas:
    Code:
    ADValue VAR WORD
    Temp VAR WORD
    Result VAR WORD
    
    ADValue = 3272
    Temp = ADValue ** 35809   ' Multiply by ~0.5464
    Result = ADValue + Temp     ' Result now 5059
    
    ' Or, same as above but without using the Temp variable:
    Result = ADValue + (ADValue ** 35809)
    
    ' Or, perhaps:
    ADValue = 3272
    Result = ADValue */ 396     ' Multiply by ~1.5469, Result now 5061
    
    'Display the value
    LCDOUT Result / 1000, ".", DEC3 Result // 1000
    /Henrik.

  5. #5
    Join Date
    Jan 2011
    Location
    Sydney, Australia
    Posts
    172


    Did you find this post helpful? Yes | No

    Default Re: 12 bit A2D on 18F46K80, need a bit of help for figuring TAD and getting correct v

    Hi,

    If you change your voltage divider to a 50%-50% configuration (say 4k7 and 4k7) and then set the reference voltage for the ADC to internal 4.096V, each step of the ADC will equate 0.5mV
    Multiply your ADC reading by two and then manipulate the result to read "X.XXX Volts" per Henrik's LCDOUT routine.
    Yes, I understand there may be some slight inaccuracies but I have found this approach to be quite effecting in recent projects.

    Cheers
    Barry
    VK2XBP

  6. #6
    Join Date
    Sep 2007
    Location
    Waco, Texas
    Posts
    151


    Did you find this post helpful? Yes | No

    Default Re: 12 bit A2D on 18F46K80, need a bit of help for figuring TAD and getting correct v

    Henrik-
    That looks like a cool way to do this, I have never used these operators, but I will try them all, just to see more about them.
    It looks much more efficient than what I had done - multiple dividing......

    Thanks! I will let you know how it turned out.
    -Steve
    "If we knew what we were doing, it wouldn't be called research"
    - Albert Einstein

  7. #7
    Join Date
    Sep 2007
    Location
    Waco, Texas
    Posts
    151


    Did you find this post helpful? Yes | No

    Default Re: 12 bit A2D on 18F46K80, need a bit of help for figuring TAD and getting correct v

    Barry-
    I understand what you are saying, and yes, I am using the internal 4.1 reference - 1st time in fact to rely on an internal!. I was trying to use more of the available resolution on the ADC. If I do a 50% voltage divider, I have 2.5 volts against a 4.096 voltage reference. The divider I am using, uses more of the resolution of the 4.096 reference, 3.23 volts against 4.096 which gives me a little headroom above 5 volts.

    I have done that in the past, but felt that I left some resolution on the table. This way does work, perhaps not straightforward, but I think it does give me more bits of resolution that can be used.

    That being said, if I hadn't found a way (though it was more clunky than Henrik's) - I was sure thinking of doing just that!

    Thanks and Regards to All,
    Steve
    "If we knew what we were doing, it wouldn't be called research"
    - Albert Einstein

  8. #8
    Join Date
    Sep 2007
    Location
    Waco, Texas
    Posts
    151


    Did you find this post helpful? Yes | No

    Default Re: 12 bit A2D on 18F46K80, need a bit of help for figuring TAD and getting correct v

    Henrik-
    Sorry for the late reply, been out with a respiratory illness - geeesh.
    In your example :
    ADValue = 3272
    Temp = ADValue ** 35809 ' Multiply by ~0.5464
    Result = ADValue + Temp ' Result now 5059

    Why are you using 'Top 16 bits' for multiplying? and how did you arrive at '35809' as the multiplier?

    I really want to learn from this, Thanks.
    -Steve
    "If we knew what we were doing, it wouldn't be called research"
    - Albert Einstein

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


    Did you find this post helpful? Yes | No

    Default Re: 12 bit A2D on 18F46K80, need a bit of help for figuring TAD and getting correct v

    Hi,
    We want a "raw" display value of 5060 when the ADC returns 3272. That's a factor of 1.5464, right?
    The ** operator does a 16*16bit multiplication and then returns the 16 top bits of the intermediate 32bit result which is the same as dividing that intermediate result by 65536.

    So, on a calculator, 3272 * 35809 / 65536 = 1787 (truncated). Add in the "original" 3272 and we get 5059 which is pretty close to 5060.

    Just think of the ** operators as multiplying by units of 1/65536.
    65536*0.5464 = 35809...
    35809 * (1/65536) = 0.5464...
    And so on.

    /Henrik.

  10. #10
    Join Date
    Sep 2007
    Location
    Waco, Texas
    Posts
    151


    Did you find this post helpful? Yes | No

    Default Re: 12 bit A2D on 18F46K80, need a bit of help for figuring TAD and getting correct v

    Henrik-
    So, I kinda get the top 16 bits thing, but I still don't know where you got the number 35809?
    65536 * 0.5464 ----> shouldn't this be 65535 * 1.5464?
    -Steve
    "If we knew what we were doing, it wouldn't be called research"
    - Albert Einstein

Similar Threads

  1. How do I use 10 bit A/D on 8 bit Pic? 12F675
    By polymer52 in forum mel PIC BASIC Pro
    Replies: 8
    Last Post: - 1st April 2020, 20:10
  2. Replies: 1
    Last Post: - 12th March 2012, 23:34
  3. Averaging 16 bit values without using 32 bit math
    By sirvo in forum mel PIC BASIC Pro
    Replies: 2
    Last Post: - 5th October 2007, 22:18
  4. LCDOUT 4-bit data on 8-bit setting
    By breesy in forum mel PIC BASIC Pro
    Replies: 6
    Last Post: - 26th June 2006, 18:39
  5. Help 14-bit and 16-bit Core
    By jetpr in forum mel PIC BASIC Pro
    Replies: 3
    Last Post: - 14th September 2005, 03:29

Members who have read this thread : 0

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

Posting Permissions

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