;*************************************************************************** ;* ;* Title: Tiny BASIC ;* Version: 1.0 ;* Updated: 8-10-2017 ;* Target: ATmega328 ;* ;* Written by Dick Whipple dickwhipple@whippleway.com ;* ;* DESCRIPTION ;* An implementation of Tiny BASIC as per PCC Vol. 3 No. 4. ;* ;*************************************************************************** ; .equ PLPrgm = 0 ;1 to preload TB Start-Up Program and RUN .equ PRT = 0 ;1 to inhibit printing ; .LIST ;***** Reserved Registers ; X R27:D -> TINY BASIC program pointer ; Y R29:R28 -> Numeric Stack (NS) pointer ;***** Register Variables .def A=r22 ;8080 Register Complement - Never safe in subroutines .def C=r16 ;Never safe in subroutines .def B=r17 ;Never safe in subroutines .def E=r18 ; .def D=r19 ; .def L=r20 ; .def H=r21 .def genStat=r23 ;General status register ;Bit 0 Inhibit leading zero if = 1 ;Bit 1 Direct Run from input buffer = 1 ;Bit 2 First digit flag ;Bit 3 Relational Op < ;Bit 4 Relational Op > ;Bit 5 Relational Op = ;Bit 6 Relational Op First pass ;Bit 7 Run mode = 1, command mode = 0; Line delete only = 1, Not = 0 .def ALx=r24 ;Auxilliary A register low .def AHx=r25 ;Auxilliary A register high ; .def errorCode=r2;Error code .def subLevel=r3 ;Subrouine level .def Lx=r6 ;Auxilliary L register .def Hx=r7 ;Auxilliary H register .def XLx=r8 ;Auxilliary XL register .def XHx=r9 ;Auxilliary XH register .def SL=r10 ;Stack exchange register low .def SH=r11 ;Stack exchange register high .def CLNL=r12 ;Current line number - low .def CLNH=r13 ;Current line number - high .def IBL=r14 ;Input buffer low (temp) .def IBH=r15 ;Input buffer high (temp) ; ; Macros ; .macro popRP ; rcall popS movw @0:@1, SH:SL ; .endmacro ; .macro pushRP ; movw SH:SL, @0:@1 rcall pushS ; .endmacro ; .macro pushi ; ldi A, low(@0) mov SL, A ldi A, high(@0) mov SH, A rcall pushS ; .endmacro ; .macro addi ; subi @0, -@1 ;subtract the negative of an immediate value ; .endmacro ; .macro subiw ; subi @1, low(@2) sbci @0, high(@2) ; .endmacro ; ; Misc Equates ; .equ inBufferSize = 64 ;Input buffer size .equ outBufferSize = 64 ;Outpu buffer size .equ SRSTACKSIZE = 100 ;Subroutine stack size .equ TBEND = RAMEND - SRSTACKSIZE ;End of allowed TINY BASIC program segment .equ numStkSize = 64 ;Numeric stack size .equ quote = 0x22 ;ASCII quotation mark .equ CR = 0x0D ;ASCII carriage return .equ EOF = 0xFF ;End-of-file .equ LF = 0x0A ;ASCII line feed .equ BackSpace = 127 ;Back space key .equ BS = 0x08 ;ASCII back space for terminal .equ ESC = 0x1b ;ASCII escape .equ subLevelMax = 5 ;Maximum number of subroutine levels .equ baud_rate_const = 103 ;9600 BPS ; jmp RESET ; Reset jmp null_int ; IRQ0 jmp null_int ; IRQ1 jmp null_int ; PCINT0 jmp null_int ; PCINT1 jmp null_int ; PCINT2 jmp null_int ; Watchdog Timeout jmp null_int ; Timer2 CompareA jmp null_int ; Timer2 CompareB jmp null_int ; Timer2 Overflow jmp null_int ; Timer1 Capture jmp null_int ; Timer1 CompareA jmp null_int ; Timer1 CompareB jmp null_int ; Timer1 Overflow jmp TIM0_COMPA ; Timer0 CompareA jmp null_int ; Timer0 CompareB jmp null_int ; Timer0 Overflow jmp null_int ; SPI Transfer Complete jmp null_int ; USART RX Complete jmp null_int ; USART UDR Empty jmp null_int ; USART TX Complete jmp null_int ; ADC Conversion Complete jmp null_int ; eeprom Ready jmp null_int ; Analog Comparator jmp null_int ; 2-wire Serial jmp null_int ; SPM Ready ; null_int: reti ; ; Digital I/O Initialization Code ; reset: ; ; Initialize stack pointers ; ; Subroutine stack ; ldi A,low(RAMEND) out SPL,A ldi A,high(RAMEND) out SPH,A ; ; Initialize numeric stack ; ldi YL, low(numSTK) ldi YH, high(numSTK) ; ; Zero variables ; rcall zeroVariables ; ; Clear TB program segment ; ldi A, EOF ;Write EOF to first byte of TB program segment sts prgStart, A ldi A, low(prgStart) ;Update TB program end sts prgEnd, A ldi A, high(prgStart) sts prgEnd + 1, A ; ; Seed random number generator ; ldi L, 100 ;Seed with 100 ldi H, 0 rcall seedRandomNumber ; ; Clear general status register ; clr genStat ; ; Reset error code ; ldi A, 0xff mov errorCode, A ; ldi A, CR sts inBuffer, A ; ; Set baud rate to 9600 ; ldi C, low(baud_rate_const) ldi B, high(baud_rate_const) sts UBRR0H, B sts UBRR0L, C ; ; ; Set 8-bit, no partity, 2-stop bits ; ; ldi A, (0<100 then 10", CR, "70 goto 20", CR, 0xff, 0 ; signOnMsg: ; .db "AVR TINY BASIC Version 1.0 (RBW 2017)", EOF ; ; Routine: command ; ; Purpose: Process commands or statements in direct mode ; command: ; ; Basic Initialization ; ; Subroutine stack ; ldi A,low(RAMEND) out SPL,A ldi A,high(RAMEND) out SPH,A ; ; Initialize numeric stack ; ldi YL, low(numSTK) ldi YH, high(numSTK) ; ; Clear general status register ; clr genStat ; rcall crlf ;New line ldi A, '>' ;Send greater than (>) prompt to serial device rcall xmtByte andi genStat, 0b01111111 ;Set command mode rcall inBuf ;Get command into input buffer rcall crlf ;New line ldi XL, low(inBuffer) ;Point X to start of input buffer ldi XH, high(inBuffer) rcall skipSpace ;Skip to first non-space rcall getNumber ;Line number present? brcs lineProcess ;If so, continue...process the line ; ; Process a direct command or statement ; clr CLNL ;Set current line number zero clr CLNH rcall skipSpace ;Skip to first non-space rjmp exeStatement ;Process command/statement ; ; Routine: lineProcess ; ; Purpose: Process program line currently in input buffer ; ; Options: ; ; If only line number in input buffer and line exists, delete it ; If full line in input buffer and line exists, delete it first and then insert new line ; Otherwise, insert new line ; lineProcess: ; movw CLNH:CLNL, H:L ;Save new line number rcall skipSpace ;Get next non-space byte ori genStat, 0b10000000 ;Set delete only bit cpi A, CR ;Carriage return? ldi XL, low(prgStart) ;Point X to TB program start ldi XH, high(prgStart) breq lineProcessLoop ;If so, continue...delete line CLN andi genStat, 0b01111111 ;Otherwise, clear delete only bit (i.e., prepare to delete and insert new line) ; ; Find line CLN if it exists ; lineProcessLoop: ; movw ZH:ZL, XH:XL ;Save start of line in Z rcall getNumber ;Get line number from TB program segment brcc lineInsert ;No line found, try to insert if not delete only ; ; Current TB program line number is in HL; does it match CLN? ; sub L, CLNL ;HL = CLN? sbc H, CLNH breq lineProcess1 ;Branch - Matches - delete old line and insert new line! brcs lineProcess0 ;Branch - TB program line number less than CLN. Keep looking ; movw H:L,ZH:ZL ;Z->HL rjmp lineInsert0 ;Insert new line at (Z) ; lineProcess0: ; ld A, X+ ;Search for CR cpi A, CR ;CR? brne lineProcess0 ;Otherwise, loop rjmp lineProcessLoop ;Keep looking! ; ; Reached EOF, insert new line here! ; lineInsert: ; movw H:L,XH:XL ;X->HL tst genStat ;Delete only? brpl lineInsert0 ;Otherwise, continue rjmp LineNumberNotFoundError ;If so, raise line not found error ; lineInsert0: ; ; Find length of line and store in BC ; clr ALx ;0->Ax clr AHx ldi XL, low(inBuffer) ;Point X to start of input buffer ldi XH, high(inBuffer) ; lineInsert0Loop0: ; ld A, X+ ;Get new line byte into A adiw AHx:ALx, 1 ;Increment Ax cpi A, CR ;CR? brne lineInsert0Loop0 ;Otherwise, loop movw B:C,AHx:ALx ;Ax -> BC ; ; Length of remaining bytes in current TB program -> DE ; clr AHx ;0->Ax clr ALx movw XH:XL,H:L ;HL->X ; lineInsert0Loop1: ; ld A, X+ ;Loop looking for EOF adiw AHx:ALx, 1 ;Increment Ax cpi A, EOF ;End of TB program? brne lineInsert0Loop1 ;Otherwise, loop movw D:E,AHx:ALx ;Ax->DE ; lineInsert1: ; ; Move remaining bytes in TB program up BC bytes to make room for new line ; movw ZH:ZL,XH:XL ;X + BC -> Z add ZL, C adc ZH, B ldi C, low(TBEND) ;Out of Memory? ldi B, high(TBEND) sub C, ZL sbc B, ZH brcs lineInsertError ;If so, error movw AHx:ALx,D:E ;DE -> Ax ; lineInsert1Loop: ; ld A, -X ;(X) -> (Z) st -Z, A sbiw AHx:ALx, 1 ;Ax - 1 -> Ax mov A, AHx ;Ax = 0? or A, ALx brne lineInsert1Loop ; ; Copy new line to opened space ; lineInsert2: ; movw ZH:ZL,H:L ;HL -> Z ldi XL, low(inBuffer) ;Point X to start of input buffer ldi XH, high(inBuffer) ; lineInsert2Loop: ; ld A, X+ ;Copy byte st Z+, A cpi A, CR ;CR? brne lineInsert2Loop ;Otherwise, loop...keep copying bytes ; lineInsert3: ; ; Done, return to command mode ; sbiw Z, 1 sts prgEnd, ZL ;Update TB program end sts prgEnd + 1, ZH rcall crlf ;New line rjmp command + 1 ;Done...go to commane=d mode ; ; ; Delete line CLN and insert new line ; lineProcess1: ; ; Delete line ; movw H:L,ZH:ZL ;Z->HL movw XH:XL,ZH:ZL ;Z->H ; lineDeleteLoop0: ; ld A, Z+ ;Look for CR cpi A, CR ;CR? brne lineDeleteLoop0 ;Otherwise, loop ; lineDeleteLoop1: ; ld A, Z+ ;Move remaining TB program down to back fill removed line st X+, A cpi A, EOF ;End of TB program? brne lineDeleteLoop1 ;Otherwise, loop ; lineDeleteDone: ; sbiw Z, 1 sts prgEnd, ZL ;Update TB program end sts prgEnd + 1, ZH tst genStat ;Delete only? brpl lineInsert0 ;Otherwise, insert new line rjmp command + 1 ;If so, done...go to command mode ; lineInsertError: ; rjmp outOfMemoryError ; ; Routine: inBuf ; ; Purpose: Take input from serial device and place in input buffer ; inBuf: ; clr B ;Clear BC (input buffer pointer) clr C ; inBufSS: ; rcall rcvByte ;Get next byte from serial device and skip leading spaces ; cpi A, ESC ;ESC? brne inBuf0 ;Otherwise, continue rjmp command ;If so, go to command mode ; inBuf0: ; cpi A, ' ' ;Space? breq inBufSS ;Otherwise, loop rjmp inBuf1 + 1 ;If so, continue...skip rcvByte statement ; inBufLoop: ; cpi A, ESC ;ESC? brne inBuf1 ;Otherwise, continue rjmp command ;If so, go to command mode ; inBuf1: ; rcall rcvByte ;Get next byte cpi A, BackSpace ;Back space? brne inBuf2 ;Otherwise, continue ; ; Process back space ; tst C ;At beginning of buffer? breq inBufLoop ;If so, do nothing.. ldi A, BS ;Back up one byte rcall xmtByte ldi A, ' ' ;Wipe byte rcall xmtByte ldi A, BS ;Back up again rcall xmtByte dec C ;Pointer back one space rjmp inBufLoop ;Get another byte ; inBuf2: ; cpi A, CR ;Carriage return? brne inBuf3 ;if not, continue ; ; process carriage return ; rcall putByteInBuf ;Put CR in input buffer ret ;Done ; inBuf3: ; cpi A, ' ' ;Space? brcs inBufLoop ;If a control byte, ignore rcall putByteInBuf ;Put byte in input buffer brcc inBufLoop ;If put failed, do nothing rcall xmtByte ;Output byte to serial port rjmp inBufLoop ;Back for another byte ; putByteInBuf: ; ldi ZL, low(inBuffer) ;Z points to beginning of input buffer ldi ZH, high(inbuffer) cpi C, low(inBufferSize);End of input buffer? brcs putByteInBuf0 ;Otherwise, continue ret ;If so, do nothing. Return with carry clear ; putByteInBuf0: ; add ZL, C ;Point to input buffer write address adc ZH, B st Z, A ;Store byte inc C ;Point next input buffer position sec ;Set carry ret ;Done...return with carry set ; ; Routine: rcvByte ; ; Purpose: If byte in serial buffer, gets it in A from serial port. ; rcvByte: ; lds A, UCSR0A ;Byte available? sbrs A, RXC0 rjmp rcvByte ;Otherwise, loop ; ; Get received byte ; lds A, UDR0 ;If so, get from serial port into A ret ;Done ; ; Routine: xmtByte ; ; Purpose: Waits for transmit ready, then transmits byte in A through serial port. ; xmtByte: ; .IF PRT == 1 ret ;If simulation, do nothing .ELSE rcall pushA ;Save A ; xmtByteLoop: ; lds A, UCSR0A ;Ready to transmit byte? sbrs A, UDRE0 rjmp xmtByteLoop ;Otherwise, loop ; ; Put byte in xmt buffer ; rcall popA ;Restore A sts UDR0, A ;Transmit it to serial port ret ;Done ; .ENDIF ; ; Routine: crlf ; ; Purpose: Outputs carriage return and linefeed to serial port. ; crlf: ; clr A ;Set output buffer pointer to start sts outBufPtr, A ldi A, CR ;Send carriage return to serial port rcall xmtByte ldi A, LF ;Send line feed to serial port rjmp xmtByte ; ; Routine: runCommand ; ; Purpose: Starts execution at TB program start. ; runCommand: ; tst genStat ;Command Mode? brpl runCommand0 ;If so, continue rjmp runModeError ;Otherwise, error ; runCommand0: ; ori genStat, 0b10000000 ;Set RUN mode rcall crlf ;New line rcall clearOutputBuffer ;Clear the output buffer ??? Is this really necessary? ; rcall zeroVariables ;Zero variables ; ldi YL, low(numSTK) ;Initialize numeric stack ldi YH, high(numSTK) ; ldi XL, low(prgStart) ;Point X to TB program start ldi XH, high(prgStart) ; runP0: ; rcall getNumber ;Is there a line number? brcs runP1 ;If so, continue rjmp command ;Otherwise, back to command mode ; runP1: ; movw CLNH:CLNL, H:L ;Update current line number lds A, UCSR0A ;Byte available? sbrc A, RXC0 rcall runP4 ;If so, continue rcall skipSpace ;Skip to first non-space rjmp exeStatement ;Assume statement follows and execute it ; runP2: ; or CLNH, CLNL ;Direct command? brne runP3 ;Otherwise, continue rjmp command ;If so, go to command mode ; runP3: ; rcall nextByte ;Get next TB program byte (Should be beginning of next line number or EOF) rjmp runP0 ;Go see ; runP4: ; lds A, UDR0 ;Get from serial port into A cpi A, ESC ;ESC? breq runP5 ;If so, continue ret ;Otherwise, return ; runP5: ; ldi A,low(RAMEND) ;Reinitialize stack pointer out SPL,A ldi A,high(RAMEND) out SPH,A rcall clearOutputBuffer ;Clear output buffer rcall crlf ;New line ldi L, low(breakMsg) ;Point to break message ldi H, high(breakMsg) rjmp error1 ;Finish at error code ; done: ; cpi A, CR ;CR? breq runp2 ;If so, done cpi A, ':' ;Colon? brne doneError ;Otherwise, error ld A,x+ rcall skipSpace rjmp exeStatement ; doneError: ; rjmp syntaxError ;report syntax error ; doneCheck: ; cpi A, CR ;CR? brne doneCheck0 ;Otherwise, continue ret ;If so, done ; doneCheck0: ; cpi A, ':' ;Colon? breq doneCheck1 ;If so, continue ret ; doneCheck1: ; ldi A, CR ret ; breakMsg: ; ; .db "BREAK AT LINE ", 0xff, 0 ; ; ; Routine: listCommand ; ; Purpose: Lists program in TB program segment ; listCommand: ;; tst genStat ;Command Mode? brpl listCommand0 ;If so, continue rjmp runModeError ;Otherwise, error ; listCommand0: ; ldi XL, low(prgStart) ;Point X to TB program start? ldi XH, high(prgStart) ; listCommandNL: ; rcall crlf ;New line ; listCommandLoop: ; ld A, X+ ;Get byte? cpi A, 0xFF ;EOF? breq listCommandDone ;If so, done cpi A, CR ;Carriage return? breq listCommandNL ;If so, output new line then continue rcall xmtByte rjmp listCommandLoop ;Back for more ; listCommandDone: ; rjmp command ;Back to command mode ; ; Routine: newCommand ; ; Purpose: Clears TB program segment ; newCommand: ; tst genStat ;Command Mode? brpl newCommand0 ;If so, continue rjmp runModeError ;Otherwise, error ; newCommand0: ; ldi A, EOF ;Write EOF to first byte of TB program segment sts prgStart, A ldi A, low(prgStart) ;Update TB program end sts prgEnd, A ldi A, high(prgStart) sts prgEnd + 1, A ; rjmp command ;Back to command mode ; ; Routine: exeStatement ; ; Purpose: Checks current byte(s) at (X) for a valid command/statement and if found, branches to it. ; exeStatement: ; ldi ZL, low(2 * iTable) ;Point Z to start of statement table ldi ZH, high(2 * iTable) rcall findReserveWord ;Statement/command in table? brcs exeStatement1 ;If so, continue clr c ;Assume LET ; exeStatement1: ; ldi ZL, low(iJmpTable) ;Start of iJmpTable -> Z ldi ZH, high(iJmpTable) clr B ;2 * BC -> BC add ZL, C ;Z + BC -> Z adc ZH, B ijmp ;Jump indirect to statement ; iTable: ; ; Note: Command/Statement reserved word table must match iJmpTable! ; .db "LE", 'T' + 0x80, 'I', 'F' + 0x80, "THE", 'N' + 0x80, "PRIN", 'T' + 0x80, "GOT", 'O' + 0x80, "GOSU", 'B' + 0x80, "RETUR", 'N' + 0x80, "INPU", 'T' + 0x80, "PW", 'M' + 0x80, "OU", 'T' + 0x80, "DL", 'Y' + 0x80, "PU", 'T' + 0x80, "RE", 'M' + 0x80, "EN", 'D' + 0x80, "RU", 'N' + 0x80, "LIS", 'T' + 0x80, "NE", 'W' + 0x80, 0xff,0 ; iJmpTable: ; rjmp letStmt rjmp ifStmt rjmp gotoStmt rjmp printStmt rjmp gotoStmt rjmp gosubStmt rjmp returnStmt rjmp inputStmt rjmp pwmStmt rjmp outStmt rjmp dlyStmt rjmp putStmt rjmp remStmt rjmp endStmt rjmp runCommand rjmp listCommand rjmp newCommand ; ; ; Routine: findReserveWord ; ; Purpose: Checks current byte(s) pointed to by X for a reserved word (command/statement/function) ; in table pointed to by Z. ; Returns carry set if found and in C the number of reserved word in table (base 0) ; Returns carry cleared if not found ; findReserveWord: ; movw XHx:XLx, XH:XL ;Save X in Xx (X auxilliary) ; ldi B, -1 ;Set statement found flag to -1 (no valid statement) ldi C, -1 ;Set statement counter to 0 (first statement) ; findInLoop0: ; movw XH:XL, XHx:XLx ;Point X back to beginning of possible statement inc C ;Point first statement in iTable ; findInLoop1: ; ld A, X+ ;Get TB program byte? andi A, 0b01111111 ;Mask lower seven bits rcall makeUpperCase ;Make upper case if letter ; findIn: ; cpi A, 'A' brcs findInNone ;Branch to done if (X) less than ASCII 'A' cpi A, 'Z' + 1 brcc findInNone ;Branch to done if (X) greater than 'Z' lpm D, Z+ ;(Z) -> D cpi D, 0xFF breq findInNone ;Branch to done if at end of table cpi D, 0b10000000 brcc findIn0 ;Branch if last letter of statement in table cp A, D breq findInLoop1 ;Byte match! Check next TB program byte ; ; No match ; findInLoop2: ; lpm D, Z+ ;Look for last byte of current iTable statement cpi D, 0b10000000 brcs findInLoop2 rjmp findInLoop0 ; findIn0: ; andi D, 0b01111111 ;Mask lower seven bits cp A, D brne findInLoop0 ;Branch in no byte match ; ; Statement matches! ; findInFound: ; sec ;Set carry ret ;Done ; ; No statement found ; findInNone: ; movw XH:XL, XHx:XLx ;Point X back to beginning of statement clc ;Clear carry ret ;Done ; ; Convert letter to upper case ; makeUpperCase: ; sbrs A, 6 ;Letter? ret ;Otherwise, done andi A, 0b11011111 ;Make upper case ret ; ; Routine: expression ; ; Purpose: Evaluate expression at X ; ; Used: All basic registers ; expression: ; rcall skipSpace ;Get first non-space byte of expression cpi A, '+' ;Plus? brne expr0 ;Otherwise, continue rcall nextByteSS ;If so, get next TB program byte then skip spaces rjmp expr1 ; expr0: ; cpi A, '-' ;Negation? brne expr1 ;Otherwise, continue rcall nextByteSS ;If so, get next TB program byte then skip spaces rcall term ; Get term value on numeric stack rcall twosComp16Stk ; Negate it. rjmp expr2 ; continue ; expr1: ; rcall term ;Get first term ; expr2: ; cpi A, '+' ;Addition? brne expr3 ;Otherwise, continue rcall nextByteSS ;If so, get next TB program byte then skip spaces rcall term ; Get next term on numeric stack rcall add16Stk ; Add top two terms on numeric stack rjmp expr2 ; continue ; expr3: ; cpi A, '-' ;Subtraction? brne expr4 ;Otherwise, done. rcall nextByteSS ;If so, get next TB program byte then skip spaces rcall term ; Get next term on numeric stack rcall twosComp16Stk ; Neagate it rcall add16Stk ; Add top two terms on numeric stack rjmp expr2 ; continue ; expr4: ; ret ;Done ; term: ; rcall factor ;Get first factor ; term0: ; rcall skipSpace ;Skip to non-space byte cpi A, '*' ;Multiply? brne term1 ;Otherwise, continue rcall nextByteSS ;If so, get next TB program byte then skip spaces rcall factor ; Get next factor rcall mult16Stk ; Multiply top two factors on numeric stack rjmp term0 ; continue ; term1: ; cpi A, '/' ;Divide? brne term2 ;Otherwise, continue rcall nextByteSS ;If so, get next TB program byte then skip spaces rcall factor ; Get next factor rcall div16Stk ; Multiply top two factors on numeric stack rjmp term0 ; continue ; term2: ; ret ;Done ; factor: ; rcall getFunction ;Function? brcc fact0 ;Otherwise, continue rcall skipSpace ;If so, skip to next non-space pushRP H, L ; Put function value on numeric stack ret ; Done ; fact0: ; rcall getVariable ;Variable? brcc fact1 ;Otherwise, continue rcall skipSpace ;If so, skip to next non-space byte pushRP H, L ; Put value variable found on numeric stack ret ; Done ; fact1: ; rcall getNumber ;Number? brcc fact2 ;Otherwise, continue rcall skipSpace ;If so, skip to next non-space pushRP H, L ; Put HL on numeric stack ret ; Done ; fact2: ; ld A, X ;Get current TB program byte? cpi A, '(' ;Begin grouping? breq fact3 ;If so, continue rjmp syntaxError ;Otherwise, unexpected byte indicates syntax error. ; fact3: ; rcall nextByteSS ;Get next TB program byte then skip spaces rcall expression ;Recursively rcall expression rcall skipSpace ;Skip to first non-space cpi A, ')' ;End grouping? breq fact4 ;If so, continue rjmp unpairedParenError ;Otherwise, unpaired parentheses error ; fact4: ; rjmp nextByteSS ;Get next TB program byte then skip spaces ; ; Statement Routines ; ; Process LET statement ; letStmt: ; rcall skipSpace ;Skip to first non-space rcall makeUpperCase ;If letter, make upper case (Variable a is same as A, etc) cpi A, 'A' ;Variable name brcs letStmtError ;Otherwise, syntax error cpi A, 'Z' + 1 brcc letStmtError ;Otherwise, syntax error rcall pushA ;Put variable name on numeric stack rcall nextByteSS ;Get next TB program byte then skip spaces cpi A, '=' ;Should be equal sign? brne letStmtError ;Otherwise, syntax error rcall nextByteSS ;Get next TB program byte then skip spaces rcall expression ;Evaluate expression rcall storeVariable ;Store it rcall skipSpace ;Skip to first non-space rjmp done ;Done ; letStmtError: ; rjmp syntaxError ; ; Process IF statement ; ifStmt: ; rcall skipSpace ;Skip to first non-space rcall expression ;Evaluate first expression on numeric stack andi genStat, 0b10000111 ;Clear all relational bits ori genStat, 0b01000000 ;Set bit 6 indicating first pass ; ifLoop: ; rcall skipSpace ;Skip to first non-space cpi A, '<' ;Less than? brne if0 ;Otherwise, continue looking ori genStat, 0b00001000 ;If so, set bit 3 rjmp if3 ; if0: ; cpi A, '>' ;Greater than? brne if1 ;Otherwise, continue looking ori genStat, 0b00010000 ;If so, set bit 4 rjmp if3 ; if1: ; cpi A, '=' ;Equals to? brne if2 ;Otherwise, continue looking ori genStat, 0b00100000 ;If so, set bit 5 rjmp if3 ; if2: ; sbrc genStat, 6 ;First pass bit? rjmp missingRelopError ;if so, expected relational operator on first pass rjmp if4 ; if3: ; rcall nextByteSS ;Get next TB program byte then skip spaces sbrs genStat, 6 ;First pass? rjmp if4 ;Otherwise, continue andi genStat, 0b10111111 ;Clear first pass bit rjmp ifLoop ; if4: ; rcall expression ;Evaluate second expression rcall twosComp16Stk ;Negate second expression rcall add16Stk ;Add expressions popRP H, L ;Result in HL or H, L ;Result zero? brne if5 ;Otherwise, continue sbrc genStat, 5 ;Equal bit set? rjmp ifThen ;If so, execute THEN statement ; ifDone0: ; rcall skipSpace ;Skip to first non-space ; ifDone0Loop: ; cpi A, CR ;Carriage return? breq ifDone1 ;If so, execute next statement rcall nextByteSS ;Otherwise, get next TB program byte then skip spaces rjmp ifDone0Loop ;Keep looking ; ifDone1: ; rjmp runP2 ;Done ; if5: ; tst H ;Test if H negative brbc 2, if6 ;Otherwise, continue sbrc genStat, 3 ;Less than bit set? rjmp ifThen ;If so, execute THEN statement rjmp ifDone0 ; if6: ; sbrc genStat, 4 ;Greater than bit set? rjmp ifThen ;If so, execute THEN statement rjmp ifDone0 ; ifThen: ; rjmp exeStatement ; ifError0: ; rjmp missingRelopError ; ifError1: ; rjmp syntaxError ; ; Process PRINT statement ; printStmt: ; rcall skipSpace ;Skip to first non-space rcall printString ;String? If so, Write to outBuffer brcc printStmt0 ;Otherwise, continue rcall skipSpace ;Skip to first non-space rcall doneCheck ;CR or Colon? brne printStmt2 ;Otherwise, continue rcall putByte ;If so, write CR to output buffer rjmp printStmt6 ;Done ; printStmt0: ; rcall skipSpace ;Skip to non-space byte rcall doneCheck ;CR or Colon? brne printStmt1 ;Otherwise, continue rcall putByte ;If so, write CR to output buffer rjmp printStmt6 ;Done ; printStmt1: ; rcall expression ;Assume an expression and evaluate it rcall printNumber ;Write resulting value to output buffer rcall skipSpace ;Skip to non-space byte rcall doneCheck ;CR or Colon? brne printStmt2 ;Otherwise, continue rcall putByte ;If so, Write CR to output buffer rjmp printStmt6 ; printStmt2: ; cpi A, ';' ;Semicolon? brne printStmt3 ;Otherwise, check for comma. ldi A, ' ' ;If so, Write space to outBuffer rcall putByte rjmp printStmt4 ;continue ; printStmt3: ; cpi A, ',' ;Comma? Space to next zone (assumes 8 byte zone) brne printStmt5 ;Otherwise, check for carriage return. ; printStmt3Loop: ; ldi A, ' ' ;Write space character to output buffer rcall putByte lds A, outBufPtr ;Is output buffer pointer at end of zone? andi A, 0x07 ;Assumes zone width 8 breq printStmt4 ;If so, continue rjmp printStmt3Loop ;Otherwise, loop ; printStmt4: ; rcall nextByteSS ;Get next TB program byte then skip spaces rcall doneCheck ;CR? brne printStmt ;Otherwise, continue rcall putByte rcall dumpOutBuf ;Dump output buffer clr A ;Set output buffer pointer to start sts outBufPtr, A rjmp printStmt7 ;If so, done ; printStmt5: ; rcall skipSpace ;Skip to non-space byte rcall doneCheck ;CR or Colon? brne printStmt ;Otherwise, continue ; rcall putByte ;If so, Write CR to output buffer ; printStmt6: ; rcall dumpOutBuf ;Dump output buffer ; rcall crlf ;New line ; printStmt7: ; ld A, X cpi A,':' breq contExe rjmp runP2 ;Done ; contExe: ; rcall nextByteSS rjmp exeStatement ; ; Routine: dumpOutBuf ; ; Purpose: Sends contents of output buffer to serial device ; dumpOutBuf: ; ldi ZL, low(outBuffer) ldi ZH, high(outbuffer) ; dumpOutBufLoop: ; ld A, Z+ cpi A, CR ;EOF? brne dumpOutBuf0 ;Otherwise, continue ret ;If so, done ; dumpOutBuf0: ; rcall xmtByte rjmp dumpOutBufLoop ; ; Routine: putByte ; ; Purpose: Write contents of register A to output buffer ; putByte: ; clr B ;Buffer pointer -> BC lds C, outBufPtr ;Past end of output buffer? cpi C, outBufferSize ;BC > Buffer Size brcs putByte0 ;Otherwise, continue push A ;If so, Save A ldi A, CR ;Write CR to output buffer (extra byte) rcall putbyte0 rcall dumpOutBuf ;Dump the output buffer clr A ;Set output buffer pointer to start sts outBufPtr, A mov C, A ;C back to start of output buffer pop A ;Restore A and continue ; putByte0: ; clr B ;Calculate buffer address for byte movw XHx:XLx, XH:XL ;Save X ldi XL, low(outBuffer) ;BC + outBuffer -> X ldi XH, high(outbuffer) add XL, C adc XH, B st X, A ;Store A -> (X) inc C ;Point buffer pointer to next byte sts outBufPtr, C ;Store buffer pointer. movw XH:XL, XHx:XLx ;Restore X ret ;Done ; ; ; Routine: printString ; ; Purpose: if A contains a quotation mark, Write string to output buffer. ; printString: ; cpi A, '"' ;Quotation mark? (string literal) breq printString0 ;If so, continue clc ;Clear carry ret ;Done ; printString0: ; adiw X, 1 ;Point next byte. ; printStringLoop: ; ld A, X+ ;Get next byte -> A cpi A, '"' ;Quotation mark? (end of string literal) brne printString1 ;Otherwise, continue ld A, X ;If so, get next byte sec ret ;Done ; printString1: ; rcall putByte ;Put byte in output buffer rjmp printStringLoop ;Back for more ; ; Routine: printNumber ; ; Purpose: Print number on top of numeric stack ; printNumber: ; sbr genStat, 0b00000001 ;Inhibit leading zeros popRP H, L ;Get number into HL then repush onto numeric stack pushRP H, L tst H ;Test for sign? brmi pN0 ;Branch if negative or H, L ;HL = 0? breq pN1 ;If so, Write zero to output buffer rjmp printLineNumber + 1 ;Otherwise, continue ; pN0: ; rcall twosComp16Stk ;Negate the top on numeric stack ldi A, '-' ;Write a minus sign to output buffer rcall putByte rjmp printLineNumber + 1 ;Continue ; pN1: ; ldi A, '0' ;ASCII zero -> A rcall putByte ;Put A in output buffer rjmp printLineNumber + 1 ;Continue ; ; Routine: printLineNumber ; ; Purpose: Print number on top of numeric stack with leading zeros ; printLineNumber: ; cbr genStat, 0b00000001 ;Print leading zeros pushi 10000 ;Divide top of numeric stack by 10000 rcall divMod16Stk rcall pLN0 ;Write quotient to output buffer with ASCII bias pushi 1000 ;Divide top of numeric stack (remainder of previous division) by 1000 rcall divMod16Stk rcall pLN0 ;Write quotient to output buffer with ASCII bias pushi 100 ;Divide top of numeric stack (remainder of previous division) by 1000 rcall divMod16Stk rcall pLN0 ;Write quotient to output buffer with ASCII bias pushi 10 ;Divide top of numeric stack (remainder of previous division) by 1000 rcall divMod16Stk rcall pLN0 ;Write quotient to output buffer with ASCII bias ; pLN0: ; popRP H, L ;Top of numeric stack -> HL ldi A, '0' ;Add ASCII bias (ASCII zero) add A, L sbrs genStat, 0 ;Check inhibit leading zero bit rjmp putByte ;If cleared, output byte cpi A, '0' ;If set, see if byte is an ASCII 0 brne pLN1 ;Otherwise, continue ret ;If so, do nothing ; pLN1: ; cbr genStat, 0b00000001 ;Clear inhibit leading zero bit rjmp putByte ;Put byte in output buffer ; ; msgOut ; msgOut: ; clc ;2 * HL -> Z (in code segment) rol L rol H mov ZL, L ; mov ZH, H ; msgOutLoop: ; lpm ;Get LSB byte into A mov A, R0 cpi A, 0xFF ;EOF? brne msgOut1 ;Otherwise, continue ; msgOut0: ; ret ;Done...return ; msgOut1: ; rcall putByte ;Write byte to output buffer adiw Z, 1 ;Point next byte lpm ;Get it into A mov A, R0 cpi A, 0xFF ;EOF? breq msgOut0 ;If so, done rcall putByte ;Otherwise, put it into output buffer adiw Z, 1 ;Point next byte rjmp msgOutLoop ;Look for more ; ; Routine: gotoStmt ; ; Purpose: Processes the GOTO statement ; gotoStmt: ; rcall skipSpace ;Skip to non-space byte call expression popRP H, L ; goto0: ; ldi XL, low(prgStart) ;Point X to TB program start ldi XH, high(prgStart) movw Hx:Lx, H:L ;Save HL in HLx ; gotoLoop: ; rcall getNumber ;Get line number from TB program brcs goto1 ;If found then a line number in HL but does it match HLx? ; rjmp LineNumberNotFoundError ;Otherwise, error ; goto1: ; sub L, Lx ;HL - HLx -> HL sbc H, Hx ;Match? breq goto2 ;If so, continue brcs goto3 ;If TB program line number less than GOTO line number, keep looking ; rjmp LineNumberNotFoundError ;Otherwise, error ; ; goto2: ;Ready to execute new line ; movw CLNH:CLNL, Hx:Lx ;Update current line number rcall skipSpace ;Skip to first non-space rjmp exeStatement ;Done ; goto3: ; ld A, X+ ;Search for CR? cpi A, CR ;End of line? brne goto3 ;Otherwise, loop cpi A, 0xFF ;End of TB program? brne gotoLoop ;Otherwise, check next line number. ; rjmp LineNumberNotFoundError ;If so, should've found by now; error ; ; Routine: gosubStmt ; ; Purpose: Processes the GOSUB statement ; gosubStmt: ; tst genStat ;RUN Mode? brmi gosubStmt0 ;If so, continue rjmp directModeError ;Otherwise, error ; gosubStmt0: ; mov A,subLevel ;Max subroutine level reached? cpi A, subLevelMax brne goSubStmt1 ;Otherwise, continue rjmp subLevelMaxError ;If so, error ; gosubStmt1: ; movw H:L,XH:XL ;Save X, the current TB program location ; gosubStmt1Loop: ; ld A, X+ ;Locate beginning of next TB program line? rcall doneCheck ;CR or Colon? brne gosubStmt1Loop ;Otherwise, loop ; gosubStmt2: ; sbiw X, 1 ;Back up one location pushRP XH,XL ;Save it on numeric stack inc subLevel ;Increment subroutine level movw XH:XL,H:L ;Restore X rjmp gotoStmt ;Done ; ; Routine: returnStmt ; ; Purpose: Processes the RETURN statement ; returnStmt: ; tst genStat ;RUN Mode? brmi returnStmt0 ;If so, continue rjmp directModeError ;Otherwise, error ; returnStmt0: ; tst subLevel ;Subroutine level = 0? brne returnStmt1 ;Otherwise, continue rjmp subReturnError ;If so, error ; returnStmt1: ; dec subLevel ;Decrement subroutine level popRP XH,XL ;Get return TB program location from numeric stack rjmp runP2 ;Go execute ; ; Routine: inputStmt ; ; Purpose: Processes the INPUT statement ; inputStmt: ; tst genStat ;RUN Mode? brmi inputStmt0 ;If so, continue rjmp directModeError ;Otherwise, error ; inputStmt0: ; ldi A, '?' ;Output a question mark prompt rcall xmtByte rcall inBuf pushRP XH,XL ;Save current TB program pointer (X) ldi XL, low(inbuffer) ;Point X to beginning of input buffer ldi XH, high(inBuffer) rcall getNumber ;Get the inputted number into HL popRP XH,XL ;Restore current TB program pointer (X) rcall skipSpace ;Skip to first non-space rcall makeUpperCase ;If letter, make upper case cpi A, 'A' ;Control character? brcc inputStmt1 ;Otherwise, continue rjmp expectedVariableError;If so, error ; inputStmt1: ; cpi A, 'Z' + 1 ;ASCII letter A-Z? brcs inputStmt2 ;If so, continue rjmp expectedVariableError;Otherwise, error ; inputStmt2: ; rcall pushA ;Save variable name on numeric stack pushRP H,L ;Save inputted number on numeric stack rcall storeVariable ;Store it at variable named rcall nextByteSS ;Get next TB program byte skipping spaces cpi A, ',' ;Comma? brne inputStmt3 ;Otherwise, continue rcall nextByteSS ;If so, get next TB program byte skipping spaces rjmp inputStmt ;Back for another ; inputStmt3: ; rcall doneCheck ;Cr or Colon? breq inputStmt4 ;If so, continue rjmp expectedEOLError ;EOL error ; inputStmt4: ; rcall crlf ;New line rjmp runP2 ;Done ; ; Routine: endStmt ; ; Purpose: Processes the END statement ; endStmt: ; ldi L, low(endMsg1) ;Point HL to END message ldi H, high(endMsg1) rcall msgOut ;Write to output buffer pushRP CLNH, CLNL ;Put END line number on numeric stack rcall printNumber ;Write to output buffer ldi A, CR ;Write carriage return to output buffer rcall putByte rcall dumpOutBuf ;Send output buffer to serial device rcall crlf ;New line rjmp command ;Back for another command ; endMsg1: ; .db "END AT LINE ", 0xff, 0 ;END message ; remStmt: ; rcall skipSpace ;Skip to next non-space byte ; remStmtLoop: ; rcall doneCheck ;CR or Colon; breq remStmtDone ;If so, continue rcall nextByte ;Get next TB program byte rjmp remStmtLoop ;Keep looking ; remStmtDone: ; rjmp runP2 ;Done ; ; Start Custom Statements ; ; Statement: PWM(n) Statement ; ; Purpose: Outputs pulse width modulated waveform to pin 9 of Redboard where n = percent duty cycle ; pwmStmt: ; ld A, X ;Get current byte cpi A, '(' ;Open parentheses? breq pwmStmt0 ;If so, continue rjmp unpairedParenError ;Otherwise, unpaired parentheses error ; pwmStmt0: ; rcall nextByteSS ;Get next non-space TB program byte rcall expression ;Evaluate expression call skipSpace ;Get first non-space byte cpi A, ')' ;Closed parentheses? breq pwmStmt1 ;If so, continue rjmp unpairedParenError ;Otherwise, unpaired parentheses error ; pwmStmt1: ; popRP H, L ;Get duty cycle or H,L ;HL should be 0 to 100, so H must be zero breq pwmStmt2 ;If so, continue rjmp overflowError ;Otherwise, overflow error ; pwmStmt2: ; mov A,L cpi A, 101 ;L then should be 0 to 100 or less than 101 brcs pwmStmt3 ;If so, continue rjmp overflowError ;Otherwise, overflow error ; pwmStmt3: ; sbi ddrb,1 ;Set port b bit 1 (pin 9) output for timer 1 compare register "a" ldi A,0b00000011 ;Prescaler timer 0 N=64 490 Hz sts TCCR1B,A ldi A,0b10000001 ;Enable timer 1, clear on compare match, and PWM phase correct ;0bxxyy00zz xx = 10 enable to clear timer 1 compare register "a" on compare match when up-counting ; and set timer 0 compare register "a" on compare match when down-counting. ; yy = 00 timer 1 compare register "b" not used ; and set timer 1 compare register "b" on compare match when down-counting. ; zz = 01 phase correct 8-bit mode sts TCCR1A,A sts ocr1al,L ;Preset timer 1 compare register "a" duty cycle = 0% (0 out of 255) sts ocr1ah,H rcall nextByteSS ;Get next non-space TB program byte rjmp done ; ; Statement: OUT(n, m) ; ; Purpose: Outputs a low (m = 0) or high (m <> 0) to pin n of Redboard ; outStmt: ; ld A, X ;Get current byte cpi A, '(' ;Open parentheses? breq outStmt0 ;If so, continue rjmp unpairedParenError ;Otherwise, unpaired parentheses error ; outStmt0: ; rcall nextByteSS ;Get next non-space TB program byte rcall expression ;Evaluate expression for n call skipSpace ;Get first non-space byte cpi A, ',' ;Should be equal sign? breq outStmt1 ;If so, continue rjmp syntaxError ;Otherwise, syntax error ; outStmt1: ; rcall nextByteSS ;Get next non-space TB program byte rcall expression ;Evaluate expression for m call skipSpace ;Get first non-space byte cpi A, ')' ;Closed parentheses? breq outStmt2 ;If so, continue rjmp unpairedParenError ;Otherwise, unpaired parentheses error ; outStmt2: ; popRP h, L ;get n mov D, H ;save n mov E, L ; popRP H, L ;get m or H, H ;m should be 0 to 13 so H must be zero? breq outStmt3 ;if so, continue rjmp overflowError ;otherwise, over flow error ; outStmt3: ; cpi L, 14 ;m should be 0 to 13, so L must be less than 14 brcs outStmt4 ;if so, continue rjmp overflowError ;otherwise, over flow error ; outStmt4: ; cpi L, 8 ;out to port d? brcs outStmt_portd ;if so, continue to port d code ;otherwise, it must be port b subi L, 8 ;remove bias rcall cnvtBinBit ;get bit position into c in B,ddrb ;make sure bit is output or B, C out ddrb,B or D, E ;is D:E zero? breq outStmt_portb_clr ;if so, continue to clear bit ;otherwise, set bit in B, portb ;read port b to B or B, C ;set bit at position C out portb, B ;update port b rjmp outStmt_done ; outStmt_portb_clr: ; ldi B, 0xff ;invert bits in C eor C, B in B, portb ;read port b to B and B, C ;clear bit at position C out portb, B ;update port b rjmp outStmt_done ; outStmt_portd: ; rcall cnvtBinBit ;get bit position into C in B,ddrd ;make sure bit is output or B, C out ddrd,B or D, E ;is D:E zero? breq outStmt_portd_clr ;if so, continue to clear ;otherwise, set bit in B, portd ;read port b to B or B, C ;set bit at position C out portd, B ;update port b rjmp outStmt_done ; outStmt_portd_clr: ; ldi B, 0xff ;invert bits in C eor C, B in B, portd ;read port b to B and B, C ;clear bit at position C out portd, B ;update port b rjmp outStmt_done ; outStmt_done: ; rcall nextByteSS ;Get next non-space TB program byte rjmp done ; ; Routine: cnvtBinBit ; ; Purpose: Converts binary value 0 to 7 in L to bit position in C ; cnvtBinBit: ; ldi C, 0b00000001 ;preload L with 0b00000001 and prepare to rotate ; cnvtBinBit_loop: ; or L, L ;is L = 0? breq cnvtBinBit_done ;if so, continue lsl C ;shift C left once dec L ;decrement L rjmp cnvtBinBit_loop ;do again ; cnvtBinBit_done: ; ret ; ; Statement: DLY(n) ; ; Purpose: Introduces a delay of n = milliseconds ; dlyStmt: ; ld A, X ;Get current byte cpi A, '(' ;Open parentheses? breq dlyStmt0 ;If so, continue rjmp unpairedParenError ;Otherwise, unpaired parentheses error ; dlyStmt0: ; rcall nextByteSS ;Get next non-space TB program byte rcall expression ;Evaluate expression call skipSpace ;Get first non-space byte cpi A, ')' ;Closed parentheses? breq dlyStmt1 ;If so, continue rjmp unpairedParenError ;Otherwise, unpaired parentheses error ; dlyStmt1: ; popRP H, L ;Get n = number of ms sts delay, H ;save HL in delay sts delay+1, L ; ldi A,0b00000010 ;enable CTC mode for timer 0 ;0bxxyy00zz xx = 00 timer 0 compare register "a" not connected to pin 6 ; yy = 00 timer 0 compare register "b" not connected to pin 5 ; wzz = 010 CTC mode (w is bit 3 of TCCR0B below) out TCCR0A,A ; ldi A,250 ;preset compare register "a" to K=250 giving a 1000 Hz interrupt; adjust up or down to fine tune timing out ocr0a,A ; ldi A,0b00000010 ;enable timer 0 interrupt on count reaching value in compare register "a" ;0b00000xxx xxx = 010 interrupt on count reaching value in compare register "a" sts TIMSK0,A ; ; Main Program ; ldi A,0b00000011 ;prescaler N=64; start timer 0 out TCCR0B,A ; sei ;enable global interrupt ; dlyStmt_wait: ; lds H, delay ;wait for delay = 0 lds L, delay+1 or H,L brne dlyStmt_wait ; cli ;disable global interrupt rcall nextByteSS ;Get next non-space TB program byte rjmp done ; ; Timer 0 Interrupt Processing Routine ; TIM0_COMPA: ; push H ;save HL & A push L push A lds H, delay ;load delay into hl lds L, delay+1 mov A,L ;if zero, do nothing or A,H breq TIM0_COMPA_done subi L, 1 ;dec hl sbci H, 0 sts delay, H ;save hl sts delay+1,L ; TIM0_COMPA_done: ; pop A ;restore A, HL pop L pop H reti ;set gloabal interrupt and return ; ; 25lc1024 EEPROM instruction set ; .equ eeprom_READ = 0b00000011 .equ eeprom_WRITE = 0b00000010 .equ eeprom_WREN = 0b00000110 .equ eeprom_WRDI = 0b00000100 .equ eeprom_RDSR = 0b00000101 .equ eeprom_WRSR = 0b00000001 .equ eeprom_PE = 0b01000010 .equ eeprom_SE = 0b11011000 .equ eeprom_CE = 0b11000111 .equ eeprom_RDID = 0b10101011 .equ eeprom_DPD = 0b10111001 ; ; Statement: PUT(p, l, d) ; ; Purpose: Writes d = data to EEPROM at p = page and l = location ; putStmt: ; ; Set Up SPI ; ldi A,0b00101100 ;port b bits 2 (CE), 3 (MOSI), and 5 (SCK) as output ; out ddrb,A ;update data direction register B sbi portb,2 ;deselect eeprom ldi A,0b01010001 ;0btuvwxyzz t = 0 disable SPI interrupt (See section 23.5.1) ; u = 1 enable SPI ; v = 1 least significant bit (LSB) first ; w = 1 select ATmega328 as master ; xx = 00 SPI mode 0 ; zz = 01 prescale = 16 for SPI clock = 1 Mhz ("Table 23-5" in ATmega328 Datasheet) out spcr,A ;configure SPI control register ; ; Check that EEPROM connected ; rcall EEPROM_esig ;get EEPROM electronic signature cpi A, 41 ;is 41? breq putSTMT_cont ;if so, continue rjmp spiError ;otherwise, spi error ; putStmt_cont: ; ld A, X ;Get current byte cpi A, '(' ;Open parentheses? breq putStmt0 ;If so, continue rjmp unpairedParenError ;Otherwise, unpaired parentheses error ; putStmt0: ; rcall nextByteSS ;Get next non-space TB program byte rcall expression ;Evaluate expression for n call skipSpace ;Get first non-space byte cpi A, ',' ;Should be equal sign? breq putStmt1 ;If so, continue rjmp syntaxError ;Otherwise, syntax error ; putStmt1: ; rcall nextByteSS ;Get next non-space TB program byte rcall expression ;Evaluate expression for m call skipSpace ;Get first non-space byte cpi A, ',' ;Should be equal sign? breq putStmt2 ;If so, continue rjmp syntaxError ;Otherwise, syntax error ; putStmt2: ; rcall nextByteSS ;Get next non-space TB program byte rcall expression ;Evaluate expression for m call skipSpace ;Get first non-space byte cpi A, ')' ;Closed parentheses? breq putStmt3 ;If so, continue rjmp unpairedParenError ;Otherwise, unpaired parentheses error ; putStmt3: ; popRP H, L ;data in HL push H ;save HL push L popRP B, C ;get location in C push C ;save location subiw B, C, 128 ;location must be <= 127? pop C ;restore location brcs putStmt4 ;if so, continue rjmp overflowError ;otherwise, overflow error ; putStmt4: ; lsl C ;double location popRP D, E ;get page in DE push D ;save page push E subiw D, E, 512 ;page must be <= 511 pop E ;retrieve page pop D brcs putSTMT5 ;if so, continue rjmp overflowError ;otherwise, overflow error ; putStmt5: ; pop L ;retrieve data pop H rcall EEPROM_write_word;write data to EPROM rcall nextByteSS ;Get next non-space TB program byte rjmp done ; ; SPI Read Electronic Signature ; EEPROM_esig: ; cbi portb,2 ;select eeprom ldi A,eeprom_RDID ;send esig request rcall spi_write ; ldi B,3 ;send 3 dummy 24-byte address ; EEPROM_esig_loop: ; ldi A,0 rcall spi_write dec B ;done? brne EEPROM_esig_loop ;if not, loop ; rcall spi_read ;read esig sbi portb,2 ;deselect eeprom ret ; ; SPI Write Word (Double Byte) ; ; HL contains the word to written ; D:E:C contain the 24-bit address ; EEPROM_write_word: ; cbi portb,2 ;select eeprom ldi A,eeprom_WREN ;send write enable request rcall spi_write sbi portb,2 ;deselect eeprom cbi portb,2 ;select eeprom ldi A,eeprom_WRITE ;send write request rcall spi_write mov A,D ;send 24-bit address rcall spi_write mov A,E rcall spi_write mov A,C rcall spi_write mov A,H ;send most significant byte to be written rcall spi_write mov A,L ;send least significant byte to be written rcall spi_write sbi portb,2 ;deselect eeprom and start write cycle ; circuit_write_word_wait: ; rcall spi_read_SDSR ;read status register sbrc A,0 ;wait while WIP bit 0 set (write in progress) rjmp circuit_write_word_wait ret ; ; SPI Read Word (Double Byte) ; ; HL contains the byte read ; D:E:C contain the 24-bit address ; EEPROM_read_word: ; cbi portb,2 ;select eeprom ldi A,eeprom_READ ;send read request rcall spi_write mov A,D ;send 24-bit address rcall spi_write mov A,E rcall spi_write mov A,C rcall spi_write rcall spi_read ;read most significant byte mov H,A rcall spi_read ;read least significant byte mov L,A sbi portb,2 ;deselect eeprom ret ; ; SPI Read Status Register into A ; spi_read_SDSR: ; cbi portb,2 ;select eeprom ldi A,eeprom_RDSR ;send status register read request rcall spi_write rcall spi_read ;read status register sbi portb,2 ;deselect eeprom and start write cycle ret ; ; SPI Write A ; spi_write: ; out spdr,A ;send byte to SPI ; spi_write_wait: ; in A,spsr ;write completed? sbrs A,spif ;if not, wait rjmp spi_write_wait ret ; ; SPI Read into A ; spi_read: ; ldi A,0 ;send dummy byte to spi out spdr,A ; spi_read_wait: ; in A,spsr ;write completed? sbrs A,spif ;if not, wait rjmp spi_read_wait in A,spdr ;get return byte ret ; ; End Custom Statements ; ; Routine: skipSpace ; ; Purpose: Skips to first non-space byte ; skipSpace: ; ld A, X ;Get TB program byte? cpi A, ' ' ;A space? breq skipSpace0 ;If so, continue ret ;Otherwise, done...return ; skipSpace0: ; adiw X, 1 ;Point next TB program byte rjmp skipSpace ;Loop ; ; Routine: nextByte ; ; Purpose: Loads next TB program byte at (X) and returns. ; nextByte: ; adiw X, 1 ;Point next TB program byte? ; getByte: ; ld A, X ;Get TB program byte ret ;Done...return ; ; Routine: nextByteSS ; ; Purpose: Loads next TB program byte at (X), then skips to first non-space byte ; nextByteSS: ; adiw X, 1 ;Point next TB program byte rjmp skipSpace ;Skip spaces ; ; ; Routine: getNumber ; ; Purpose: Checks at X for a number represented in ASCII. If present, return it in HL with carry set. ; Otherwise present, return with HL=0 and carry cleared. ; getNumber: ; clr H ;0->HL clr L cbr genStat, 0b00000100 ;Clear digit flag bit ; gnLoop: ; ld A, X ;Get TB program byte? subi A, '0' ;Remove ASCII bias brcs gnDone0 ;If byte < ASCII zero, continue cpi A, 10 ;byte > ASCII nine? brcc gnDone0 ;If so, continue ldi E, 10 ;10 -> DE clr D rcall mult16 ;10 * HL -> BC clr D add L, A ;10 * HL + A -> HL adc H, D sbr genStat, 0b00000100 ;Found at least one digit, so set digit flag bit adiw X, 1 ;Next byte rjmp gnLoop ;Loop ; gndone0: ; clc ;Clear carry sbrc genStat, 2 ;Skip next statement if set digit flag cleared sec ;Set carry (at least one digit found) ret ;Done...return ; ; Zero variables A-Z ; zeroVariables: ; ldi ZL, low(varStart) ldi ZH, high(varStart) ; ldi B, 2 * 26 ldi C, 0 ; zV0: ; st Z+, C dec B brne zV0 ret ; ; Twos Complement top of numeric stack; result on numeric stack ; twosComp16Stk: ; popRP H, L rcall twosComp16 pushRP H, L ret ; ; Add top two numbers on numeric stack; sum on numeric stack ; add16Stk: ; popRP D, E popRP H, L rcall add16 pushRP H, L ret ; ; Subtrack top two numbers on numeric stack; difference on numeric stack ; sub16Stk: ; popRP D, E popRP H, L rcall sub16 pushRP H, L ret ; ; Multiply top two numbers on numeric stack; product on numeric stack ; mult16Stk: ; popRP D, E popRP H, L rcall mult16 pushRP H, L ret ; ; Divide top two numbers on numeric stack; quotient on numeric stack ; div16Stk: ; popRP D, E popRP H, L rcall div16 pushRP H, L ret ; ; ; Divide top two numbers on numeric stack; modulo (remainder) on numeric stack then quotient on numeric stack ; divMod16Stk: ; popRP D, E popRP H, L rcall div16 pushRP B, C pushRP H, L ret ; ; Modulo top two numbers on numeric stack; modulo (remainder) on numeric stack ; mod16Stk: ; popRP D, E popRP H, L rcall div16 pushRP B, C ret ; ; 16 Bit twosComp HL -> HL ; twosComp16: ; ldi A, 0xff eor L, A eor H, A subi L, low(-1) sbci H, high(-1) ret ; ; 16 Bit Add HL + DE -> HL ; add16: ; add L, E adc H, D ret ; ; 16 Bit Subtract HL - DE -> HL ; sub16: ; clc sub L, E sbc H, D ret ; ; 16 Bit Mulitiply HL * DE -> HL ; mult16: ; mul L, E ; al * bl movw B:C,r1:r0 mul H, E ; ah * bl add B, r0 mul D, L ; bh * al add B, r0 mov L, C mov H, B ret ; ; 16 Bit Divide HL / DE -> HL with BC remainder ; div16: ; clr C ;clear remainder Low byte sub B,B ;clear remainder High byte and carry ldi A,17 ;init loop counter ; div16_1: ; rol L ;shift left dividend rol H dec A ;decrement counter brne div16_2 ;if done ret ; return ; div16_2: ; rol C ;shift dividend into remainder rol B sub C,E ;remainder = remainder - divisor sbc B,D ; brcc div16_3 ;if result negative add C,E ; restore remainder adc B,D clc ; clear carry to be shifted into result rjmp div16_1 ;else ; div16_3: ; sec ;set carry to be shifted into result rjmp div16_1 ; ; Routine: getFunction ; ; Purpose: Gets value in HL for function. Carry set if function found; carry cleared otherwise ; getFunction: ; ldi ZL, low(2 * fTable) ;Point Z to start of function table ldi ZH, high(2 * fTable) rcall findReserveWord ;Item in table? brcs getFunction0 ;If so, continue...C contains number of item in table ld A, X ;Get current byte ret ;Otherwise, done...return with carry cleared ; getFunction0: ; ldi L, low(fCallTable) ;Point Z to start of function rcall table ldi H, high(fCallTable) clr B ; add L, C ;HL + BC -> HL adc H, B clc ;2*HL -> HL rol L rol H movw ZH:ZL, H:L ;HL->Z lpm ;Read LSB of word in code segment mov L, R0 ;Save LSB in L adiw Z, 1 ;Point MSB of word in code segment lpm ;Read MSB of word in code segment mov H, R0 ;Save MSB in H movw ZH:ZL,H:L ;HL->Z icall ;Call function sec ;Set carry ret ;Done...return ; ; Function Name Table fTable: ; ; Note: Table must match fCallTable! ; .db "RN", 'D' + 0x80, "AD", 'C' + 0x80, "PI", 'N' + 0x80, "GE", 'T' + 0x80, 0xff, 0 ; fCallTable: ; .db low(getRandomNumber), high(getRandomNumber) .db low(getADC), high(getADC) .db low(getPin), high(getPin) .db low(getGET), high(getGET) ; ; Function Subroutines ; ; Function: RND(n) ; ; Purpose: Returns a psuedo-random number in HL. If n = 0, returns same number each time. ; getRandomNumber: ; ld A, X+ ;Get current TB program byte cpi A, '(' ;Open parentheses? breq getRN1 ;If so, continue rjmp unpairedParenError ;Otherwise, unpaired parentheses error ; getRN1: ; rcall expression ;Get parameter n ; getRN2: ; popRP H, L or H, L ;n = 0? lds L, seed3 ;If so, get last random number and return lds H, seed4 brne getRN3 ;Otherwise, continue rjmp getRN4 ;Done ; getRN3: ; ldi ZL, low(seed4) ;Point Z to Seed4 ldi ZH, high(seed4) ; getRN3Loop1: ; ldi B, 8 ;Prepare to loop 8 times ; getRN3Loop2: ; clr C ;Manipulate seeds ld A, Z lsl A adc A, C lsl A adc A, C lsl A adc A, C ld C, Z eor A, C rol A rol A ld A, -Z ld A, -Z ld A, -Z rcall getRN6 rcall getRN6 rcall getRN6 rcall getRN6 sbiw Z, 1 dec B brne getRN3Loop2 ldi C, 0x27 lds A, seed4 andi A, 0x3f sts seed4, A sub C, A brcs getRN3Loop1 brne getRN4 ldi C, 0x10 lds A, seed3 sub C, A brcs getRN3Loop1 ; getRN4: ; rcall skipSpace cpi A, ')' ;Closed parentheses? breq getRN5 ;If so, continue rjmp unpairedParenError ;Otherwise, unpaired parentheses error ; getRN5: ; rcall nextByte ;Get next TB program byte ret ;Done...return with random number in HL ; getRN6: ; ld A, Z ;(Z)->A rol A ;2 * A + carry st Z+, A ;A->(Z) ret ;Done...return with random number in HL ; ; Routine: seedRandomNumber ; ; Purpose: Seed random number with HL. ; seedRandomNumber: ; ldi ZL, low(seed4) ;Point Z to Seed4 ldi ZH, high(seed4) sts seed3, L ;Manipulate seeds sts seed4, H rol L swap L rol H swap H sts seed1, H sts seed2, L ret ; ; Start Custom Functions ; ; Function: DAC(n) ; ; Purpose: Returns value from A/D channel n value in HL ; getADC: ; rcall skipSpace ;Get next non-space TB program byte cpi A, '(' ;Open parentheses? breq getADC1 ;If so, continue rjmp unpairedParenError ;Otherwise, unpaired parentheses error ; getADC1: ; rcall nextByte ;Get next TB program byte rcall expression ;Get A/D channel number n into HL popRP H, L ;Is n on the range of 0 to 5? or H,H ;Is H = 0? breq getADC2 ;If so, continue rjmp overflowError ;Otherwise, overflow error ; getADC2: ; cpi L, 6 ;Is L between 0 and 5 brcs getADC3 ;If so, continue rjmp overflowError ;Otherwise, overflow error ; getADC3: ; ; Set Up Analog-to-Digital Converter ; ldi A,0b01000000 ;0bxxy0zzzz xx = 01 use internal AVcc for reference ("Table 28-3" in ATmega328 Datasheet) ; ; y = 0 right adjust result (Search for "Bit 5 – ADLAR" in ATmega328 Datasheet) ; zzzz = 0000 A/D channel 0 ("Table 28-4" in ATmega328 Datasheet) or A,L ;fix A/D channel to be read by or'ing with n sts admux,A ;ADC Multiplexer Selection Register (Section "28.9.1" in ATmega328 Datasheet) ; ldi A,0b11000111 ;0bxy000zzz x = 1 enable A/D (Search for "Bit 7 – ADEN" in ATmega328 Datasheet) ; y = 1 start conversion (Search for "Bit 6 – ADSC" in ATmega328 Datasheet) ; zzz = 111 prescale = 128 (Section "Table 28-5") sts adcsra,A ;ADC Control and Status Register A (Section "28.9.2" in ATmega328 Datasheet) ; getADC4: ; lds A,adcsra ;Is A/D conversion complete? sbrc A,adsc ;ADSC cleared? rjmp getADC4 ;If not, wait lds L,adcl ;A/D result in HL lds H,adch ; rcall skipSpace ;Get next non-space TB program byte cpi A, ')' ;Closed parentheses? breq getADC5 ;If so, continue rjmp unpairedParenError ;Otherwise, unpaired parentheses error ; getADC5: ; rcall nextByte ;Get next TB program byte ret ;Done...return with A/D value in HL ??? ; ; Function: PIN(n) ; ; Purpose: Returns status of Redboard pins n = 0 to 13 (0=low 1=high) in HL ; getPin: ; ld A, X ;Get current byte cpi A, '(' ;Open Parentheses? breq getPin0 ;If so, continue rjmp unpairedParenError ;Otherwise, unpaired parentheses error ; getPin0: ; rcall nextByteSS ;Get next non-space TB program byte rcall expression ;Evaluate expression for m call skipSpace ;Get first non-space byte cpi A, ')' ;Closed parentheses? breq getPin1 ;If so, continue rjmp unpairedParenError ;Otherwise, unpaired parentheses error ; getPin1: ; popRP h, l ;Get pin number n or h, h ;n should be 0 to 13 so h must be zero? breq getPin2 ;If so, continue rjmp overflowError ;Otherwise, over flow error ; getPin2: ; cpi l, 14 ;n should be 0 to 13, so l must be less than 14 brcs getPin3 ;If so, continue rjmp overflowError ;Otherwise, over flow error ; getPin3: ; cpi l, 8 ;Input to port d (pins 0 to 7)? brcs getPin_portd ;If so, continue to port d code ;Otherwise, port b subi l, 8 ;Remove bias to get bits 0 to 5 rcall cnvtBinBit ;Get bit position into c mov E, C ;Save C in E ldi D, 0xff eor C, D ;Complement C in B,ddrb ;Make sure bit is input and B, C out ddrb,B in B, pinb ;Read pin b to b and B, E ;Check bit at position c = ldi L,1 ;Pin high? brne getPin_done ;If so, continue with L=1 ldi L,0 rjmp getPin_done ;Otherwise, L=0 ; getPin_portd: ; rcall cnvtBinBit ;Get bit position into C mov E,C ;Save C in E ldi D, 0xff eor C, D ;Complement C in B,ddrd ;Make sure bit is input and B, C out ddrd,B in B, pind ;Read pin d to b and B, E ;Check bit at position c ldi L,1 ;Pin high? brne getPin_done ;If so, continue with L=1 clr L rjmp getPin_done ;Otherwise, L=0 ; getPin_done: ; clr H ;H=0 rcall nextByte ;Get next TB program byte ret ;Done...return with pin status in HL ; ; Function: GET(p, l) ; ; Purpose: Returns data in HL from EEPROM where p = page and l = location ; getGet: ; ; Set Up SPI ; ldi A,0b00101100 ;Port b bits 2 (CE), 3 (MOSI), and 5 (SCK) as output ; out ddrb,A ;Update data direction register B sbi portb,2 ;Deselect eeprom ldi A,0b01010001 ;0btuvwxyzz t = 0 disable SPI interrupt (See section 23.5.1) ; u = 1 enable SPI ; v = 0 most significant byte (MSB) first ; w = 1 select ATmega328 as master ; xx = 00 SPI mode 0 ; zz = 01 prescale = 16 for SPI clock = 1 Mhz ("Table 23-5" in ATmega328 Datasheet) out spcr,A ;Configure SPI control register ; ; Check that EEPROM connected ; rcall EEPROM_esig ;Get EEPROM electronic signature cpi A, 41 ;Is 41? breq getGet_cont ;If so, continue rjmp spiError ;Otherwise, spi error ; getGet_cont: ; ld A, X ;Get current byte cpi A, '(' ;Open parentheses? breq getGet0 ;If so, continue rjmp unpairedParenError ;Otherwise, unpaired parentheses error ; getGet0: ; rcall nextByteSS ;Move next non-space byte rcall expression ;Get EEPROM page on numeric stack rcall skipSpace ;Get first non-space byte cpi A, ',' ;Should be a comma? breq getGet1 ;If so, continue rjmp syntaxError ;Otherwise, syntax error ; getGet1: ; rcall nextByteSS ;Get next non-space byte rcall expression ;Get EEPROM location on numeric stack call skipSpace ;Get first non-space byte cpi A, ')' ;Closed parentheses? breq getGet2 ;If so, continue rjmp unpairedParenError ;Otherwise, unpaired parentheses error ; getGet2: ; popRP B, C ;Get location in C push C ;Save location subiw B, C, 128 ;Location must be <= 127? pop C ;Restore location brcs getGet3 ;If so, continue rjmp overflowError ;Otherwise, overflow error ; getGet3: ; lsl C ;Double location (data is two bytes) popRP D, E ;Get page in DE push D ;Save page push E subiw D, E, 512 ;Page must be <= 511? pop E ;Retrieve page pop D brcs getGet4 ;If so, continue rjmp overflowError ;Otherwise, overflow error ; getGet4: ; rcall EEPROM_read_word ;Get EEPROM data into HL rcall nextByte ;Get next TB program byte ret ; ; End Custom Functions ; ; Routine: getVariable ; ; Purpose: Gets value in HL for variable (ASCII A-Z) designated ; by register A. Carry set if variable found; carry cleared otherwise. ; getVariable: rcall makeUpperCase ;If letter, make upper case cpi A, 'A' ;Valid variable (A-Z)? brcs gVar0 ;Otherwise, continue cpi A, 'Z' + 1 brcc gVar0 ;Otherwise, continue subi A, 'A' ;Remove ASCII bias mov E, A ;A->DE clr D lsl E ;2*DE->DE (Allows two bytes per variable) rol D ldi ZL, low(varStart) ;Point Z to start of variables ldi ZH, high(varStart) add ZL, E ;Add variable location bias adc ZH, D ld L, Z+ ;LSB of variable to L ld H, Z+ ;MSB of variable to H adiw X, 1 ;Get next TB program byte sec ;Set carry for successful return ret ;Done...return ; gVar0: ; clc ;Clear carry for unsuccessful return ret ;Done...return ; ; Routine: storeVariable ; ; Purpose: Stores value (first two bytes on numeric stack in low-high order) ; in the variable next on numeric stack ; storeVariable: ; popRP H, L ;value -> HL rcall popA ;ASCII variable (A-Z) -> DE mov E, A ldi D, 0 ; ; Routine: putVariable ; ; Purpose: Store value in HL in variable (A-Z) designated ; by register DE ; putVariable: ; subi E, 'A' ;Remove ASCII bias ; lsl E ;2*DE->DE (allows two bytes per variable) rol D ldi ZL, low(varStart) ;Point Z to start of variables ldi ZH, high(varStart) add ZL, E ;Add variable location bias ; adc ZH, D st Z+, L ;Store LSB st Z+, H ;Store MSB ; ret ;Done...return ; ; Routine: pushS ; ; Purpose: Store SL at the numeric stack pointer location then ; increment numeric stack pointer (Y register); ; store SH at the numeric stack pointer location then ; increment numeric stack pointer (Y register) ; pushS: ; mov A, SL rcall pushA mov A, SH rcall pushA ret ; ; Routine: popS ; ; Purpose: Decrement numeric stack pointer (Y register) and ; load SH from the location, then decrement numeric ; stack pointer (Y register) and load SL from the ; location ; ; Assumes: NA ; popS: ; rcall popA mov SH, A rcall popA mov SL, A ret ; ; Routine: pushA ; ; Purpose: Store A at the numeric stack pointer location then ; increment numeric stack pointer (Y register) ; pushA: ; cpi YL, low(numSTK + numStkSize) breq numStackOverflowError st Y+, A ret ; ; Routine: popA ; ; Purpose: Decrement numeric stack pointer (Y register) and ; load A from the location ; popA: ; cpi YL, low(numSTK) breq numStackUnderflowError ld A, -Y ret ; ; Routine: Clear output buffer ; clearOutputBuffer: ; ldi ZL, low(outBuffer) ;Point Z to start of output buffer ldi ZH, high(outBuffer) ldi A, outBufferSize ;Output buffer size -> A clr B ;0 -> B ; clearOutputBufferLoop: ; st Z+, B ;B -> (Z) then increment Z dec A ;Decrement A brne clearOutputBufferLoop ;If A not zero, loop clr A ;Set output buffer pointer to zero sts outBufPtr, A ret ;Done...return ; ; Error handling - Set B to error code (1-xx) ; syntaxError: ; ldi b, 0 rjmp error ; directModeError: ; ldi B, 1 rjmp error ; runModeError: ; ldi B, 2 rjmp error ; subLevelMaxError: ; ldi b, 3 rjmp error ; subReturnError: ; ldi b, 4 rjmp error ; lineNumberNotFoundError: ; ldi b, 5 rjmp error ; expectedLineNumberError: ; ldi b, 6 rjmp error ; overflowError: ; ldi B, 7 rjmp error ; divideByZeroError: ; ldi B, 8 rjmp error ; ; numStackOverflowError: ; ldi B, 9 rjmp error ; ; numStackUnderflowError: ; ldi B, 10 rjmp error ; outBufferOverflowError: ; ldi B, 11 rjmp error ; unpairedParenError: ; ldi B, 12 rjmp error ; missingRelopError: ; ldi B, 13 rjmp error ; expectedVariableError: ; ldi B, 14 rjmp error expectedEOLError: ; ldi B, 15 rjmp error ; expectedNumberError: ; ldi B, 16 rjmp error ; outOfMemoryError: ; ldi B, 17 rjmp error; ; spiError: ; ldi B, 18 rjmp error ; error: ; mov errorCode, B ;Store error code ; error0: ; rcall clearOutputBuffer ;Clear output buffer rcall crlf ;New line ldi L, low(errorMsg0) ;Point HL to first error message ldi H, high(errorMsg0) rcall msgOut ;Write to output buffer mov L, errorCode ;Put error number on numeric stack clr H pushRP H, L ldi L, low(100) ;Put 100 on numeric stack ldi H, high(100) pushRP H, L rcall add16Stk ;Add them; error number plus 100 now on top of numeric stack rcall printNumber ;Write it to output buffer ldi L, low(errorMsg1) ;Point HL to second error message ldi H, high(errorMsg1) ; error1: ; rcall msgOut ;Write it to output buffer pushRP CLNH, CLNL ;Put current line number on numeric stack rcall printNumber ;Write it to output buffer ldi A, CR ;Write a CR to output buffer rcall putByte rcall dumpOutBuf ;Send output buffer to serial port rcall crlf ;New line ; rjmp command ;Back to command mode ; errorMsg0: ; .db "ERROR ", 0xff, 0 ; errorMsg1: ; .db " IN LINE ", 0xff ; ; ; Input: Binary value in A, T flag set to inhibit leading zeros ; ; Returns: Nothing ; ; Registers Used: r16,r17,r18,sreg ; decout: mov r18,A ;r16 -> r18 ldi A,' ' ;output space rcall xmtByte ldi A,'0'-1 ; ASCII 0 less 1 -> r16 dloop100: inc A ;next ACSCII numeral subi r18,100 ;subtract 100 brcc dloop100 ;if r18 > 0 then do again addi r18,100 ;otherwise, add back 100 rcall xmtByte ;output ASCII numneral ; ldi A,'0'-1 ; ASCII 0 less 1 -> r16 dloop10: inc A ;next ACSCII numeral subi r18,10 ;subtract 10 brcc dloop10 ;if r18 > 0 then do again addi r18,10 ;otherwise, add back 10 rcall xmtByte ;output ASCII numneral ldi A,'0'-1 ; ASCII 0 less 1 -> r16 dloop1: inc A ;next ASCII numeral subi r18,1 ;subtract 1 brcc dloop1 ;if r18 > 0 then do again addi r18,1 ;otherwise, add back 1 rcall xmtByte ;output ASCII numneral and return self: rjmp self ; ; Data Segment ; .dseg ; .org SRAM_START ; ; Variable Storage ; ; A - Z each a dataword ; varStart: .byte 2 * 26 ; ; Keyboard input buffer ; inBuffer: .byte inBufferSize ; ; Monitor output buffer ; outBuffer: .byte outBufferSize + 1 ; outBufPtr: .byte 1 ; ; Random number bytes ; seed1: .byte 1 seed2: .byte 1 seed3: .byte 1 seed4: .byte 1 ; ; Numeric stack ; numStk: .byte numStkSize ; ; Custom SRAM ; delay: .byte 2 ;delay in ms ; prgEnd: .byte 2 ; ; TINY BASIC program start ; prgStart: .byte 1