;***************************************************************************************** ; I/O Expander, v1.0 ; G. Heron, N2APB n2apb@amsat.org ; ; v1.0 First public release. ; ; Copyright 2002, George L. Heron. All rights reserved. ; ;***************************************************************************************** device SX28L,oscxt4,turbo,stackx_optionx ; SX-Key device directives freq 50_000_000 ; default run speed = 50MHz id 'IOX-v1.0' ; reset reset_entry ; set reset vector ;***************************************************************************************** ; ; Global Register definitions org $08 ; start of program registers isr_temp ds 1 ; temp variable used by the ISR flags ds 1 ; Flags to indicate various things timer_flag equ flags.0 ; Indicates a 16-bit timer rollover rx_flag equ flags.1 ; Indicates the reception of a byte from the UART 1 counter_flag equ flags.2 ; Indicates counter mode (vs serial mode) temp ds 1 ; temp variables LCD_char ds 1 temp1 ds 1 RTCCsave ds 1 count_lo ds 1 count_hi ds 1 ;***************************************************************************************** ; Watch statements (to view variable in debug screen) watch RTCC,8,uhex watch count_lo,8,uhex watch count_hi,8,uhex ;***************************************************************************************** ; RAM Bank Register definitions ; Bank 0 org $10 wcntr0 ds 1 ; wait counters wcntr1 ds 1 wcntr2 ds 1 wcntr3 ds 1 wcntr4 ds 1 Count_On ds 1 ; hold settable Counter on/off bit patterns Count_Off ds 1 WiperCount ds 1 ; number of times pot wiper is asked to be moved ; Bank 1 org $30 serial = $ ; UART bank tx_high ds 1 ; hi byte to transmit tx_low ds 1 ; low byte to transmit tx_count ds 1 ; number of bits sent tx_divide ds 1 ; xmit timing (/16) counter rx_count ds 1 ; number of bits received rx_divide ds 1 ; receive timing counter rx_byte ds 1 ; buffer for incoming byte string ds 1 ; used by send_string to store the address in memory byte ds 1 ; used by serial routines hex ds 1 ; used in send_hex and get_hex routines timers = $ ; Bank 2 org $50 math = $ bin_number ds 4 bcd_number ds 5 count ds 1 tempm ds 1 ; Bank 3 org $70 Keypad = $ Row ds 1 Key ds 1 Key_Index ds 1 ADC_value ds 1 ; Bank 4 org $90 ; Bank 5 org $b0 ; Bank 6 org $d0 ; Bank 7 org $f0 read_buffer = $ ;***************************************************************************************** ; Port Assignment RA_init equ %1111 RA_io equ %0110 ; b3(out) b2(in) b1(in) b0(out) RB_init equ %11111111 RB_io equ %11100000 ; define PortB 0..4 as outputs, 5..7 as inputs RC_init equ %11111111 RC_io equ %00000000 ; define PortC as all output LCD_e equ rc.3 LCD_rw equ rc.2 LCD_rs equ rc.1 ;************************************************************************** ; System Equates rx_pin equ ra.1 ; UART receive input tx_pin equ ra.0 ; UART transmit output WAIT_HI equ $40 ; wait loop high byte WAIT_LO equ $40 ; wait loop low byte ACK equ $01 PotDirection equ rb.0 ; up (1), down (0) PotClock equ rc.0 Start_Convert equ rb.1 ; shared with LSB of keypad scan ADC_Data equ ra.2 ADC_clock equ ra.3 ;************************************************************************** ; Counter Equates ; RTW,RTI,RTS,RTE PSA,PS2,PS1,PS0 ; 1 = RTCC ; 0 = rollover interrupt enabled ; 1 = RTCC counts transition of input pin ; 0 = RTCC counts instruction cycles ; 1 = incr on hi-to-lo transition ; 1 = 1:1 divide rate ; 0 = Pre-scaler ; 0 1 0 = 1:4 COUNT_ON_1_1 equ %10111111 ; Counter On at 1:1 rate COUNT_OFF_1_1 equ %10011111 ; Counter Off at 1:1 rate COUNT_ON_1_4 equ %10110001 ; Counter On at 1:4 rate ;***************************************************************************************** ; UART Constants ; The following three values determine the UART baud rate. ; The value of baud_rate and int_period affect the baud rate as follows: ; Baud rate = 50MHz/(baud_rate * int_period * RTCC_prescaler) ; ; Note: *int_period must <256 and longer than the length of the slowest possible ; interrupt sequence in instruction cycles. Changing the value of int_period will ; affect the rest of the virtual peripherals due to timing issues. The start delay ; value must be set equal to (baud_rate)*1.5 + 1 ;********************************************************************************* baud_rate_24 = 96 ;for 2400 baud rate generation start_delay_24 = baud_rate_24+baud_rate_24/2+1 ;baud_rate_96 = 24 ;for 9600 baud rate generation ;start_delay_96 = baud_rate_96+baud_rate_96/2+1 int_period equ 217 ; RTCC interrupt rate ;***************************************************************************************** ; Interrupt Service Routine ; ; Note: The interrupt code must always originate at address $0. ; ; Interrupt Frequency = (Cycle Frequency / -(retiw value)) For example: ; With a retiw value of -217 and an oscillator frequency of 50MHz, this ; code runs every 4.34us. org $0 interrupt ; mov w,m ; Save the m register mov isr_temp,w sb counter_flag ; if counter mode jmp @transmit ; go do serial processing in page 3 (org 600) ; else we're counting incsz count_lo ; increment low byte counter reti inc count_hi ; if low passed 0, increment the high byte counter reti ; Set Interrupt Rate isr_end mov w,isr_temp ; Restore the m register. mov m,w ; mov w,#-int_period ; refresh RTCC on return retiw ; return from the interrupt ; = 1/(int_period*RTCC prescaler*1/50MHz) ; = 1/(217*1*20ns) = 4.34us ; End of the Interrupt Service Routine ;***************************************************************************************** ; RESET VECTOR -- Program execution begins here on power-up or after a reset reset_entry jmp @Initialize ; Initialize all ports, variables, modes ;***************************************************************************************** ; MAINLINE ;***************************************************************************************** Main call @ClearDisplay mov w,#_signon ; send title string call @DisplayString loop call @Get_Byte ; await command or data from host cje byte,#$FF,Ping_char ; if PING code received, ACK it cje byte,#$FE,@ProcessCommand ; if CMD code received, go process it jmp DisplayChar ; else must be char for display, go display it Ping_char call @ClearDisplay mov w,#_ping ; send ping msg to the LCD call @DisplayString mov w,#ACK ; send ACK response call @Send_Byte ; send to host jmp loop ; and go do again ; Incoming character should be send to the LCD DisplayChar mov LCD_char,byte call @Data2LCD jmp loop _signon dw 'IOX v0.9.0',0 _ping dw '-ping-',0 _blank_line dw ' ',0 ;********************************************************************************* org $200 ;********************************************************************************* ; Jump table for second half of page send_byte jmp send_byte_ get_byte jmp get_byte_ send2BCD jmp send2BCD_ MeasureFreqCmd jmp MeasureFreqCmd_ ReadOutFreqRegs jmp ReadOutFreqRegs_ ReadOutFreqString jmp ReadOutFreqString_ ReadKeypadCmd jmp ReadKeypadCmd_ CheckColumn jmp CheckColumn_ ;*************************************************************************** ; Init LCD ; Power on initialization of Liquid Crystal Display. ; The LCD controller chip must be equivalent to an Hitachi 44780. ; The LCD is assumed to be a 16 X 2 display. Init_LCD call @wait64ms mov rc,#$30 ; func set setb LCD_e call @wait64ms clrb LCD_e call @wait1us setb LCD_e call @wait1us mov rc,#$30 ; func set setb LCD_e call wait32ms clrb LCD_e call @wait1us setb LCD_e call @wait1us mov rc,#$30 ; func set setb LCD_e call @wait32ms clrb LCD_e call @wait1us mov rc,#$20 ; set 4-bit mode setb LCD_e call @wait16ms clrb LCD_e call @wait1us mov LCD_char,#$28 ; 1/16 duty cycle, 5x8 matrix call Cmd2LCD mov LCD_char,#$08 ; disp off, curs & blank off call Cmd2LCD mov LCD_char,#$01 ; clear & reset cursor call Cmd2LCD mov LCD_char,#$06 ; cursor moves right, no shift call Cmd2LCD mov LCD_char,#$0C ; display on, cursor & blink off call Cmd2LCD ; call BusyCheck ; make sure LCD is quiet and ready retp ;*************************************************************************** ;BusyCheck ; ;LCD read/write operations are slooooow, this subroutine ;polls the LCD busy flag to determine if previous operations are completed. ;Note side effect that the LCD_rw and LCD_rs are left in write data mode. BusyCheck call @wait5ms ret mov !rc,#$F0 ; tristate the 4 data pins clrb LCD_rs ; set up to read the busy flag setb LCD_rw ; raise the r/w bit to read the LCD call @wait1us :busy setb LCD_e call @wait1us mov temp1,rc ; read the status byte clrb LCD_e call @wait1us setb LCD_e ; get next nibble to keep LCD happy call @wait1us clrb LCD_e call @wait1us snb temp1.7 ; check for busy flag ... wait if set jmp :busy ret ;**************************************************************************** ; Send Character to LCD ; ; The character to be sent must have been placed in "LCD_char" prior to calling ; the subroutine. LCD_rw and LCD_rs must be set up prior to entry. Cmd2LCD clrb LCD_rs ; rs is low for cmnd call BusyCheck ; LCD ready for new data? clr rc mov !rc,#0 ; setup for all outputs clrb LCD_rw ; change LCD back to Write mode clrb LCD_rs ; ensure that rs is low for cmnd jmp write_LCD ; continue Data2LCD setb LCD_rs ; rs is hi for data call BusyCheck ; LCD ready for new data? clr rc mov !rc,#0 ; setup for all outputs clrb LCD_rw ; change LCD back to Write mode setb LCD_rs ; ensure that rs is hi for data write_LCD mov temp1,LCD_char ; copy char to be sent to LCD and rc,#$0F ; clear data nibble and temp1,#$F0 or rc,temp1 ; load first nibble setb LCD_e ; transfer first nibble call @wait1us clrb LCD_e mov temp1,LCD_char ; get char to be sent to LCD swap temp1 and rc,#$0F ; clear data nibble and temp1,#$F0 or rc,temp1 call @wait1us setb LCD_e ; transfer second nibble call @wait1us clrb LCD_e retp ;********************************************************************************* ; DisplayString - Displays null-terminated string pointed to by address in W register DisplayString mov temp,w ; store string address :loop mov w,temp ; read next string character mov m,#0 ; with indirect addressing (use page #) iread ; using the mode register mov m,#$0f ; reset the mode register test w ; are we at the last char? snz ; if not=0, skip ahead retp ; yes, leave & fix page bits mov LCD_char,w call Data2LCD ; not 0, so send character inc temp ; point to next character jmp :loop ; loop until done ;********************************************************************************* ; ClearDisplay -- Clears the LCD ClearDisplay mov LCD_char,#$01 call Cmd2LCD retp ;********************************************************************************* ; hex_table - Returns ASCII digit hex_table add pc,w retw '0' retw '1' retw '2' retw '3' retw '4' retw '5' retw '6' retw '7' retw '8' retw '9' retw 'A' retw 'B' retw 'C' retw 'D' retw 'E' retw 'F' ;********************************************************************************* ; Key Table - Returns the code of the Keypad press, per the Key_index used here to index Key_Table mov w,Key_Index add pc,w retw 1 retw 2 retw 3 retw 4 retw 5 retw 6 retw 7 retw 8 retw 9 retw 10 retw 0 retw 11 ;********************************************************************************* org $300 ;********************************************************************************* ;********************************************************************************* ; Send2BCD - Send w to host as 2 BCD numbers send2BCD_ mov temp,w call @Wait64ms mov w,<>temp and w,#$0f call hex_table call send_byte call @Wait64ms mov w,temp and w,#$0f call hex_table call send_byte call @Wait64ms retp ;********************************************************************************* ; Function: send_byte - Send w via serial port send_byte_ bank Serial :wait test Tx_Count ; wait for not busy sz jmp :wait not w ; ready bits (inverse logic) mov Tx_High,w ; store data byte setb Tx_Low.7 ; set up start bit mov Tx_Count,#10 ; 1 start + 8 data + 1 stop bit retp ; leave and fix page bits ;********************************************************************************* ; Get_Byte - Get byte via serial port and return in Byte Get_Byte_ sb Rx_Flag ; wait till byte is received jmp $-1 clrb Rx_Flag ; reset the receive flag bank Serial mov Byte,Rx_Byte ; store incoming byte in Byte retp ;********************************************************************************* ; MeasureFreqCmd - Toggles the system from "serial ISR RTCC instruction rollover" mode ; to "counter RTCC event count" mode, waits the gating period, and ; then switches the interrupt mechanism back. MeasureFreqCmd_ clr RTCC clr count_lo clr count_hi setb counter_flag ; counter mode (i.e., no ISR serial processing) bank 0 mov !option,Count_On ; rtcc counts transitions of RTCC pin (disables serial ISR) call @Wait1sec clrb counter_flag ; stop counting mov RTCCsave,RTCC bank 0 mov !option,Count_Off ; rtcc counts instruction cycle (enables serial ISR) retp ;********************************************************************************* ; ReadOutFreqRegs - Sends the 3 Frequency Counter registers to the host (LSB...MSB) ReadOutFreqRegs_ call @Wait64ms mov w,RTCCsave call @Send_Byte call @Wait10ms mov w,count_lo call @Send_Byte call @Wait10ms mov w,count_hi call @Send_Byte call @Wait10ms retp ;********************************************************************************* ; ReadOutFreqString Routine - converts 3 Freq counter regs to 8 BCD equivalent hex ; digits in 4 bytes then sends to host as 8 individual BCD chars. ReadOutFreqString_ bank math mov bin_number,RTCCsave ; load up LS byte counter (RTCC) mov bin_number+1,count_lo ; load up Middle bytye counter (count_lo) mov bin_number+2,count_hi ; load up MS byte counter (count_hi) clr bin_number+3 call @bindec ; convert 3 binary counters in [bin_number+2,1,0] to ; eight hex decimal digits in [bcd_number+3,2,1,0] bank math mov w,bcd_number+3 call @Send2BCD ; send 2 bytes representing BCD values of bcd_number+3 bank math mov w,bcd_number+2 call @Send2BCD ; send 2 bytes representing BCD values of bcd_number+2 bank math mov w,bcd_number+1 call @Send2BCD ; send 2 bytes representing BCD values of bcd_number+1 bank math mov w,bcd_number call @Send2BCD ; send 2 bytes representing BCD values of bcd_number+0 retp ;********************************************************************************* ; ReadKeypadCmd - ReadKeypadCmd_ bank Keypad mov Key,#$FF ; set Key to "not pressed" to start clr Key_Index CheckRow1 mov Row,#1 clrb rb.1 ; strobe row 1 call CheckColumn ; check for any key closures setb rb.1 bank Keypad cje Key,#$FF,CheckRow2 ; no keypress found ye, continue retp ; keypress found in this row, return with Key set CheckRow2 inc Row clrb rb.2 ; strobe row 2 call CheckColumn ; check for any key closures setb rb.2 bank Keypad cje Key,#$FF,CheckRow3 ; no keypress found yet, continue retp ; keypress found in this row, return with Key set CheckRow3 inc Row clrb rb.3 ; strobe row 3 call CheckColumn ; check for any key closures setb rb.3 bank Keypad cje Key,#$FF,CheckRow4 ; no keypress found yet, continue retp ; keypress found in this row, return with Key set CheckRow4 inc Row clrb rb.4 ; strobe row 4 call CheckColumn ; check for any key closures setb rb.4 retp ; return with Key set CheckColumn_ sb rb.5 jmp KeyFound inc Key_Index sb rb.6 jmp KeyFound inc Key_Index sb rb.7 jmp KeyFound inc Key_Index ret KeyFound call @Wait10ms ; debounce bank Keypad call Key_Table mov Key,w ret ;********************************************************************************* org $400 ;********************************************************************************* TogglePot jmp TogglePot_ Get_ADC jmp Get_ADC_ Clock_ADC jmp Clock_ADC_ Get_ADC_Bit jmp Get_ADC_Bit_ ;********************************************************************************* ; BinDec - 32 bit binary to BCD conversion ; entry: 32 bit binary number in $10-13 ; exit: 10 digit BCD number in $14-18 ; algorithm= shift the bits of binary number into the BCD number and decimal ; correct on the way bindec mov count,#32 mov fsr,#bcd_number ; points to the BCD result clr_bcd clr ind ; clear BCD number snb fsr.3 ; reached $18? jmp shift_both ; yes, begin algorithm inc fsr ; no, continue on next byte jmp clr_bcd ; loop to clear shift_both mov fsr,#bin_number ; points to the binary number input clc ; clear carry, prepare for shifting shift_loop rl ind ; shift the number left snb fsr.3 ; reached $18? (finish shifting both numbers) jmp check_adj ; yes, check if end of everything inc fsr ; no, next byte jmp shift_loop ; not yet check_adj decsz count ; end of 32 bit operation? jmp bcd_adj ; no, do bcd adj retp bcd_adj mov fsr,#bcd_number ; points to first byte of the BCD result bcd_adj_loop call digit_adj ; decimal adjust snb fsr.3 ; reached last byte? jmp shift_both ; yes, go to shift both number left again inc fsr ; no, next byte jmp bcd_adj_loop ; looping for decimal adjust ; prepare for next shift ; 0000 --> 0000 0 -->0 ; 0001 --> 0010 1 -->2 ; 0010 --> 0100 2 -->4 ; 0011 --> 0110 3 -->6 ; 0100 --> 1000 4 -->8 ; 0101 --> 1010 5 -->A, correct result is 10, so need to add 3 ; so that 5+3=8, and 1000 will be shifted to be 1 0000 ; the same is true for 6-9 digit_adj ; consider LSD first mov w,#3 ; 3 will become 6 on next shift add w,ind ; which is the decimal correct factor to be added mov tempm,w snb tempm.3 ; > 7? if bit 3 not set, then must be <=7, no adj. mov ind,w ; yes, decimal adjust needed, so store it ; now for the MSD mov w,#$30 ; 3 for MSD is $30 add w,ind ; add for testing mov tempm,w snb tempm.7 ; > 7? mov ind,w ; yes, store it ret ;*************************************************************************************** ; WAIT ROUTINES ;********************* ; Wait 1 sec wait1sec bank 0 mov wcntr4,#100 :wloop call wait10ms decsz wcntr4 jmp :wloop retp ;******************* ; wait 640ms wait640ms bank 0 mov wcntr4,#10 :wloop call wait64ms decsz wcntr4 jmp :wloop retp ;******************* ; wait 64ms wait64ms bank 0 mov wcntr3,#64 :wloop call wait1ms decsz wcntr3 jmp :wloop retp ;******************* ; wait 32ms wait32ms bank 0 mov wcntr3,#32 :wloop call wait1ms decsz wcntr3 jmp :wloop retp ;******************* ; wait 16ms wait16ms bank 0 mov wcntr3,#16 :wloop call wait1ms decsz wcntr3 jmp :wloop retp ;******************* ; wait 10ms wait10ms bank 0 mov wcntr2,#100 :wloop call wait100us decsz wcntr2 jmp :wloop retp ;******************* ; wait 5ms wait5ms bank 0 mov wcntr3,#5 :wloop call wait1ms decsz wcntr3 jmp :wloop retp ;******************* ; wait 1ms wait1ms bank 0 mov wcntr2,#10 :wloop call wait100us decsz wcntr2 jmp :wloop retp ;******************* ; wait 100us wait100us bank 0 mov wcntr1,#100 :wloop call wait1us decsz wcntr1 jmp :wloop retp ;******************* ; wait 1us wait1us bank 0 mov wcntr0,#$09 nop nop nop :wloop decsz wcntr0 jmp :wloop retp ;********************************************************************************* org $500 ;********************************************************************************* ;********************************************************************************* ; Virtual Peripheral: Universal Asynchronous Receiver Transmitter (UART) ; These routines send and receive RS232C serial data, and are currently ; configured (though modifications can be made) for the popular ; "No parity-checking, 8 data bit, 1 stop bit" (N,8,1) data format. ; RECEIVING: The rx_flag is set high whenever a valid byte of data has been ; received and it the calling routine's responsibility to reset this flag ; once the incoming data has been collected. ; TRANSMITTING: The transmit routine requires the data to be inverted ; and loaded (tx_high+tx_low) register pair (with the inverted 8 data bits ; stored in tx_high and tx_low bit 7 set high to act as a start bit). Then ; the number of bits ready for transmission (10=1 start + 8 data + 1 stop) ; must be loaded into the tx_count register. As soon as this latter is done, ; the transmit routine immediately begins sending the data. ; This routine has a varying execution rate and therefore should always be ; placed after any timing-critical virtual peripherals such as timers, ; adcs, pwms, etc. ; Note: The transmit and receive routines are independent and either may be ; removed, if not needed, to reduce execution time and memory usage, ; as long as the initial "BANK serial" (common) instruction is kept. ; ; Input variable(s) : tx_low, tx_high, tx_count ; Output variable(s) : rx_flag, rx_byte ; Variable(s) affected : tx_divide, rx_divide, rx_count ; Flag(s) affected : rx_flag transmit bank serial ;switch to serial register bank decsz tx_divide ;only execute the transmit routine jmp :receive ; mov w,#baud_rate_24 ;load UART 1 baud rate mov tx_divide,w ; test tx_count ;are we sending? snz ; jmp :receive ; clc ;yes, ready stop bit rr tx_high ; and shift to next bit rr tx_low ; dec tx_count ;decrement bit counter snb tx_low.6 ;output next bit clrb tx_pin ; sb tx_low.6 ; setb tx_pin ; :receive sb rx_pin ;get current rx bit clc ; snb rx_pin ; stc ; test rx_count ;currently receiving byte? sz ; jmp :rxbit ;if so, jump ahead mov w,#9 ;in case start, ready 9 bits sc ;skip ahead if not start bit mov rx_count,w ;it is, so renew bit count mov w,#start_delay_24 ;ready 1.5 bit periods mov rx_divide,w ; :rxbit decsz rx_divide ;middle of next bit? jmp :rxdone ;exit mov w,#baud_rate_24 ;yes, ready 1 bit period mov rx_divide,w ; dec rx_count ;last bit? sz ;if not rr rx_byte ; then save bit snz ;if so, setb rx_flag ; then set flag :rxdone ;else, exit jmp @isr_end ;********************************************************************************* ; INITIALIZE - Initialize the system ; Initialize all port configuration Initialize mov w,#$0f ; address the tri-state registers mov m,w mov w,#RA_init ; Initialize data latches for port A mov ra,w mov w,#RA_io ; Initialize DDIR for port A mov !ra,w mov w,#RB_init ; Initialize data latches for port B mov rb,w mov w,#$0E ; address the pull-up registers mov m,w mov !rb,#0 ; enable pull-ups on port B inputs mov w,#$0F ; point back to the tri-state registers mov m,w mov w,#RB_io ; Initialize DDIR for port B mov !rb,w mov w,#RC_init ; Initialize data latches for port C mov rc,w mov w,#RC_io ; Initialize DDIR for port C mov !rc,w ; Clear all Data RAM locations :cont clr fsr ; reset all ram banks :zero_ram sb fsr.4 ; are we on low half of bank? setb fsr.3 ; If so, don't touch regs 0-7 clr ind ; clear using indirect addressing incsz fsr ; repeat until done jmp :zero_ram clrb counter_flag ; not in counter mode to start ; Init Pot position to mid-scale ; clrb PotDirection ; first move to min position ; bank 0 ; mov WiperCount,#100 ; call TogglePot ; setb PotDirection ; now move to mid-position ; bank 0 ; mov WiperCount,#50 ; call @TogglePot ; Setup and enable RTCC interrupt bank 0 mov Count_On,#COUNT_ON_1_4 ; setup defaul 1:1 counter on/off bit patterns mov Count_Off,#COUNT_OFF_1_1 mov !option,Count_Off ; rtcc counts instruction cycle (enables serial ISR) call @Init_LCD jmp @main ;********************************************************************************* ; TogglePot - Toggle the PotClock line WiperCount times. ; Assumes PotDirection set prior to entry (1=up, 0=down). TogglePot_ clrb PotClock call @wait1ms setb PotClock bank 0 decsz WiperCount jmp TogglePot_ retp ;********************************************************************************* ; GetADC - Gets an A/D reading and returns it in ADC_value Get_ADC_ clrb Start_Convert ; start conversion call @Wait1us bank 3 clr ADC_value call @Clock_ADC ; issue start pulse call @Get_ADC_Bit ; get B7 call @Get_ADC_Bit ; get B6 call @Get_ADC_Bit ; get B5 call @Get_ADC_Bit ; get B4 call @Get_ADC_Bit ; get B3 call @Get_ADC_Bit ; get B2 call @Get_ADC_Bit ; get B1 call @Get_ADC_Bit ; get B0 call @Clock_ADC ; issue stop pulse ; call @Clock_ADC ; issue last pulse (?) setb Start_Convert ; end the conversion cycle retp Get_ADC_Bit_ call @Clock_ADC ; get bit bank 3 snb ADC_data jmp :here clc ; D0 = 0 ... clr carry & shift left into ADC_value rl ADC_value retp :here stc ; D0 = 1 ... set carry & shift left into ADC_value rl ADC_value retp Clock_ADC_ setb ADC_clock call @Wait1ms clrb ADC_clock call @Wait1ms retp ;********************************************************************************* org $600 ; COMMAND PROCESSORS ;********************************************************************************* ; Command code received ... determine specific command coming next ProcessCommand call @Get_Byte ; next byte coming is the specific command cje byte,#1,ClearCmd ; Clear Display cje byte,#2,ClearLine1 ; Clear Line 1 cje byte,#3,ClearLine2 ; Clear Line 2 cje byte,#12,UnBlankDisplay ; UnBlank Display cje byte,#8,BlankDisplay ; Blank Display cje byte,#12,HideCursor ; Hide Cursor cje byte,#15,ShowCursor ; Show Cursor (blinking) cje byte,#65,MeasureFreq ; Measure Freq cje byte,#66,ReadOutFreqRegisters ; ReadOut Freq Regs cje byte,#67,ReadOutFreqStringData ; ReadOut Freq String cje byte,#68,Set1_1prescaler ; Set 1:1 Counter prescaler cje byte,#69,Set1_4prescaler ; Set 1:4 Counter prescaler cje byte,#80,ReadADC ; Read A/D Converter cje byte,#90,SetPot ; Set Potentiometer cje byte,#91,IncPot ; Increment Potentiometer cje byte,#92,DecPot ; Decrement Potentiometer cje byte,#100,ReadKeypad ; read Keypad cje byte,#101,WaitKeypad ; wait for Keypad entry cje byte,#200,ResetCmd ; Reset IOX rl byte ; b7 set? (display positioning?) jnc @loop ; no, just await new cmd/data rl byte ; b6 set? (line 1 or line 2 positioning?) jnc Line1position ; place cursor at column [b5..b0] on Line 2 Line2position rr byte rr byte ; put column bits back into b5..b0 or byte,#$C0 mov LCD_char,byte call @Cmd2LCD call @Wait1ms jmp @loop Line1position rr byte rr byte ; put column bits back into b5..b0 or byte,#$80 mov LCD_char,byte call @Cmd2LCD call @Wait1ms jmp @loop ; COMMAND PROCESSORS ClearCmd mov LCD_char,#1 ; Clear the LCD call @Cmd2LCD jmp @loop ClearLine1 mov LCD_char,#$80 ; point to 1st char line 1 call @Cmd2LCD call @Wait1ms mov w,#_blank_line call @DisplayString mov LCD_char,#$80 ; leave cursor at home on line 1 call @Cmd2LCD jmp @loop ClearLine2 mov LCD_char,#$C0 ; point to 1st char line 2 call @Cmd2LCD call @Wait1ms mov w,#_blank_line call @DisplayString mov LCD_char,#$C0 ; leave cursor at home on line 22 call @Cmd2LCD jmp @loop BlankDisplay mov LCD_char,#8 ; Blank the LCD call @Cmd2LCD jmp @loop UnBlankDisplay mov LCD_char,#12 ; UnBlank the LCD call @Cmd2LCD jmp @loop ShowCursor mov LCD_char,#15 ; Show Cursor (blinking) call @Cmd2LCD call @Wait1ms jmp @loop HideCursor mov LCD_char,#12 ; Hide Cursor call @Cmd2LCD call @Wait1ms jmp @loop ReadKeypad call @ReadKeypadCmd ; Read Keypad Command call @Wait64ms bank Keypad mov w,Key call @Send_byte jmp @Loop WaitKeypad call @ReadKeypadCmd ; Wait Keypad Command bank Keypad cje Key,#$FF,WaitKeypad mov w,Key call @Send_Byte jmp @loop ;********************************************************************************** org $700 ;********************************************************************************** MeasureFreq call @MeasureFreqCmd ; Measure Frequency Command jmp @loop ReadOutFreqRegisters call @ReadOutFreqRegs ; Readout Frequency Registers jmp @Loop ReadOutFreqStringData call @ReadOutFreqString ; Readout Frequency String jmp @loop Set1_1prescaler bank 0 mov Count_On,#COUNT_ON_1_1 jmp @loop Set1_4prescaler bank 0 mov Count_On,#COUNT_ON_1_4 jmp @loop ReadADC call @Get_ADC bank 3 mov w,ADC_value call @Send_Byte jmp @loop SetPot call @Get_Byte ; get desired position of wiper jmp @loop IncPot call @Get_Byte ; get number of steps to increment mov w,byte bank 0 mov WiperCount,#1 setb PotDirection call @TogglePot jmp @loop DecPot call @Get_byte ; get number of steps to decrement mov w,byte bank 0 mov WiperCount,#1 clrb PotDirection call @TogglePot ; move the wiper jmp @loop ResetCmd bank 0 jmp @Reset_Entry ; reset the IOX software by restarting at top END ; End of program code