Author Topic: PIC - getting lost / stuck in data table  (Read 9921 times)

0 Members and 1 Guest are viewing this topic.

Offline katzohkiTopic starter

  • Frequent Contributor
  • **
  • Posts: 378
  • Country: us
    • My Blog
PIC - getting lost / stuck in data table
« on: February 06, 2015, 11:30:12 pm »
Hi All,

I'm working on a program for the PIC12F1840. As part of my ISR, I am adjusting a target value that is then later compared with the A/D. I've narrowed it down to my target adjustment subroutine using traps (execution goes in, but it never comes out!). I'd appreciate any help you can offer. Stepping through the code manually in MPLAB X works fine.

Code: [Select]
AD_switch   ;Change target value    ; TODO: FIX THIS! CALLS GO IN, BUT THEY NEVER COME OUT!!!
    movf    jump,w
    call    output_table
    movwf   target  ;load value from output table into target for A/D
    incf    jump,f
    return
output_table                        ; TODO: NEVER LEAVES HERE ALIVE?
    addwf   PCL,f
outputs dt  0xDB,0x1F,0x3F,0x5E,0x7D,0x9C,0xBC,0xDB,0xFA    ;retlw with value   ;   GETTING STUCK HERE?
    clrf    jump            ;reset counter if gone past last value
    clrw    ; also need to do this as we are using w for PCL jump
    goto    output_table    ;and try again

Thanks
 

Offline Rory

  • Frequent Contributor
  • **
  • Posts: 410
  • Country: us
Re: PIC - getting lost / stuck in data table
« Reply #1 on: February 06, 2015, 11:35:18 pm »
Page boundaries?
 

Offline katzohkiTopic starter

  • Frequent Contributor
  • **
  • Posts: 378
  • Country: us
    • My Blog
Re: PIC - getting lost / stuck in data table
« Reply #2 on: February 06, 2015, 11:53:00 pm »
Page boundaries?

I don't think so, last code location is 0x00E2 according to the .lst file, but map says program starts at 0x0004 and ends at 0x011b so maybe? I'll try putting some pagesel in.
 

Online Andy Watson

  • Super Contributor
  • ***
  • Posts: 2082
Re: PIC - getting lost / stuck in data table
« Reply #3 on: February 07, 2015, 12:02:43 am »
I don't think so, last code location is 0x00E2 according to the .lst file, but map says program starts at 0x0004 and ends at 0x011b so maybe? I'll try putting some pagesel in.
Consider what happens if the page boundary occurs in the middle of the table.
 

Offline katzohkiTopic starter

  • Frequent Contributor
  • **
  • Posts: 378
  • Country: us
    • My Blog
Re: PIC - getting lost / stuck in data table
« Reply #4 on: February 07, 2015, 12:06:39 am »
I don't think so, last code location is 0x00E2 according to the .lst file, but map says program starts at 0x0004 and ends at 0x011b so maybe? I'll try putting some pagesel in.
Consider what happens if the page boundary occurs in the middle of the table.

 :palm: Yeah I think this is the problem. I tried moving that bit of code earlier and it works. I'm going to move my subroutines to a specific page and fcall them. Especially that one.

Edit: Now I'm not so sure...
« Last Edit: February 07, 2015, 01:10:06 am by katzohki »
 

Offline katzohkiTopic starter

  • Frequent Contributor
  • **
  • Posts: 378
  • Country: us
    • My Blog
Re: PIC - getting lost / stuck in data table
« Reply #5 on: February 07, 2015, 12:44:47 am »
Wait a second, I don't understand because as I said my last code location is 0x00E0 and my code is only 560 bytes? Could this really be going past page boundaries?
 

Online Andy Watson

  • Super Contributor
  • ***
  • Posts: 2082
Re: PIC - getting lost / stuck in data table
« Reply #6 on: February 07, 2015, 12:51:32 am »
Can you post the listing of the table with against absolute addresses?
 

Offline katzohkiTopic starter

  • Frequent Contributor
  • **
  • Posts: 378
  • Country: us
    • My Blog
Re: PIC - getting lost / stuck in data table
« Reply #7 on: February 07, 2015, 01:05:32 am »
Can you post the listing of the table with against absolute addresses?

Now I've moved it around a bit, but here it is

Code: [Select]
008E                  00470 AD_switch   ;Change target value    ; TODO: Problem is this is on seperate page
008E   08??           00471     movf    jump,w
008F   2???           00472     call    output_table
0090   00??           00473     movwf   target  ;load value from output table into target for A/D
0091   0A??           00474     incf    jump,f
0092   0008           00475     return
0093                  00476 output_table
0093   0782           00477     addwf   PCL,f
0094   34DB 341F 343F 00478 outputs dt  0xDB,0x1F,0x3F,0x5E,0x7D,0x9C,0xBC,0xDB,0xFA    ;retlw with value   ;probably sits across pa
                            ge boundary
       345E 347D 349C
       34BC 34DB 34FA
009D   01??           00479     clrf    jump            ;reset counter if gone past last value
009E   0103           00480     clrw    ; also need to do this as we are using w for PCL jump
009F   2???           00481     goto    output_table    ;and try again
                      00482
 

Online Andy Watson

  • Super Contributor
  • ***
  • Posts: 2082
Re: PIC - getting lost / stuck in data table
« Reply #8 on: February 07, 2015, 01:12:01 am »
Looks ok but the question marks suggest that that is not the final compilation. Can you get to the absolute code listing? i.e. the code that is programmed into the chip.
 

Offline katzohkiTopic starter

  • Frequent Contributor
  • **
  • Posts: 378
  • Country: us
    • My Blog
Re: PIC - getting lost / stuck in data table
« Reply #9 on: February 07, 2015, 01:17:24 am »
Like the .hex file? I got the .lst from /build/default/production in my project folder.
 

Online Andy Watson

  • Super Contributor
  • ***
  • Posts: 2082
Re: PIC - getting lost / stuck in data table
« Reply #10 on: February 07, 2015, 01:29:43 am »
I'm not familiar with the MPLAB X tool chain, but there should be some method of generating an absolute listing. As a last resort you could try disassembling the hex file.
 

Offline katzohkiTopic starter

  • Frequent Contributor
  • **
  • Posts: 378
  • Country: us
    • My Blog
Re: PIC - getting lost / stuck in data table
« Reply #11 on: February 07, 2015, 01:41:16 am »
OK well I do think there is a good chance that this is a paging issue because now that I've moved this function it works differently. I can only see that being a paging thing. The thing I don't understand is I was under the impression that page 0 is 0x0000 to 0x07ff? Or is that not right? The map says that the program runs from 0x0004 to 0x0129, so if page 0 is 0x00 to 0xff then I can see that happening. What is your advice to handle paging? I took a shot at pagesel and lcall, but it did not produce good results.
 

Online Andy Watson

  • Super Contributor
  • ***
  • Posts: 2082
Re: PIC - getting lost / stuck in data table
« Reply #12 on: February 07, 2015, 01:53:04 am »
The add PCL,f only works on 8 bit values - so we are talking about 256 word pages. The upper bits are determined by PCLATH. If your table crosses a 256 word page boundary I believe the address simply wraps around to the start of the page - not the next - i.e. there's no carry.

Map? Does that give you the addresses of the labels too? If so, just look up the address of your table. The end of the code at 0x0129 indicates that a 256 word boundary is being crossed.
 

Offline katzohkiTopic starter

  • Frequent Contributor
  • **
  • Posts: 378
  • Country: us
    • My Blog
Re: PIC - getting lost / stuck in data table
« Reply #13 on: February 07, 2015, 03:00:32 am »
Looking at map, the last function in the program is at e9 and the table is before that. So I don't think it should be crossing a page boundary, but the fact that moving the subroutine higher in the program does some to suggest it is. Now the first three values in my table work. Before the subroutine was near the bottom and now it is at the too of my subroutines. Weird.

Anyway the powers out here now so I can't copy over any more code.
 

Offline 22swg

  • Frequent Contributor
  • **
  • Posts: 274
  • Country: gb
Re: PIC - getting lost / stuck in data table
« Reply #14 on: February 07, 2015, 10:34:05 am »
The jump value would have to be in the range of H'00 to H'08  if not = stuck ( anywhere )  the table  addwf PLC adds w to program counter that then addresses your table RETLW  returns with value to the call address +1 . call and table has to be in same page .   
Check your tongue, your belly and your lust. Better to enjoy someone else’s madness.
 

Offline katzohkiTopic starter

  • Frequent Contributor
  • **
  • Posts: 378
  • Country: us
    • My Blog
Re: PIC - getting lost / stuck in data table
« Reply #15 on: February 07, 2015, 09:57:12 pm »
The jump value would have to be in the range of H'00 to H'08  if not = stuck ( anywhere )  the table  addwf PLC adds w to program counter that then addresses your table RETLW  returns with value to the call address +1 . call and table has to be in same page .

Yep. You will see that the code resets the "jump" value and WREG and starts over again in case it goes past the table by one. I realize that assumes that it only goes past by one though.

I tried moving the subroutines to 0x100 and 0x800 and using lcall and pagesel, but that didn't seem to help. I might have rushed it. I'm going to try using some of the tricks from Microchip's AN 556 and see if that helps as well as stepping through the code and watching PCLATH. ... Now that the power's back on...
 

Offline 22swg

  • Frequent Contributor
  • **
  • Posts: 274
  • Country: gb
Re: PIC - getting lost / stuck in data table
« Reply #16 on: February 07, 2015, 10:13:15 pm »
Only if jump has a value of H'09 what happens if jump is H'0A or H'FF  ? ,  you need restrict the jump value < H'09 before you call output_table . ( I usually put retlw tables in the first page alond with the sub that calls it.)
I would AND jump with H'0F and make your table 16 bytes long ... pad with H'00 ,  don't need your clrf code then either 
« Last Edit: February 07, 2015, 10:18:26 pm by 22swg »
Check your tongue, your belly and your lust. Better to enjoy someone else’s madness.
 

Offline dannyf

  • Super Contributor
  • ***
  • Posts: 8221
  • Country: 00
Re: PIC - getting lost / stuck in data table
« Reply #17 on: February 07, 2015, 10:20:33 pm »
Quote
I'm going to try using some of the tricks

Would coding it in C work?
================================
https://dannyelectronics.wordpress.com/
 

Offline katzohkiTopic starter

  • Frequent Contributor
  • **
  • Posts: 378
  • Country: us
    • My Blog
Re: PIC - getting lost / stuck in data table
« Reply #18 on: February 07, 2015, 11:09:33 pm »
Only if jump has a value of H'09 what happens if jump is H'0A or H'FF  ? ,  you need restrict the jump value < H'09 before you call output_table . ( I usually put retlw tables in the first page alond with the sub that calls it.)
I would AND jump with H'0F and make your table 16 bytes long ... pad with H'00 ,  don't need your clrf code then either

I get what you're saying. The only place 'jump' is modified is in the code pasted above, but I'll give it a shot.

@Dannyf, lol yeah it probably would. I wanted to finish this project off in assembly before moving on to the next program that I will write in C. Partly because I wanted to make sure I'm confident in assembly again.

Get this though, the program runs -as expected- immediately after programming, but with a power reset it does not!  :scared: WTF?  |O

Edit: should mention that it acts like it has seen a POR. Code and data protect are off.
 

Offline dannyf

  • Super Contributor
  • ***
  • Posts: 8221
  • Country: 00
Re: PIC - getting lost / stuck in data table
« Reply #19 on: February 07, 2015, 11:43:54 pm »
C's value-add is that it allows you to focus on the more value-add stuff, like logic, algorithm, etc. while leaving the low value-add stuff to the compiler.

Quote
Get this though, the program runs -as expected- immediately after programming, but with a power reset it does not!  :scared: WTF?  |O

If I were you, I would produce a minimalist and full program so that others can play with it and help you diagnose the issue.

From where I stand, it sounds like a memory over-boundary issue.
================================
https://dannyelectronics.wordpress.com/
 

Online Andy Watson

  • Super Contributor
  • ***
  • Posts: 2082
Re: PIC - getting lost / stuck in data table
« Reply #20 on: February 07, 2015, 11:46:25 pm »
Get this though, the program runs -as expected- immediately after programming, but with a power reset it does not!  :scared: WTF?  |O
Have you left it set for debug mode?
 

Offline katzohkiTopic starter

  • Frequent Contributor
  • **
  • Posts: 378
  • Country: us
    • My Blog
Re: PIC - getting lost / stuck in data table
« Reply #21 on: February 07, 2015, 11:51:55 pm »
Get this though, the program runs -as expected- immediately after programming, but with a power reset it does not!  :scared: WTF?  |O
Have you left it set for debug mode?

No. Doing that produces "different" results. I have done that before.

@Dannyf: Oh yes, I agree, but since I was out of practice I wanted to have some practice. IMO understanding what the MCU is doing is crucial before writing with a high level language. OK here goes the whole shebang:

Code: [Select]
list p=12F1840      ; list directive to define processor
#include <p12F1840.inc> ; processor specific variable definitions

;------------------------------------------------------------------------------
;
; CONFIGURATION WORD SETUP
;
; The 'CONFIG' directive is used to embed the configuration word within the
; .asm file. The lables following the directive are located in the respective
; .inc file.  See the data sheet for additional information on configuration
; word settings.
;
;------------------------------------------------------------------------------


; Configurations are set. LVP Off OK?

    __CONFIG _CONFIG1, _FOSC_INTOSC & _WDTE_OFF & _PWRTE_ON  & _MCLRE_ON  & _CP_OFF & _CPD_OFF & _BOREN_OFF & _CLKOUTEN_OFF & _IESO_OFF & _FCMEN_OFF
    __CONFIG _CONFIG2, _WRT_OFF & _PLLEN_ON & _STVREN_OFF & _BORV_19 & _LVP_OFF

; TODO: Setup Watchdog timer (off in sleep)
; TODO: Setup BOREN

;------------------------------------------------------------------------------
; VARIABLE DEFINITIONS
;
; Available Data Memory divided into Bank 0-15.  Each Bank may contain
; Special Function Registers, General Purpose Registers, and Access RAM
;
;------------------------------------------------------------------------------

TEMP_VAR    UDATA   ;NON Common RAM
sT2CON      RES     1


COMMON_RAM  UDATA_SHR   0x70    ;COMMON RAM
target  RES     1
dc1     RES     1
dc2     RES     2
dc3     RES     1
db_cnt  RES     1
AD_DATA RES     1
jump    RES     1
d1      RES     1
d2      RES     1

;target      EQU    0x7D        ; TARGET value to compare A/D with
;                               ; Sample user registers (common RAM)
;RAM2        EQU    0x7E        ; (0x70 -> 0x7F are RAM LOCATIONS)
;RAM3        EQU    0x7F        ; (sets up named RAM location)

;------------------------------------------------------------------------------
; EEPROM INITIALIZATION
;
; The 12F1822 has 256 bytes of non-volatile EEPROM, starting at address 0xF000
;
;------------------------------------------------------------------------------

; TODO: Some EEPROM data if needed
;DATAEE    ORG  0xF000
;    DE    "MCHP"  ; Place 'M' 'C' 'H' 'P' at address 0,1,2,3
;This might be a good place for copyright info

;------------------------------------------------------------------------------
; RESET VECTOR
;------------------------------------------------------------------------------

    ORG     0x0000            ; processor reset vector
    GOTO    initialize        ; When using debug header, first inst.
                              ; may be passed over by ICD2.

;------------------------------------------------------------------------------
; INTERRUPT SERVICE ROUTINE - Debounce button press and increment PWM *********
;------------------------------------------------------------------------------
; TODO: COMPLETE OVERHAUL OF ISR - DOES NOT WORK AND NEVER DID

isr ORG      0x0004
    ; GIE is cleared automatically so another interrupt does not occur while
    ; handling the current one.

;    BANKSEL PIR1
;    btfss   PIR1,ADIF   ;check if A/D interrupt triggered
;    goto    int_exit    ; nope, exit
;    goto    ADC2        ; yes, handle A/D

    BANKSEL IOCAF
    btfss   IOCAF,IOCAF4    ; Test if IOC on RA4 was triggered
    goto    int_exit        ;nope, let's get out of here! (technically an error)

    call    db_dn   ; wait for solid down state
    addwf   PCL,f   ; skip next if debounce confirmed
    goto    int_exit    ;switch is still bouncing or it was a glitch

;   DO SOMETHING HERE
    ; Increment comparison for A/D (target in RAM)
    call    AD_switch   ; TODO: FIX (SEE BELOW)

;trap1
;    BANKSEL CCPR1L
;    movlw   b'11111111'
;    movwf   CCPR1L
;    goto    $

    call    db_up   ; wait for solid up state
    addwf   PCL,f
    goto    $-2     ; keep waiting for solid up state
    goto    int_exit


;    ;For testing: TODO: remove
;    BANKSEL CCPR1L
;    movlw   b'00100000'
;    addwf   CCPR1L
;    goto    int_exit


    goto    int_exit


int_exit    ; need to update if other interrupts are eventually used
    BANKSEL IOCAF
    clrf    IOCAF   ; also magically clears INTCON,IOCIF
    BANKSEL IOCAN
    bsf     IOCAN,IOCAN4    ; Wasn't doing before, may be needed
    BANKSEL INTCON
    bsf     INTCON,IOCIE    ; Same
    BANKSEL PORTA
    movf    PORTA,w ; read PORTA to clear mismatches
    retfie          ; automatically reenables GIE and restores status

;------------------------------------------------------------------------------
; END ISR   *******************************************************************
;------------------------------------------------------------------------------



;------------------------------------------------------------------------------
; INITIALIZATION
;------------------------------------------------------------------------------

initialize
    clrf    target
;    ;TODO: Remove this delay for production
;    movlw   .20
;    call    delay10 ;This delay is intended to help with MCLRE_OFF during programming

;Set Fosc to 32 MHz
;OSCCON =     11110000 ;SPLLEN on, IRCF 8MHz, SCS = 00
    BANKSEL OSCCON
    movlw   b'11110000'
    movwf   OSCCON

; Set timer prescale to 1 (31.25kHz for Pulse Width Period)
; This seems to be the default condition. Maybe skip?
    BANKSEL T2CON
    movf    T2CON,w
    movwf   sT2CON
    bcf sT2CON,0
    bcf sT2CON,1
    movf    sT2CON,w
    movwf   T2CON


; PWM SETUP: *****RA2 PWM OUTPUT Pin 5****************************************
;   Disable CCP1 output driver by setting appropriate TRIS bit
    BANKSEL TRISA
    bsf     TRISA,2     ;Set RA2 as input (tristated)
;   Load PR2 register with PWM period value - 0xFF
;   Also a default condition, skip?
    BANKSEL PR2
    movlw   0xFF
    movwf   PR2
;   Configure CCP1 module for PWM mode by loading CCP1CON register with appropriate values
    ;CCP1CON = 00001101     PWM single output, 2 LSBs of PWM duty cycle, 1101 = PWM mode: P1A active-high; P1B active-low
    BANKSEL CCP1CON
    ;           xx  <- these two bits are 2 LSBs of PWM duty cycle
    movlw   b'00001101' ;00001101
    movwf   CCP1CON
;   Load the CCPR1L register and DC1B1 bits of CCP1CON register with PWM duty cycle value
    clrf    CCPR1L  ;initialize at 0% Duty-cycle ("off")
;   Configure and start Timer 2:
;       Clear TMR2IF of the PIR1 register
    BANKSEL PIR1
    bcf     PIR1,1
;       Config T2CKPS bits of T2CON register with Timer prescale value
;       This is already done above!
;       Enable Timer 2 by setting the TMR2ON bit of T2CON register
    bsf T2CON,2
;   Enable PWM output pin: Enable CCP1 Pin output by clearing associated TRIS bit
    BANKSEL TRISA
    bcf TRISA,2     ;PWM should now be active on pin 5 (but zero, since DC = 0%)
;   (Note: we are ignoring step 6 - see PIC12F1840 datasheet 24.3.2)
; PWM DUTY CYCLE (see 24.3.4)
    ;SET PWM to 0% for initialize
    BANKSEL CCPR1L
    movlw   b'00000000' ;   50% => 10000000 LSB=00, 512 = 1024/2
    movwf   CCPR1L
; END PWM SETUP ***************************************************************


; ***** Initialize Interrupt - falling edge RA4 *******************************
; NOTE: ;TODO: rewrite / fix / check
    BANKSEL INTCON
    ; set GIE bit of INTCON - global interrupt enable
    bsf INTCON,GIE
;    ; Enable peripheral interrupts
;    bsf INTCON,PEIE
;    ;enable A/D peripheral interrupt
;    BANKSEL PIE1
;    bsf PIE1,ADIE

    ; OLD - Set INTE bit of INTCON Interrupt enable INT pin

    ; OLD - clear INTEDG bit of OPTION_REG (falling edge) (set = rising)

;     set IOCIE of INTCON - interrupt on change enable
    bsf INTCON,IOCIE
;     set IOCAN4 of IOCAN - enable falling edge detection on RA4 for interrupt
    BANKSEL IOCAN
    bsf IOCAN,IOCAN4
; END INTERRUPT SETUP *********************************************************


; A/D Setup: *****AN1 channel, pin 1 ******************************************

    ; configure port
    BANKSEL TRISA
    bsf TRISA,1   ;set RA1 / pin 6 as input
    BANKSEL ANSELA
    bsf ANSELA,ANSA1    ;set RA1 as ANALOG input (probably is default)
    ; select channel
    BANKSEL ADCON0
    movlw   b'00000101' ;select AN1 as input channel
    ;              1    --Channel 1
    ;               0   -- A/D start bit
    ;                1  --A/D enabled
    movwf   ADCON0
    ; ADC volt ref selection    ; select clock source   ; result formatting
    BANKSEL ADCON1
    movlw   b'00100011'
    ;         0         -- ADC Result Format     = Left  Justified
    ;          010      -- ADC Conversion Clock  = Fosc/32 (1.0 us conv)
    ;               00  -- ADC Voltage Reference = Vdd
    ;               11  -- ADC Voltage Reference = internal Vref (4.096V)
    movwf   ADCON1

    ; interrupt control (optional)
; END A/D SETUP ***************************************************************


; Initialize FVR **************************************************************
    BANKSEL FVRCON
    movlw   b'10000011'
            ; 1         -- FVREN - enable FVR
            ; xx0       -- Temperature sense enable (1=en)
            ; xxx0      -- Temp sense range
            ; xxxx00    -- Comp, DAC and CPS FVR (default 00 off)
            ; xxxxxx11  -- ADC FVR 4X = 4.096V
    movwf   FVRCON

;FVR_ready      ; page 111, note 1: "FVRRDY is always 1 on PIC12F1840"
;    btfsc   FVRCON,FVRRDY   ; FVR Ready?
;    goto    FVR_ready       ; Wait until ready
; END FVR INITIALIZATION ******************************************************


; TODO: Setup Brown Out Reset
; TODO: Setup Watch Dog Timer

;   TODO: double check this:
; Initialize Switch: RA4 is input with weak pull up - Pin 3 *******************
    BANKSEL TRISA
    bsf TRISA,4   ;bit 4. Set as input RA4
    BANKSEL ANSELA
    bcf ANSELA,ANSA4    ;make sure RA4 is DIGITAL input (was analog by default)
    BANKSEL WPUA
    movlw   b'00010000'
    movwf   WPUA  ;Set WPUA to enable pull up on RA4
    BANKSEL OPTION_REG
    bcf     OPTION_REG,NOT_WPUEN    ;Enable pull-ups globally (bit 7)
; switch enabled **************************************************************


;INITIALIZE TARGET OUTPUT VALUE TO ZERO:
    clrf   target

;------------------------------------------------------------------------------
; MAIN PROGRAM
;------------------------------------------------------------------------------
    movlw   0x7D    ;TEMP for test TODO: remove this
    movwf   target
    BANKSEL PORTA
    movfw   PORTA
    BANKSEL ADCON0
    bsf     ADCON0,GO
main
; select demo program:    roll_main, butt_main, adc_main, int_test_main
    call    delay_10ms  ;10ms delay
    BANKSEL ADCON0
    btfsc   ADCON0,GO_NOT_DONE  ; A/D conversion done?
    goto    main                ; nope, wait another 10ms
    call    compare             ; yes, handle the data
    BANKSEL ADCON0
    bsf     ADCON0,GO           ; Begin A/D conversion
    goto    main
   

; DEMO PROGRAMS:
; INTERRUPT TESTING
int_test_main
    BANKSEL CCPR1L
    movlw   b'00001000'
    movwf   CCPR1L
int_test_loop
    goto    $

; ADC DEMO
; Demo program for A/D - shifts A/D value directly into CCPR1L
adc_main
    BANKSEL ADCON0
    bsf ADCON0,GO   ; Begin A/D conversion
    btfsc   ADCON0,GO_NOT_DONE  ; is A/D conversion completed?
    goto    $-1 ; no - keep checking
adc_handle      ; yes - handle the data
    ;read     BANKSEL ADRESH
    movf    ADRESH,w
    movwf   AD_DATA   ; Store A/D Result (high bits) into AD_DATA GPR (common RAM)ADRESL

    BANKSEL CCPR1L
    movwf   CCPR1L  ; Load A/D Result directly into PWM control value from w
    goto    adc_main

; PWM ROLL DEMO
roll_main
    BANKSEL CCPR1L
    movf    CCPR1L,w
    addlw   b'00001000' ;1000
    movwf   CCPR1L
    movlw   .10
    call    delay10
    goto    roll_main

; BUTTON PRESS DEMO
butt_main
    BANKSEL PORTA
    btfsc   PORTA,RA4   ;check button pressed (RA4 pulled down)?
    call    button_press
    goto    butt_main

button_press
    call    db_dn   ;db_dn will return with literal in W = 1
    BANKSEL PCL
    addwf   PCL,f   ;jumps next instruction if debounce confirmed
    goto    main
    BANKSEL CCPR1L
    movf    CCPR1L,w
    addlw   b'00100000' ; increment PWM DC%
    movwf   CCPR1L
    call    db_up
    BANKSEL PORTA
    return

;------------------------------------------------------------------------------
; SUBROUTINES
;------------------------------------------------------------------------------\

compare ; Compare A/D to target setting
    BANKSEL ADRESH
    movf    ADRESH,w
    movwf   AD_DATA   ; Store A/D Result (high bits) into AD_DATA GPR (common RAM)
    movf    target,w
    subwf   AD_DATA,w
    BANKSEL STATUS
    btfsc   STATUS,Z
    return    ; A/D and target are equal, do nothing
    btfsc   STATUS,C
    goto    decrement   ; A/D is greater so decrease PWM
    goto    increment   ; A/D is lessor so increase PWM
    return

decrement   ; Decrement PWM
    BANKSEL CCPR1L
    decf    CCPR1L,f    ; This is much simpler! D'Oh!
;    movlw   b'000000001'
;    subwf   CCPR1L,w
;    movwf   CCPR1L
;;    movf    CCPR1L,w
;;    sublw   b'00000001' ;sub wreg from literal!! (oops! WRONG ORDER!)
;;    movwf   CCPR1L
    return

increment   ; Increment PWM
    BANKSEL CCPR1L
    incf    CCPR1L,f
;    movf    CCPR1L,w
;    addlw   b'00000001'
;    movwf   CCPR1L
    return

AD_switch   ;Change target value    ; TODO: Problem is this is on seperate page
    movf    jump,w
    call    output_table
    movwf   target  ;load value from output table into target for A/D
    incf    jump,f
    return
output_table
    addwf   PCL,f
outputs dt  0xDB,0x1F,0x3F,0x5E,0x7D,0x9C,0xBC,0xDB,0xFA    ;retlw with value   ;probably sits across page boundary
    clrf    jump            ;reset counter if gone past last value
    clrw    ; also need to do this as we are using w for PCL jump
    goto    output_table    ;and try again

; Some simple delay loops
;125 ns instruction time at 32MHz
delay10     ;delay W * 10 ms    (I don't know if this is right running at 32MHz)
;        BANKSEL dc3
        movwf   dc3

dly2    movlw   .13
        movwf   dc2
        clrf    dc1
dly1    decfsz  dc1,f
        goto    dly1
        decfsz  dc2,f
        goto    dly1
        decfsz  dc3,f
        goto    dly2
;    retlw   0
    return
; 1ms delay at 32 MHz:
Delay1
;7993 cycles
movlw 0x3E
movwf dc1
movlw 0x07
movwf dc2
Delay_0             
decfsz dc1, f
goto $+2
decfsz dc2, f
goto Delay_0
;3 cycles
goto $+1
nop
;4 cycles (including call)
return

; Delay = 0.01 seconds
; Clock frequency = 32 MHz

; Actual delay = 0.01 seconds = 80000 cycles
; Error = 0 %

delay_10ms
;79993 cycles
movlw 0x7E
movwf d1
movlw 0x3F
movwf d2
delay_10ms_0
decfsz d1, f
goto $+2
decfsz d2, f
goto delay_10ms_0

;3 cycles
goto $+1
nop

;4 cycles (including call)
return

;Some Switch Debouncing ; TODO: Fix this for general use
db_dn       clrf    db_cnt
dn_smp      call    Delay1  ;1ms delay at 32MHz
    BANKSEL PORTA
    btfsc   PORTA,RA4   ;test RA4, skip if clear
    retlw   .0
    incf    db_cnt,f    ;increment counter
    movlw   .10
    xorwf   db_cnt,w    ;repeat until 10 counts
    btfss   STATUS,Z
    goto    dn_smp
    retlw   .1

db_up       clrf    db_cnt
up_smp      call    Delay1  ;1ms delay at 32MHz
    BANKSEL PORTA
    btfss   PORTA,RA4   ;test RA4, skip if set
    retlw   .0
    incf    db_cnt,f    ;increment counter
    movlw   .10
    xorwf   db_cnt,w    ;repeat until 10 counts
    btfss   STATUS,Z
    goto    up_smp
    retlw   .1




ORG     0x07F0
trap1
    BANKSEL CCPR1L
    movlw   b'11111111'
    movwf   CCPR1L
    goto    $

ORG 0x0FF0
    BANKSEL CCPR1L
    movlw   b'11111111'
    movwf   CCPR1L
    goto    $

    END
 

Offline 22swg

  • Frequent Contributor
  • **
  • Posts: 274
  • Country: gb
Re: PIC - getting lost / stuck in data table
« Reply #22 on: February 08, 2015, 09:15:52 am »
Katzohki   Im with you on getting to grips with asm , then moving on to C , but it does test you , If i have time will desect 'shebang '  I dont have a 12F1840 to try.

re "jump" , I would run code in simulator see where it goes  you can load hex into the registers in the watch window in MPLAB 8 and single step. Not sure about MPLABX sim  may do same.
I am pretty sure  addwf   PCL,f will perform add on low 8 bits only so if PLC was say  H' 01f9  and w was H'08 result H'0101 .(and a carry) in PLC  .

Edit in my experience the first AD result is crap after a por ..
« Last Edit: February 08, 2015, 09:21:12 am by 22swg »
Check your tongue, your belly and your lust. Better to enjoy someone else’s madness.
 

Offline voja

  • Contributor
  • Posts: 45
  • Country: 00
Re: PIC - getting lost / stuck in data table
« Reply #23 on: February 08, 2015, 02:16:43 pm »
It's a good practice to put all the tables at the very beginning of the program, at least for 8-bit processors. There is only one GOTO START at the beginning (and some more GOTOs if there are interrupts) and then the table follows.

Something like this:
 
    org 0
    goto    start

    org 4            ; processor family dependent, addr 4 is for 12F
    goto interrupt_routine

table:
    ...
    ... (lookup table)
    ...

interrupt_routine:
    ...
    ... (int routine)
    ...
    retfie

start:
    ...
    ... (main program)
    ...
   end
:( + :( = :) :)
 

Offline 22swg

  • Frequent Contributor
  • **
  • Posts: 274
  • Country: gb
Re: PIC - getting lost / stuck in data table
« Reply #24 on: February 08, 2015, 02:42:08 pm »
Agree voja...

Katzohki... also your PIC should support  BRW  as hex to ascii example .

Code: [Select]

HEXTAB ANDLW 0X0F ; MAX 0F
BRW ; BRANCH WITH W
RETLW 0X30  ; 0 ASCII
RETLW 0X31  ; 1 ASCII
RETLW 0X32  ; 2 ASCII
RETLW 0X33  ; 3 ASCII
RETLW 0X34  ; 4 ASCII
RETLW 0X35  ; 5 ASCII
RETLW 0X36  ; 6 ASCII
RETLW 0X37  ; 7 ASCII
RETLW 0X38  ; 8 ASCII
RETLW 0X39  ; 9 ASCII
RETLW 0X41  ; A ASCII
RETLW 0X42  ; B ASCII
RETLW 0X43  ; C ASCII
RETLW 0X44  ; D ASCII
RETLW 0X45  ; E ASCII
RETLW 0X46  ; F ASCII
RETLW 0X59  ; X ASCII

Check your tongue, your belly and your lust. Better to enjoy someone else’s madness.
 

Offline katzohkiTopic starter

  • Frequent Contributor
  • **
  • Posts: 378
  • Country: us
    • My Blog
Re: PIC - getting lost / stuck in data table
« Reply #25 on: February 08, 2015, 06:15:31 pm »
Part of what's frustrating to me is that I am getting different results depending on what I do, stepping through the code it seems to work. And especially the fact that it works immediately after programming, but not on POR. That I really don't understand.
 

Offline 22swg

  • Frequent Contributor
  • **
  • Posts: 274
  • Country: gb
Re: PIC - getting lost / stuck in data table
« Reply #26 on: February 08, 2015, 08:15:12 pm »
Stepping through in simulator what values are you loading in 'jump' ?    I will repeat ...In my experience  AD result can be wild value after a POR .
Check your tongue, your belly and your lust. Better to enjoy someone else’s madness.
 

Offline katzohkiTopic starter

  • Frequent Contributor
  • **
  • Posts: 378
  • Country: us
    • My Blog
Re: PIC - getting lost / stuck in data table
« Reply #27 on: February 08, 2015, 09:43:06 pm »
Stepping through in simulator what values are you loading in 'jump' ?    I will repeat ...In my experience  AD result can be wild value after a POR .

0,1,2,3... up through 8. I have stepped through it and 9 gets reset. I have tried all of the above suggestions too, without success. That includes AND-ing 'jump' with 0x0F and padding the table.

Maybe I am missing your point about the AD result. Are you suggesting that the bad A/D result causes a malfunction to PCL, PCLATH, STKPTR or something? If the data is garbage I don't see how that will cause the program to jump somewhere unexpected. There is no computed GOTO during the handling of A/D data.
 

Offline 22swg

  • Frequent Contributor
  • **
  • Posts: 274
  • Country: gb
Re: PIC - getting lost / stuck in data table
« Reply #28 on: February 08, 2015, 09:52:09 pm »
And what if AD returned a jump value of  H'0A or greater say FF ?    Have you got the table to go wrong ? or is just after POR
« Last Edit: February 08, 2015, 09:54:33 pm by 22swg »
Check your tongue, your belly and your lust. Better to enjoy someone else’s madness.
 

Online Andy Watson

  • Super Contributor
  • ***
  • Posts: 2082
Re: PIC - getting lost / stuck in data table
« Reply #29 on: February 08, 2015, 10:03:33 pm »
I may have missed something but the routines db_dn and db_up appear to be called from both inside and outside the interrupt service routine - but I can't see any provision to either deal-with, nor prevent re-entering the same code.
 

Offline katzohkiTopic starter

  • Frequent Contributor
  • **
  • Posts: 378
  • Country: us
    • My Blog
Re: PIC - getting lost / stuck in data table
« Reply #30 on: February 09, 2015, 12:15:41 am »
And what if AD returned a jump value of  H'0A or greater say FF ?    Have you got the table to go wrong ? or is just after POR

AD data does not go into 'jump'. Not sure if we're on the same page here. Ie ADRESH is not loaded into 'jump'

I may have missed something but the routines db_dn and db_up appear to be called from both inside and outside the interrupt service routine - but I can't see any provision to either deal-with, nor prevent re-entering the same code.

Is that a problem? I can make some separate denounce routines for inside and outside the isr. Actually db-up or db-dn shouldn't really be called from outside the isr. I thought that with a 16 deep stack that should not be a problem, but maybe I am wrong.

What do you think are the chances there is something wrong with the PIC? I don't have any extra PIC12f1840 to play with and I'm not sure porting the code to something spare that I do have will prove much.
 

Online Andy Watson

  • Super Contributor
  • ***
  • Posts: 2082
Re: PIC - getting lost / stuck in data table
« Reply #31 on: February 09, 2015, 12:28:56 am »
I may have missed something but the routines db_dn and db_up appear to be called from both inside and outside the interrupt service routine - but I can't see any provision to either deal-with, nor prevent re-entering the same code.

Is that a problem?
Without delving into the detail of your code and system - I don't know. But potentially it could be a problem. You have to consider the possibility that the "normal" db_dn is interrupted and another pass through the routing is initiated by the ISR - the normal routine could find its values changed in an unexpected way!

Quote

What do you think are the chances there is something wrong with the PIC? I don't have any extra PIC12f1840 to play with and I'm not sure porting the code to something spare that I do have will prove much.
If it responds in anyway what-so-ever, I would have thought the PIC will be good. Write yourself the simplest of simple programs (like wobbling one bit on a port) and check that you can program it into the PIC. I would suspect that there is a configuration bit or other setting that has been overlooked.

 

Offline 22swg

  • Frequent Contributor
  • **
  • Posts: 274
  • Country: gb
Re: PIC - getting lost / stuck in data table
« Reply #32 on: February 09, 2015, 11:09:30 am »
I put your code into MPLAB 8 , didn't understand your register directives , but eventually got it to build ( absolute). could not see a problem with the table location in disassembly listing , however you do not initialize  [jump]  with a known value ? Quite possible after a por it is  H'FF going to table = infinite loop ? PCL  099 add w  FF  = 098 [ not 198 ] PCL increments  ... PCL  now back at  099 . .............
Disassembly below
Code: [Select]


   099    0782     ADDWF 0x2, F                   407:       addwf   PCL,f
   09A    34DB     RETLW 0xdb                     408:   outputs dt  0xDB,0x1F,0x3F,0x5E,0x7D,0x9C,0xBC,0xDB,0xFA    ;retlw with value   ;probably sits across page boundary
   09B    341F     RETLW 0x1f
   09C    343F     RETLW 0x3f
   09D    345E     RETLW 0x5e
   09E    347D     RETLW 0x7d
   09F    349C     RETLW 0x9c
« Last Edit: February 10, 2015, 11:07:02 am by 22swg »
Check your tongue, your belly and your lust. Better to enjoy someone else’s madness.
 

Online nfmax

  • Super Contributor
  • ***
  • Posts: 1560
  • Country: gb
Re: PIC - getting lost / stuck in data table
« Reply #33 on: February 09, 2015, 02:44:43 pm »
In absolute mode, you can get the MPLAB 8 assembler to check for page boundary crossings like this (which is a snippet from a P16F877 program I wrote):
Code: [Select]
;---------------------------------------------------------------------------;
; ADC_Task: Measure ADC output at periodic intervals                        ;
;---------------------------------------------------------------------------;

 IF (ADCStateTableEnd > 0FF)
  ERROR "Jump table out of 8-bit page 0 in ADC_Task"
 ENDIF
 IF ((ADCStateTableStart - 1) & 0FF00) != ((ADCStateTableEnd - 1) & 0FF00)
ERROR "Jump table crosses page boundary in ADC_Task"
 ENDIF
 
ADC_Task movf ADC_task_state,w ; Get state (0 to 4)
addwf PCL,f ; vectored goto based on current state
ADCStateTableStart
goto ADC_wait ; 0 (waiting for timeout)
goto CAL_ADC ; 1 (start ADC calibration cycle)
goto CONV_ADC ; 2 (start ADC conversion cycle)
goto WaitForDRDY1 ; 3 (take CONV low when DRDY goes low)
goto WaitForDRDY2 ; 4 (take CONV low when DRDY goes low)
ADCStateTableEnd
This also checks if the jump table is not in page 0. If it is not in page 0, PCLATH needs to be set correctly before the addwf PCL,f instruction. Your initialisation code must set PCLATH correctly, and it needs to be saved and restored by the interrupt handler. neglecting to do this may explain why your code works after a programming operation, but not a reset.
 

Offline katzohkiTopic starter

  • Frequent Contributor
  • **
  • Posts: 378
  • Country: us
    • My Blog
Re: PIC - getting lost / stuck in data table
« Reply #34 on: February 10, 2015, 05:24:25 pm »
OK, now that is something I didn't think of. I was "trusting" jump and PCLATH to be 0x00 on boot-up, but you have a good point. I will add statements to clear any variables during initialization.

Now I think there may actually be a problem with my PicKit 3. It is no longer able to recognize or program the PIC. I tried with 3 brand new 10F322 in a breadboard with no circuitry connected to the PicKit 3 and it does not recognize their device ID. The program still runs on the 12F1840 so I don't think there is a problem with the PIC itself (still in the sort-of-working mode).

There was an over-current detected on one of the USB ports (the one my USB drive was plugged in). Also "someone" a few weeks ago got drunk and wired in a negative 5 Volt regulator that may have caused damage to the PicKit and / or USB ports. So what do you guys think? Do I need a new programmer? Is there a way to test it? Mplab X says self test is not supported.
 

Offline 22swg

  • Frequent Contributor
  • **
  • Posts: 274
  • Country: gb
Re: PIC - getting lost / stuck in data table
« Reply #35 on: February 10, 2015, 10:26:35 pm »
katzohki   PK3  is fairly robust... changing PIC numbers...  the PK3  will have to reload FW / AP one or both  from IDE , has it done this ? what LEDs twinkle   ....

MPLAB X will report status if you click refresh debug tool status...  green arrows on navigator side bar... also it will load the FW if PIC part is connected and powered....

I picked up my asm "skills"  from magazine articles they always cleared ram and set pages on reset, so I always included a sub to do that.

At this level I think a structured code layout is required, like the previous post by Voja . also try to develop code  in small steps .

Hope I haven't been teaching my Gran to suck eggs !

If you post here with a PK3 topic I am sure you will get lots of good suggestions ....
Check your tongue, your belly and your lust. Better to enjoy someone else’s madness.
 

Offline katzohkiTopic starter

  • Frequent Contributor
  • **
  • Posts: 378
  • Country: us
    • My Blog
Re: PIC - getting lost / stuck in data table
« Reply #36 on: February 10, 2015, 11:29:07 pm »
OK so here's the deal.

Number 1: The application works now (yay!  :-+ ) Thank you all for the great help. I think between putting the table at the top of code and clearing my variables at initialization fixed it.

Number 2: The PICkit 3 did indeed have a problem. Fortunately, it was a software issue and not a hardware one. I had to use the PICkit 3 scripting tool to reload the PICkit 3 operating system onto the PK3. Whatever happened, it must have corrupted the PK 3 somewhat. Once doing that, I was able to use the scripting tool to erase, verify and load hex files into the PICs again. Then I had to reset configurations in MPLab X and now everything is working as it should.

I was getting pretty frustrated Friday night, we were having a windstorm. All day people were coming and going and my desk looked like a disaster area, my fence gate got torn off and sections of the fence got knocked down. And to top it all off we finally lost power for several hours. I'm guessing that one of the brownouts or power surges might have something to do with the PK3 getting corrupted. I did have that mysterious overcurrent warning on the USB hub too.

Again, thank you for all the help. I really do appreciate it and I was really trying all the suggestions, but I think at a certain point the hex file wasn't getting written properly anymore. Oh, and by the way, don't drink and engineer!  :palm: Or else you might place a negative 5V regulator instead of a positive one!
 

Offline dannyf

  • Super Contributor
  • ***
  • Posts: 8221
  • Country: 00
Re: PIC - getting lost / stuck in data table
« Reply #37 on: February 11, 2015, 02:51:34 am »
Quote
Whatever happened

It usually happens if you power on the board before the pickit3 (or 2).

Reloading the OS solves quickly.
================================
https://dannyelectronics.wordpress.com/
 


Share me

Digg  Facebook  SlashDot  Delicious  Technorati  Twitter  Google  Yahoo
Smf