chiark / gitweb /
basic (probably v. buggy) program for doing i2c and morse msgs at the
authorceb <ceb>
Wed, 29 Jun 2005 23:45:15 +0000 (23:45 +0000)
committerceb <ceb>
Wed, 29 Jun 2005 23:45:15 +0000 (23:45 +0000)
same time. hacked about from i2c-test and morsepanic, so probably still
somewhat confused.

cebpic/i2c-test-reply.asm [new file with mode: 0644]

diff --git a/cebpic/i2c-test-reply.asm b/cebpic/i2c-test-reply.asm
new file mode 100644 (file)
index 0000000..bb2f71b
--- /dev/null
@@ -0,0 +1,765 @@
+; write a byte to pic0 via the serial port, pic0 will transmit it to
+; pic1, which will then toggle its colour (without checking the contents
+; of the byte)
+
+; pin 21 (per-pic-led, RD2/PSP2/C1IN) states: 
+;  high H = blue (=green), low L = orange (=red), float Z = black
+
+;***************************************************************************
+;SETUP AND DEFINITIONS
+
+; CONVENTIONS:
+;
+; In subroutines, unless otherwise stated, W and S may have any
+; value on entry and will be undefined on exit.
+;
+; labels ending _if[not_... and _endif_... are used for
+;    if ... then [... else ...]
+; labels ending _loop are for loops
+; labels ending _isr are at the start of interrupt service routines
+;                      (which must end with retfie)
+; labels starting vector_ are the reset and interrupt entrypoints
+; other labels in lowercase are normal subroutines (ending in `return')
+; labels in UPPERCASE are defined addresses (in RAM or flash)
+
+;---------------------------------------------------------------------------
+; boilerplate:
+
+        include         /usr/share/gputils/header/p18f458.inc
+       radix           dec
+
+        include common.inc
+        include morse-auto.inc
+        include ../iwjpictest/insn-aliases.inc
+
+       extern  led_green
+       extern  led_red
+       extern  led_black
+
+       ifdef   SLOW_VERSION
+       messg   "hello this is the slow version"
+       endif
+
+       ifndef  SLOW_VERSION
+       messg   "hello this is the fast version"
+       endif
+
+       ifdef   SLOW_VERSION
+       messg   "with an if"
+       else
+       messg   "and an else"
+       endif
+
+;---------------------------------------------------------------------------
+
+; ID locations layout, in flash - see README.protocol
+
+F_PIC_NO       equ     0x200000
+F_I2C_CTRL     equ     0x200001
+
+; reserved access bank locations
+
+WREG2           equ     00h     ; a 2nd working reg :-)
+WREG3           equ     01h     ; a 3rd working reg :-)
+WREG4           equ     02h     ; a 4th working reg :-)
+BLANK           equ     03h     ; register full of zeros
+TESTFLASH       equ     04h     ; test LED flash pattern
+
+; used in panic macro for temporary storage
+PANIC_MORSE     equ     05h     ; stores # bytes of morse msg in panic readout
+PANIC_REGS      equ     06h     ; stores # registers in panic readout
+PANIC_ADDRESS   equ     07h     ; stores condensed form of message start addr.
+
+
+; constants
+
+MORSE_MSG_LENGTH        equ     04h     ; lenght of morse messages in bytes
+
+
+;---------------------------------------------------------------------------
+; memory location definitions
+
+ERROR_BUF_PAGE  equ     3       ; error codes on flash p3
+F_ERROR_U       equ     00h     ; upper part of error memory locations
+F_SOS_H         equ     40h     ; high (middle) part of SOS error memory loc.
+F_SOS_L         equ     00h     ; lower part of SOS error memory loc.
+
+
+;---------------------------------------------------------------------------
+; RAM - ie, variables etc.
+
+; i2c specific stuff
+               udata   0x400
+
+PIC_NO         res     1
+
+I2C_CTRL       res     1
+I2C_CTRL_MASTER        equ     7       ; bit 7 of I2C_CTRL is 1=master 0=slave
+
+;---------------------------------------------------------------------------
+; error messages
+
+err_SOS equ     0       ; msg 0 = SOS
+
+;****************************************************************************
+; VECTORS: special locations, where the PIC starts executing
+; after reset and interrupts
+
+       org     0
+       goto    vector_reset
+
+       org     000008h
+       goto    vector_interrupt_high
+
+       org     000018h
+       goto    vector_interrupt_low
+
+;****************************************************************************
+; MACROS
+;---------------------------------------------------------------------------
+panic macro message
+        movlw   (message - morse_messages_start)/4
+        movwf   PANIC_ADDRESS
+        goto    panic_routine
+        endm
+
+;----------------------------------------
+; ifbit1(REGISTER,BITNUMBER)
+;      executes the next instruction but only if bit BITNUMBER
+;      in REGISTER (which must be in the access bank) is set
+ifbit1 macro REGISTER, BITNUMBER
+       btfsc   REGISTER, BITNUMBER, 0
+       endm
+
+;----------------------------------------
+; ifbit0(REGISTER,BITNUMBER)
+;      executes the next instruction but only if bit BITNUMBER
+;      in REGISTER (which must be in the access bank) is clear
+ifbit0 macro REGISTER, BITNUMBER
+       btfss   REGISTER, BITNUMBER, 0
+       endm
+
+;----------------------------------------
+; debug(BYTE)
+;      writes BYTE through the serial port
+;      serial port hardware must be suitably initialised
+;      serial port transmit interrupts must be disabled
+;      will spin until the byte is transmitted
+;              Before          After
+;      W       any             undefined
+;      S       any             undefined
+
+; macro to call subroutine to transmit over serial port for debugging
+; takes 8-bit value, puts in W, invokes debug_serial_transmit
+       ifndef  SLOW_VERSION
+debug macro debugvalue
+       endm
+       endif
+
+       ifdef   SLOW_VERSION
+debug macro debugvalue
+       movlw   debugvalue
+       call    polling_serial_transmit
+       endm
+       endif
+
+;----------------------------------------
+; debughf(REGISTER)
+;      reads REGISTER once and writes it to the serial port in hex
+;      for conditions etc. see "debug", above
+;              Before          After
+;      W       any             undefined
+;      S       any             undefined
+ ifdef SLOW_VERSION
+DEBUGHF_VALUE  equ     0x040   ; getting on towards end of access bank
+                               ; FIXME if all of program used udata that
+                               ; would be very nice
+
+debughf macro register
+       movff   register, DEBUGHF_VALUE
+       call    debughf_subroutine
+       endm
+
+debughf_subroutine
+       call    debughf_digit
+       call    debughf_digit
+       return
+
+;--------------------
+debughf_digit
+;      transmits top nybble of DEBUGHF_VALUE in hex
+;      through serial port, as above, and swaps nybbles
+;                      Before          After
+;      W               any             undefined
+; DEBUGHF_VALUE                BBBBaaaa        aaaaBBBB        (BBBB was sent)
+
+       swapf   DEBUGHF_VALUE,1,0
+       movf    DEBUGHF_VALUE,0,0
+       andlw   0x0f
+       sublw   10
+       sublw   0
+       bn      debughf_digit_ifnot_ge10
+       addlw   'a'-('0'+10)
+debughf_digit_ifnot_ge10
+       addlw   '0'+10
+       goto    polling_serial_transmit
+
+ else
+debughf macro register
+       endm
+ endif
+
+
+       
+;****************************************************************************
+; PORTMANTEAU CODE
+; which contains lists of checks and calls to function-specific
+; routines etc.
+
+;----------------------------------------
+vector_reset
+
+       call    serial_setup
+
+       debug   'a'
+
+       call    copy_per_pic_data
+
+       debug   'b'
+
+       call    i2c_setup
+       call    enable_interrupts
+
+       debug   'c'
+
+       goto    main
+
+;----------------------------------------
+main
+       debug   'J'
+       debughf SSPSTAT
+       debughf SSPCON1
+       debughf SSPCON2
+       debughf SSPADD
+
+       banksel I2C_CTRL                ; ser BSR=i2c BSR (4)
+       btfsc   I2C_CTRL,I2C_CTRL_MASTER,1 ; check =master?, if so
+       goto    master_main             ; goto master main routine
+       goto    slave_main              ; elso goto slave main routine
+
+;----------------------------------------
+vector_panic
+        mov_lw          0x5a
+        mov_wf          TESTFLASH
+
+        panic   morse_TG
+
+panic_routine
+; switch off interrupts and power
+; reconfigure timer0 for writing diagnostic msg to the LED
+
+        clrf    INTCON,0        ; disable all interrupts EVER
+        bcf     PORTC,1,0       ; switch off booster
+
+
+; re-initialise timer0 config
+        bcf     T0CON,6,0       ; p107 Timer0 -> 16bit mode
+        bcf     T0CON,5,0       ; timer0 use internal clock
+        bcf     T0CON,3,0       ; use prescaler
+        bcf     T0CON,2,0       ; }
+        bsf     T0CON,1,0       ; } prescale value 1:16 (13ms x 16)
+        bsf     T0CON,0,0       ; }
+
+; get # bytes of morse msg, # registers in panic readout, message start addr.
+; back from condensed message start addr. stored in PANIC_ADDRESS
+
+panic_loop
+        movlw   4
+        mulwf   PANIC_ADDRESS
+        movff   PRODL,TBLPTRL
+        movff   PRODH,WREG
+        add_lw  (morse_messages_start)/256
+        movwf   TBLPTRH
+        clr_f   TBLPTRU
+
+        tblrd   *+              ; read 1st byte of error message
+                                ; (gives # bytes morse, # bytes registers)
+
+        movff   TABLAT,PANIC_MORSE
+        movlw   00001111b
+        and_wff PANIC_MORSE     ; PANIC_MORSE now contains # bytes of morse msgs
+
+        movff   TABLAT,PANIC_REGS
+        movlw   01110000b
+        and_wff PANIC_REGS
+        swap_f  PANIC_REGS      ; PANIC_REGS now contains # registers to read
+
+        call    led_black
+        call    waiting
+        call    waiting
+        call    waiting
+        call    waiting
+        call    morsemsg        ; transmit SOS in red
+        call    led_black
+        call    waiting
+        call    waiting
+        call    waiting
+        call    waiting 
+        call    registermsg     ; transmit contents of TESTFLASH in
+                                ; red(=low) and blue(=high)
+        goto    panic_loop
+
+;****************************************************************************
+; PANIC SUBROUTINES
+
+morsemsg
+; wrapper round readout to flash the per-pic led red for a
+; (currently 4-byte) morse msg
+
+morse_msg_start
+        clrf    WREG3,0         ; clear loop counter (WREG3)
+
+morse_loop
+        mov_fw          PANIC_MORSE
+        cmp_fw_ifge     WREG3           ; if loop counter >=MORSE_MSG_LENGTH,
+        return                          ; return to panic
+
+        tblrd           *+
+        mov_ff          TABLAT,WREG2
+        call            morse_readout
+        inc_f           WREG3
+        goto            morse_loop
+
+
+;--------------------------
+morse_readout
+
+; Flashes the per-pic led red(0) in a specified pattern.
+;
+; The pattern is specified as the state for 8 identically-long time
+; periods each as long as a morse `dot', encoded into a byte with
+; most significant bit first.
+;               On entry                On exit
+; W             any                     undefined
+; WREG2         flash pattern           preserved
+; WREG4         any                     undefined
+
+        clr_f           WREG4           ; clear loop counter (WREG4)
+        rr_f            WREG2
+
+morse_readout_loop
+        mov_lw          8
+        cmp_fw_ifge     WREG4           ; if loop counter >=8, return
+        return
+
+        rl_f            WREG2           ; top bit goes into N, ie Negative if 1
+        bra_n           morse_readout_if_led_1
+
+morse_readout_if_led_0 
+        call            led_black
+        bra             morse_readout_endif_led
+
+morse_readout_if_led_1
+        call            led_red
+
+morse_readout_endif_led
+        inc_f           WREG4           ; increment loop counter
+        call            waiting
+        bra             morse_readout_loop
+
+;--------------------------
+;--------------------------
+registermsg
+
+register_msg_start
+        clrf            WREG3,0         ; clear loop counter (WREG3)
+
+register_loop
+        mov_fw          PANIC_REGS 
+        cmp_fw_ifge     WREG3           ; if loop counter >=MORSE_MSG_LENGTH,
+        return                          ; return to panic
+
+        tblrd           *+
+
+        mov_fw          TABLAT          ; TABLAT has the 8-bit version
+        mov_wf          FSR0L           ; of the address.  So, 8 bits
+                                        ; go straight into FSR0L.
+
+        mov_lw          0x0f            ; For FSR0H, we see if the
+        mov_fw          FSR0H           ; address XX is >=0x60.
+                                        ; If it is then we meant 0xfXX;
+        mov_lw          0x5f            ; if not then we meant 0x0XX.
+        cmp_fw_ifle     FSR0L           ; (This is just like PIC does
+        clr_f           FSR0H           ; for insns using Access Bank)
+
+        mov_ff          INDF0,WREG2
+        call            register_readout
+
+        inc_f           WREG3
+
+        call            waiting
+        call            waiting
+        goto            register_loop
+
+;--------------------------
+register_readout
+
+; Flashes the per-pic led red(0) and green(1) in a specified pattern.
+; (black gap between each bit)
+;
+; The pattern is specified as the state for 8 identically-long time
+; periods each as long as a morse `dot', encoded into a byte with
+; most significant bit first.
+;               On entry                On exit
+; W             any                     undefined
+; WREG2         flash pattern           preserved
+; WREG4         any                     undefined
+
+        clrf    WREG4,0         ; clear loop counter (WREG4)
+        rrncf   WREG2,1
+
+
+register_readout_loop
+        movlw           8
+        cpfslt          WREG4,0         ; if loop counter >=8 (register
+                                        ; length), return
+        return
+
+        movlw           4
+        cmp_fw_ifne     WREG4           ; if loop counter !=4 (nybble length),
+                                        ; skip insertion of extra black space
+        goto            not_nybble_boundary
+        call            waiting
+
+not_nybble_boundary
+        rlncf           WREG2,1         ; top bit goes into N flag,   
+                                        ; ie Negative if 1
+        bn              register_readout_if_led_1
+
+register_readout_if_led_0
+        call            led_red
+        bra             register_readout_endif_led
+
+register_readout_if_led_1
+        call            led_green
+
+register_readout_endif_led
+        incf            WREG4,1,0       ; increment loop counter
+        call            waiting
+        call            led_black
+        call            waiting
+        bra             register_readout_loop
+
+
+;****************************************************************************
+vector_interrupt_low
+; checks which interrupt and as soon as it finds one jumps straight
+; to the relevant ISR.  That routine will return with retfie and if
+; there was another interrupt we will re-enter, which is OK.
+
+       btfsc   PIR1,SSPIF,0    ; check if MSSP interrupt generated, if so
+;      goto    i2c_isr         ; I2C ISR will check whether master or slave
+       goto    panic           ; nothing should generate these ATM....
+
+        btfsc   PIR1,5,0        ; check for serial receive interrupt
+       goto    serial_rx_isr   ; receive serial
+
+       debug   'L'             ; else panic - interrupt but don't know why
+       goto    panic
+
+;----------------------------------------
+enable_interrupts
+;      globally enable interrupts - p77
+;      etc.
+
+       bsf     RCON,7,0        ; enable priority levels
+       bsf     INTCON,7,0      ; enable high-priority interrupts
+       bsf     INTCON,6,0      ; enable low-priority interrupts
+       bcf     PIE1,3,0        ; disable master synchronous serial port
+                               ; (MSSP; i.e. enable i2c) interrupts
+                               ; (temporary for this simple program)
+       bsf     PIE1,5,0        ; enable USART receive interrupt (p85)
+       return
+
+;****************************************************************************
+vector_interrupt_high
+       call    led_red
+       goto    vector_interrupt_high
+
+;***************************************************************************(
+; FUNCTIONALITY
+; these routines actually glue things together to make something that
+; does something
+
+;----------------------------------------
+master_main
+;      main program for master PIC
+
+       call    led_green
+
+master_main_loop
+       goto    master_main_loop
+
+
+;----------------------------------------
+slave_main
+;      main program for slave PICs
+
+       bcf     PIE1,5,0        ; disable serial receive interrupt
+       bcf     PIE1,4,0        ; disable serial transmit interrupt
+       call    led_red
+       debug   'S'
+
+slave_main_loop
+       call    wait_for_i2c_interrupt  ; wait for 1st (address) byte
+       call    led_green
+       debug   'G'
+       call    wait_for_i2c_interrupt  ; wait for 2nd (data) byte
+       call    led_black
+       debug   'B'
+       goto    slave_main_loop
+
+;----------------------------------------
+serial_rx_isr
+       call    led_black
+
+       debug   'd'
+
+;      what we actually do here is faff with I2C to start transmitting
+       bsf     SSPCON2,SEN,0           ; i2c START
+       call    wait_for_i2c_interrupt
+
+       debug   'e'
+
+       movlw   0x82                    ; transmit 1000 0010
+       movwf   SSPBUF,0                ; (ie address 1000001, read=0)
+
+       call    wait_for_i2c_interrupt
+
+       debug   'f'
+
+       ifbit1  SSPCON2,ACKSTAT         ; check for ack from slave (=0), if no
+       goto    panic                   ; then panic, else
+
+       debug   'g'
+
+       movff   RCREG,SSPBUF            ; copy byte from serial to i2c buffer
+       call    wait_for_i2c_interrupt
+       btfsc   SSPCON2,ACKSTAT,0       ; check for ack from slave (=0), if no
+       goto    panic                   ; then panic, else
+       bsf     SSPCON2,PEN,0           ; i2c STOP
+       call    wait_for_i2c_interrupt
+
+       retfie
+
+;***************************************************************************
+; SERIAL PORT
+
+;--------------------
+serial_setup
+;      sets up the serial port, 9600 8N1 etc. as required by host
+;      interrupt is enabled for reception but not transmission
+
+; initial config - TXSTA register p181
+        bcf     TXSTA,6,0      ; p181, set 8-bit mode
+       bsf     TXSTA,5,0       ; transmit enable
+       bcf     TXSTA,4,0       ; asynchronous mode
+       bsf     TXSTA,2,0       ; set high baud rate
+       
+; initial config - RCSTA register p182
+        bsf    RCSTA,7,0       ; serial port enable (p182)
+       bcf     RCSTA,6,0       ; 8-bit reception
+       bsf     RCSTA,4,0       ; enable continuous receive
+
+; set SPBRG to get correct baud rate according to table top right p186
+; (Tosc = 20MHz, desired baud rate = 9600)
+       bsf     SPBRG,7,0
+       bsf     SPBRG,0,0
+
+; interrupt set-up for serial receive
+       bcf     IPR1,5,0        ; set to low-priority interrupt
+       return
+
+;--------------------
+polling_serial_transmit
+;      writes W through the serial port
+;      serial port hardware must be suitably initialised
+;      serial port transmit interrupts must be disabled
+;      will spin until the byte is transmitted
+;              Before          After
+;      W       byte to xmit    preserved
+
+       movwf   TXREG,0         ; move contents of W (i.e. debugvalue)
+                               ;       to TXREG for transmission
+debug_waitfortsr_loop
+       btfss   TXSTA,1,0
+       bra     debug_waitfortsr_loop
+
+       return
+
+;****************************************************************************
+
+       code
+
+;***************************************************************************
+; FLASH ID LOCATIONS
+
+;--------------------
+copy_per_pic_data
+;      copies PIC-dependent info out of flash memory to RAM
+;      see README.protocol
+
+       movlw   (F_PIC_NO >> 16) & 0xff ; set table pointer to point to
+       movwf   TBLPTRU                 ; PIC number in flash
+       movlw   (F_PIC_NO >> 8) & 0xff
+       movwf   TBLPTRH
+       movlw   F_PIC_NO & 0xff
+       movwf   TBLPTRL
+
+       tblrd   *+              ; read then increment pointer 
+                               ; (now points to i2c control byte)
+
+       banksel PIC_NO
+        movf    TABLAT,0,0      ; move pic number into normal memory
+        movwf   PIC_NO,1
+
+       iorlw   '0'
+       call    polling_serial_transmit
+
+        tblrd   *               ; read i2c
+
+        movf    TABLAT,0,0      ; move i2c_ctrl byte into normal memory
+        movwf   I2C_CTRL,1
+; now have: PIC number in 400h, i2c control byte in 401h - see
+; RAM variables re i2c specific stuff, above
+
+       iorlw   '0'
+       call    polling_serial_transmit
+
+       return
+
+;***************************************************************************
+; I2C
+
+;--------------------
+i2c_setup
+;      sets up the I2C interface
+
+; see also:
+; p68
+; p314
+; p 275 ID locs
+
+; To generate our I2C address, we take PIC_NO bits 4-0 and prepend
+; 0b10 (i.e. all addresses are of the form 0b10xxxxx)
+       banksel PIC_NO          ; ser BSR=i2c BSR (4)
+
+; common to master and slaves:
+       bsf     SSPSTAT,7,0     ; disable slew rate control
+       bcf     SSPSTAT,6,0     ; disable SMBus specific commands
+                               ; (whatever that means)
+       bcf     SSPCON2,7,0     ; disable general call (for now)
+
+       bcf     IPR1,SSPIP,0    ; make interrupt low priority
+
+; are we master or slave ?
+       btfsc   I2C_CTRL,I2C_CTRL_MASTER,1      ; test whether PIC is master
+       goto    i2c_setup_if_master
+       goto    i2c_setup_if_slave
+
+i2c_setup_if_master
+       movlw   0x08            ; clear top 2 status bits; disable SSP;
+       movwf   SSPCON1,0       ;  CKP unused, set to 0; master mode.
+
+; set baud rate
+       movlw   100-1
+       movwf   SSPADD,0        ; set baud rate; clock=Fosc/(4*(SSPADD+1))
+                               ; Fosc=20MHz, currently want clock=50kHz
+                               ; => SSPADD=99
+
+       goto    i2c_setup_endif_master_slave
+
+i2c_setup_if_slave
+       movlw   0x16            ; clear top 2 status bits; disable SSP;
+       movwf   SSPCON1,0       ;  release clock; 7bit slave mode with
+                               ;  no extra start/stop interrupts.
+;      !!fixme probably want to set SSPCON2:SEN "clock stretching"
+
+; set slave address
+       banksel PIC_NO          ; set BSR=i2c BSR (4)
+       movf    PIC_NO,0,1      ; copy pic_no to W (000xxxxx)
+       iorlw   0x40            ; change top 3 bits t 010 (010xxxxx)
+       rlncf   WREG,0,0        ; shift, bottom bit is r/w (10xxxxx0)
+       movwf   SSPADD,0        ; move to slave address register 
+                               ; (bits 7-1=address, bit 0=0)
+
+i2c_setup_endif_master_slave
+       bsf     SSPCON1,5,0     ; enable I2C mode
+
+       return
+
+;----------------------------------------
+i2c_isr
+       banksel PIC_NO                  ; ser BSR=i2c BSR (4)
+       btfsc   I2C_CTRL,I2C_CTRL_MASTER,1 ; check =master?, if so
+       goto    i2c_master_isr          ; goto master interrupt routine
+       goto    i2c_slave_isr           ; elso goto interrupt_slave
+
+;--------------------
+i2c_master_isr
+       debug   'm'
+       goto    vector_panic
+
+;--------------------
+i2c_slave_isr
+       debug   's'
+       goto    vector_panic
+
+;----------------------------------------
+wait_for_i2c_interrupt
+;      polls the relevant bit until the I2C interrupt flag is set,
+;      then returns.  should not usually be used if I2C interrupts
+;      are enabled, clearly.
+
+       debug   '.'
+wait_for_i2c_interrupt_loop
+       btfss   PIR1,SSPIF,0    ; check if interrupt set, if not, loop
+       goto    wait_for_i2c_interrupt_loop
+
+       bcf     PIR1,SSPIF,0    ; clear interrupt bit
+
+       debug   'I'
+       debughf SSPSTAT
+       debughf SSPCON1
+       debughf SSPCON2
+       
+       return
+
+;****************************************************************************
+; GENERAL SUBROUTINES
+
+;----------------------------------------
+waiting
+; waits for a fixed interval, depending on the configuration of TMR0
+
+        bcf     INTCON,2,0      ; clear timer0 interrupt bit (p109)
+        clrf    TMR0H,0         ; p107 set high byte of timer0 to 0 (buffered,
+                                ; only actually set when write to tmr0l occurs)
+        clrf    TMR0L,0         ; set timer0 low byte - timer now set to 0000h
+loop
+        btfss   INTCON,2,0      ; check whether timer0 interrupt has been set -
+                                ; skip next instruction if so
+        bra     loop
+        return
+
+
+;****************************************************************************
+
+        org 0x2000
+        dw      0xffff
+
+        org 0x6000
+        dw      0xffff
+
+        end
+