***** BM_11.ASM ************************************************ * ADC + Digital Input and Output Module for Brain Master Projcet * Lead by Thomas F. Collura Ph.D., P.E. * * Written by and (c) W. Robert S. Webber Ph.D. CEng. MIEE * * Squarey Basement Software * * Date Wed 6 Sept 1995 * * Copyright ======================================================== * * As with any freeware I would make no guarantee, warranty implied or * otherwise that the code is good for anything, will not harm anyone * however used. That is, what ever happens or does not happen as a * result of using or not using this code is not my fault or * responsibility. * * This program is licensed to Tom Collura and the Brain Master * project to be freely distributed as part of that project. * * Any derived work would be the property and responsibility of the * person deriving such work. An acknowledgement of the original * source would be appreciated. * * ================================================================= * Start of Genaral stuff * From BUF32.ASM *************** * EQUATES * *************** RAMBS EQU $0000 start of ram REGBS EQU $1000 start of registers ROMBS EQU $E000 start of rom STREE EQU $B600 start of eeprom ENDEE EQU $B7FF end of eeprom PORTE EQU REGBS+$0A port E CFORC EQU REGBS+$0B force output compare TCNT EQU REGBS+$0E timer count TOC5 EQU REGBS+$1E oc5 reg TCTL1 EQU REGBS+$20 timer control 1 TMSK1 EQU REGBS+$22 timer mask 1 TFLG1 EQU REGBS+$23 timer flag 1 TMSK2 EQU REGBS+$24 timer mask 2 BAUD EQU REGBS+$2B sci baud reg SCCR1 EQU REGBS+$2C sci control1 reg SCCR2 EQU REGBS+$2D sci control2 reg SCSR EQU REGBS+$2E sci status reg SCDAT EQU REGBS+$2F sci data reg BPROT EQU REGBS+$35 block protect reg OPTION EQU REGBS+$39 option reg COPRST EQU REGBS+$3A cop reset reg PPROG EQU REGBS+$3B ee prog reg HPRIO EQU REGBS+$3C hprio reg CONFIG EQU REGBS+$3F config register DFLOP EQU $4000 evb d flip flop DUART EQU $D000 duart address PORTA EQU DUART PORTB EQU DUART+8 ACIA EQU $9800 acia address PROMPT EQU '>' BUFFLNG EQU 35 CTLA EQU $01 exit host or assembler CTLB EQU $02 send break to host CTLW EQU $17 wait CTLX EQU $18 abort DEL EQU $7F abort EOT EQU $04 end of text/table SWI EQU $3F * End of section from BUF32.ASM BUFISIT EQU $e00A * Cold Start for Buffalo after testing PE0 TMP1 EQU $00C0 * For Buffalo for use with .HEXBIN SHFTREG EQU $009C * For Buffalo for use with .HEXBIN SHFTREG2 EQU $009D * For Buffalo for use with .HEXBIN CTLQ EQU $11 * Ctrl/Q Restart i.e. DC1 CTLS EQU $13 * Ctrl/S CTLV EQU $16 * Used instead of Ctrl/S for Pause CTLD EQU $04 * Ctrl/D Stop Interrupts & Return to Buffalo CR_KEY EQU $0D * Carridge Return TFLG2 EQU REGBS+$25 Timer Flag 2 PACTL EQU REGBS+$26 Pulse Accumulator Control Reg PORT_A EQU REGBS+$00 I/O Port A PORT_B EQU REGBS+$04 I/O Port B PORT_C EQU REGBS+$03 I/O Port C PORT_D EQU REGBS+$08 I/O Port D PORT_E EQU REGBS+$0A I/O Port E PIOC EQU REGBS+$02 STAF STAI CWOM HNDS OIN PLS EGA INVB PORTCTL EQU REGBS+$05 DDRC EQU REGBS+$07 DDRD EQU REGBS+$09 * ADC Registers ADCTL EQU REGBS+$30 ADC Control Register ADC_R1 EQU REGBS+$31 ADC Result 1 ADC_R2 EQU REGBS+$32 ADC Result 2 ADC_R3 EQU REGBS+$33 ADC Result 3 ADC_R4 EQU REGBS+$34 ADC Result 4 * Relative Register Addresses wrt to REGBS R_PORTE EQU $0A port E R_CFORC EQU $0B force output compare R_TCNT EQU $0E timer count R_TOC5 EQU $1E oc5 reg R_TCTL1 EQU $20 timer control 1 R_TMSK1 EQU $22 timer mask 1 R_TFLG1 EQU $23 timer flag 1 R_TMSK2 EQU $24 timer mask 2 R_TFLG2 EQU $25 Timer Flag 2 R_PACTL EQU $26 Pulse Accumulator Control Reg R_BAUD EQU $2B sci baud reg R_SCCR1 EQU $2C sci control1 reg R_SCCR2 EQU $2D sci control2 reg R_SCSR EQU $2E sci status reg R_SCDAT EQU $2F sci data reg R_OPTION EQU $39 option reg R_PORT_A EQU $00 Port A R_PORT_B EQU $04 Port B R_PORT_C EQU $03 Port C R_PORT_D EQU $08 Port D R_PORT_E EQU $0A Port E R_PIOC EQU $02 STAF STAI CWOM HNDS OIN PLS EGA INVB R_PORTCTL EQU $05 R_DDRC EQU $07 R_DDRD EQU $09 R_ADCTL EQU $30 ADC Control Register R_ADC_R1 EQU $31 ADC Result 1 R_ADC_R2 EQU $32 ADC Result 2 R_ADC_R3 EQU $33 ADC Result 3 R_ADC_R4 EQU $34 ADC Result 4 * For ADC Channels 0 to 3 ADC_NORM03 EQU $00 ADC_MULT03 EQU $10 ADC_SCAN03 EQU $20 ADC_MULT03SCAN EQU $30 * For ADC Cahnnels 4 to 7 ADC_NORM47 EQU $04 ADC_MULT47 EQU $14 ADC_SCAN47 EQU $24 ADC_MULT47SCAN EQU $34 * RTI Clock Rate for PACTL bits RTI0, RTI1 Note DDRA7 is also set $80 * so that Port A bit 7 is an Output * Given as time periods RTI_4.10 EQU $80 RTI_8.19 EQU $81 RTI_16.38 EQU $82 RTI_32.77 EQU $83 * Given as Sampling Frequencies RTI_244Hz EQU $80 RTI_122Hz EQU $81 RTI_61Hz EQU $82 RTI_31Hz EQU $83 * Entry points into Buffalo .WARMST EQU $FF7C .BPCLR EQU $FF7F .RPRINT EQU $FF82 .HEXBIN EQU $FF85 .BUFFAR EQU $FF88 .TERMAR EQU $FF8B .CHGBYT EQU $FF8E .READBU EQU $FF91 .INCBUF EQU $FF94 .DECBUF EQU $FF97 .WSKIP EQU $FF9A .CHKABR EQU $FF9D .UPCASE EQU $FFA0 .WCHEK EQU $FFA3 .DCHEK EQU $FFA6 .INIT EQU $FFA9 .INPUT EQU $FFAC .OUTPUT EQU $FFAF .OUTLHL EQU $FFB2 .OUTRHL EQU $FFB5 .OUTA EQU $FFB8 .OUT1BY EQU $FFBB .OUT1BS EQU $FFBE .OUT2BS EQU $FFC1 .OUTCRL EQU $FFC4 .OUTSTR EQU $FFC7 .OUTST0 EQU $FFCA .INCHAR EQU $FFCD .VECINT EQU $FFD0 * End of Genaral stuff for the ADC Module ADC_RDY EQU $80 * ADC Status bits in ADC_EN ADC_RUN EQU $01 **** Start of Jump Table for ADC Module for Brain Master ********** **** Program Starts here (Table of entry Points and Config values) org STREE * Start at base of EEPROM Block ($B600) jmp BUFISIT * In case PE0 is HIGH start Buffalo anyway ADC_INIT0: jmp ADC_INIT * Cold Start the ADC Module **** Tbale of Configuration Bytes ****************************** ADC_RATE: fcb RTI_122Hz * RTI Rate bits. Other Possible Values are: * RTI_244Hz RTI_122Hz RTI_61Hz RTI_31Hz * ADC Channel Enable bits in CHAN_EN CHAN_1 EQU $01 * Bit 0 = Chan 1 Enable ( ADC Input PE 0 ) CHAN_2 EQU $02 * Bit 1 = Chan 2 Enable ( ADC Input PE 1 ) CHAN_3 EQU $04 * Bit 2 = Chan 3 Enable ( ADC Input PE 2 ) CHAN_4 EQU $08 * Bit 3 = Chan 4 Enable ( ADC Input PE 3 ) CHAN_5 EQU $10 * Bit 4 = Chan 5 Enable ( ADC Input PE 4 ) CHAN_6 EQU $20 * Bit 5 = Chan 6 Enable ( ADC Input PE 5 ) CHAN_7 EQU $40 * Bit 6 = Chan 7 Enable ( ADC Input PE 6 ) CHAN_8 EQU $80 * Bit 7 = Chan 8 Enable ( ADC Input PE 7 ) * CHAN_EN0: fcb CHAN_1+CHAN_2+CHAN_3+CHAN_4 CHAN_EN0: fcb CHAN_1 * Mode Enable Bits in ADC_MODE * Enable Code 00 Hex (0000 0000 Binary) SEND_00 EQU $01 * Allows code 00 to be sent, * else code 00 is changed to 01 before sending. CRLF_ON EQU $02 * If set will send CR, LF before Reply Messages * Sync Protocol 0 Overrides other Sync protocols SYNC_NONE EQU $04 * No Sync Byte (Only useful for one channel * Sync Protocol 1 ( N Sync, 8-N Digital Input ) if SYNC_* clear SYNC_ALT EQU $08 * Bit 3 Sync Protocol 2, 8 Sync bits, 8 Dig Input Alt SYNC_BOTH EQU $10 * Bit 4 Sync Protocol 3, 8 Sync bits, 8 Dig Input Both START_ADC EQU $20 * Bit 5 Start up with ADC Running, else Startup Paused SIG_ON EQU $40 * Bit 6 Enable Sign On Copyright Message MSG_ON EQU $80 * Bit 7 Enable Messages NOT_PROT1 EQU SYNC_ALT+SYNC_BOTH * ADC_MODE: fcb MSG_ON+SIG_ON+SYNC_ALT+CRLF_ON ADC_MODE: fcb SYNC_NONE+START_ADC PROT_1_CT: fcb 3 * Range 2 to 8 * Protocol 1 Shift count for Sync_Count and Digital Input ( i.e. Port C ) * PROT_1_CT is the number of Sync_Count bits. * The Sync_Count and Port C bits are assembled into D=(A:B) * Then this value is shifted left by ( 8 - PROT_1_CT ) bits. * This moves some of Port C bits into A * and some Sync_Count bits out of A. The result is what is left in A. * In other words ( 8 - PROT_1_CT ) is the number of Dig Input bits and IDLE_PULSE: fcb 255 * Range 1 to 255 * Idle Pulse length in units of about 3.53 micro seconds. * For E Clock = 2MHz. A count of 255 is about 0.9 milli second. **** Table of Configurable Command Keys ****************************** * These key values may be replaced if desired. RESUME_KEY: fcb CTLQ * Resume ADC Character. Pause to Run State PAUSE_KEY: fcb CTLV * Pause ADC Character (Ints still on) Run to Pause State STOP_KEY: fcb CTLD * Stop Character. Disable Interrupts Return to Buffalo **** Messages Table ************************************************** * These messages may be over written if desired. But must NOT * be made Longer and must end with EOT. M_ADC_PAUSE: fcc 'ADC_P' fcb EOT M_ADC_STOP: fcc 'ADC_S' fcb EOT M_ADC_RUN: fcc 'ADC_R' fcb EOT **** Cold Start the ADC Module ****************************** ADC_INIT: ldx #REGBS * Point to Register Base bset R_TMSK2,X $40 * Set Bit RTII ldaa R_PACTL,X * Set RTI Rate anda $FC ora ADC_RATE staa R_PACTL,X ldaa #$7E * Load Jump Instruction staa $00EB * and save Vection Table ldd #ADC_ISR * Load ADC_ISR Address staa $00EC * and save Hi byte in Vection Table stab $00ED * and save Low byte in Vection Table ldx #REGBS * Point to Register Base ldaa #$00 * Simple i/o on Port C CWOM=0 HNDS=0 staa R_PIOC,X ldaa #$00 * Set Port C Bits 0-7 In staa R_DDRC,X ldaa ADC_MODE * Set up Sync Count Mask anda #NOT_PROT1 beq SET_SYNC1 ldaa #$FF bra SET_SYNC2 SET_SYNC1: ldx #SYNC_MSK_TBL * Setup Sync Count Mask Value jsr GET_P1_SH * Get Protocol Sync Shift Count and add to X ldaa $00,X SET_SYNC2: staa SYNC_MSK ldy #ADC_MODE brclr $00,Y SIG_ON NO_SIG_ON ldx #M_SIGON bsr MSG_OUT NO_SIG_ON: ldx #M_ADC_RUN bsr MSG_OUT clr SYNC_CT * clear the ADC Sync Count clra brclr $00,Y START_ADC GO_PAUSE ldaa #ADC_RUN GO_PAUSE: staa ADC_EN cli * Enable Intrrupts **** Poll Input for Command Keys ****************************** ADC_MON: ldx #ADC_MODE * inc PORT_C * Debug Show we are in polling loop jsr .INPUT cmpa STOP_KEY BEQ ADC_EXIT cmpa PAUSE_KEY BEQ ADC_PAUSE cmpa RESUME_KEY BEQ ADC_RESUME cmpa #CR_KEY BEQ DIG_OUT **** Still Here, Read as Hex and store in SHFTREG2 jsr .HEXBIN * clr PORT_C * Debug Show we are in polling loop bra ADC_MON DIG_OUT: ldaa SHFTREG2 staa PORT_B bra ADC_MON ADC_RESUME: ldx #M_ADC_RUN bsr MSG_OUT clr SYNC_CT * clear the ADC Sync Count ldaa #ADC_RUN * Re-enable ADC staa ADC_EN bra ADC_MON ADC_PAUSE: clr ADC_EN ldx #M_ADC_PAUSE bsr MSG_OUT bra ADC_MON ADC_EXIT: sei * Set Interrupt Mask ON clr ADC_EN ldx #REGBS * Point to Register Base bclr R_TMSK2,X $40 * Clear Bit RTII ldx #M_ADC_STOP bsr MSG_OUT jmp .WARMST * Return to Buffalo Monitor **** Output Message only if enabled ************************ * X Must point to message on input MSG_OUT: ldy #ADC_MODE brclr 0,Y MSG_ON SKIP_MSG brset 0,Y CRLF_ON CRLF_MSG jsr .OUTST0 * No CR LF Before Message rts CRLF_MSG: jsr .OUTSTR * Send CR LF before Message SKIP_MSG: rts **** Get Protocol 1 Sync Count Shift Value in B & add to X ********* * B is PROT_1_CT in it on exit GET_P1_SH: ldab PROT_1_CT * Get Shift Count in B decb * Adjust from 1 base to Zero Base andb #$07 * Force into range 0 to 7 abx * Add to X rts **** ADC Module Inrerrupt Service Routine ***************** * All Registers saved on Stack by Interrupt h/w in 68HC11 ADC_ISR: EQU * ldaa #$80 staa PORT_A * Show Start of ISR on Port A bit 7 ldx #ADC_EN * Check if ADC Scan Enabled brset $00,X ADC_RUN ADC_ISR1 ldab IDLE_PULSE IDLE: asla * do something decb bne IDLE * Loop till done bra END_ISR ***** Send Sync Byte First ****************************** ADC_ISR1: ldx #SYNC_CT * Point to ADC Sync Count ldaa $00,X * Get Sync Count in A SYNC_SKP: inca * Step on to next Count anda SYNC_MSK * Check if actual bits used are <> 0 cmpa #$FF * Also skip Count 255 beq SYNC_SKP * as Protocol 2 would need to send a value for 256 (Digital In) but 256 is * zero in 8 bits and zero is not allowed. * Protocol 2 needs to send a sync byte for * every Digital input byte alternating. Since only odd values are used for * sync count, there nedds to be the same number of even Sync counts * where Digital Input is sent, hence skip 255 as 0 is also skipped. tsta * Skip Sync Count = 0 for bits used bne SYNC_OK inca SYNC_OK: staa $00,X * Put back in main memory ldx #ADC_MODE brset $00,X SYNC_NONE SYNC_P0 brset $00,X SYNC_ALT SYNC_P2 brset $00,X SYNC_BOTH SYNC_P3 * Sync Protocol 1 is: * PROT_1_CT = Number of bits of Sync_Count (Range 2 to 8) * ( 8 - PROT_1_CT ) bits of Digital input from Port C * Sync_Count that ramps up 1 to 2^PROT_1_CT - 1 incrmenting by one * for each scan of the ADC chans in the ADC_ISR. After max count * it goes back to 1. ldab PORT_C * Get Input bits from Port C to B * D=(A:B)= Sync_Count : Digital_Input (Port_C) * b15.....b8 : b7................. b0 psha * Save on stack pshb * This is a case statement where a jump is calculated ldx #SHIFT_N * Get Start of Shift Table in X bsr GET_P1_SH * Get Protocol Sync Shift Count & Add to X pulb * recover D=(A:B)= Sync_Count:Port C pula jmp 0,X * Cross Fingers and Jump to Shift line * Start of Shift line Shift PROT_1_CT No. No. * on D Value Sync Cnt Dig Input * =(A:B) Bits Bits SHIFT_N: nop * 6 1 2 6 asld * 6 2 2 6 asld * 5 3 3 5 asld * 4 4 4 4 asld * 3 5 5 3 asld * 2 6 6 2 asld * 1 7 7 1 nop * 0 8 8 0 bra ADC_ISR2 * Sync Protocol 3 is: * Sync Count sent, all 8 bits every Sweep of ADC Chans * Range 1 to 254 in tseps of 1 (1,2,3,4,5, .. 253,254) * Sync count is never 0 or 255 * Digital Inputs sent every Sweep of ADC Chans SYNC_P3: bsr BYTE_OUT bra SEND_DIG * Sync Protocol 2 is: * If Sync Count is odd send Sync Count all 8 bits. * Range 1 to 253 in steps of 2. (1,3,5,7.. 251,253) * Note: an Even Sync Count is never sent. * Sync Count bit 0 is always set when set. * If Sync Count is even send Digital Input (Port C) all 8 bits. SYNC_P2: tab * save Sync count in B to test Bit 0 andb #$01 * Test if Sync Count is ODD bne ADC_ISR2 * Send Sync Count SEND_DIG: ldaa PORT_C * Else send Port C all 8 bits ADC_ISR2: bsr BYTE_OUT * Send out the Sync Byte. **** Start Scanning ADC Channels ************************************** SYNC_P0: lda #ADC_MULT03 * Set ADC to SCAN All 4 Channels (0 to 3) staa ADCTL * Start ADC on 4 Channels ldaa CHAN_EN0 * Get enable Flags for Chans 0-3 in A bsr ADC_LOOP lda #ADC_MULT47 * Set ADC to SCAN All 4 Channels (4 to 7) staa ADCTL ldaa CHAN_EN0 * Get enable Flags for Chans 4-7 lsra * Shift to bits 0-3 in A lsra lsra lsra bsr ADC_LOOP END_ISR: ldx #REGBS * Signal End of ISR to Real Time Clock bclr R_TFLG2,X $3F clr PORT_A * Show End of ISR on Port A bit 7 rti * End of ISR ********************************************************************** * Sends byte in Reg A to SCI BYTE_OUT: pshb * ldab #$02 * Debug * stab PORT_C * Debug ldab ADC_MODE * Check if allowed to send $00 andb #SEND_00 bne B_OUT2 tsta bne B_OUT2 inca B_OUT2: ldab SCSR * Read sci status reg bitb #$80 * loop until tdre=1 beq B_OUT2 nop * mimic timing of Buffalo Output routine staa SCDAT * Send Byte out * clr PORT_C * Debug pulb rts ********************************************************************** * Loop through 4 ADC Channels and test if each is enabled * Skip those that are not. * A, B, X all modified * A must be setup with Flag bits in low for positions (0-3) * for each of the channels to be sent out ADC_LOOP: EQU * * ldab #$04 * Debug * stab PORT_C * Debug staa CHAN_EN ldx #ADCTL ldab #$01 * Mask that is scanned through all channels ADC_WAIT: brclr $00,X ADC_RDY ADC_WAIT inx * Point X to ADC Results Registers NEXT_ADC: EQU * * ldaa #$04 * Debug * staa PORT_C * Debug tba * Get Chan Select Mask anda CHAN_EN * Test against Chan Enable Mask beq SKIP_CHAN ldaa $00,X * Get ADC value for Enabled chan bsr BYTE_OUT * and Send it out SKIP_CHAN: EQU * * clr PORT_C * Debug inx * Point to next channel aslb * Shit Select mask to next channel cmpb #$10 * Test Mask if end of loop blt NEXT_ADC rts **** Short Form Copy Right Message ****************************** M_SIGON: fcc 'BM_CR_WRSW&TFC' fcb EOT **** Table of Masks for Sync Count when < 8 bits used in count SYNC_MSK_TBL: fcb $03 * Shift 6 PROT_1_CT = 1 Sync 2 Dig In 6 fcb $03 * Shift 6 PROT_1_CT = 2 Sync 2 Dig In 6 fcb $07 * Shift 5 PROT_1_CT = 3 Sync 3 Dig In 5 fcb $0F * Shift 4 PROT_1_CT = 4 Sync 4 Dig In 4 fcb $1F * Shift 3 PROT_1_CT = 5 Sync 5 Dig In 3 fcb $3F * Shift 2 PROT_1_CT = 6 Sync 6 Dig In 2 fcb $7F * Shift 1 PROT_1_CT = 7 Sync 7 Dig In 1 fcb $FF * Shift 0 PROT_1_CT = 8 Sync 8 Dig In 0 **** RAM Table ******************************************************* org $0100 SYNC_CT: rmb 1 * ADC Sync Count Range 1 to 254 ADC_EN: rmb 1 * ADC Enable Flags Set Bit 0 = Run CHAN_EN: rmb 1 * ADC Channel Enables Bits 0-3 Only used SYNC_MSK: rmb 1 * Mask to check Sync Count when < 8 bits used **** end of File BM_11.ASM ****************************************