eris2010

Documentation: http://frombelow.net/projects/eris2010/
Clone: git clone https://git.frombelow.net/eris2010.git
Log | Files | Refs | Submodules | README | LICENSE

tinybasic.asm (55700B)


      1 ; v0.2.2
      2 ;
      3 ; Bill O'Neill - Last update: 2011/11/11
      4 ;
      5 ; Monitor code is Open License and can be used freely
      6 ; Tiny Basic code is Copyright, Tom Pitman
      7 ;
      8 ; Consist of a minimal terminal monitor and Tom
      9 ; Pitman's Tiny Basic as a high-level
     10 ; programming language
     11 ;
     12 ; This code assembles as-is with the macro assembler in the
     13 ; Michal Kowalski simulator.
     14 ;
     15 ; It should be easy enough to configure this to run any-
     16 ; where in memory or convert it to assemble with any 6502
     17 ; assembler.
     18 ;
     19 ; Next steps:
     20 ;        More comments to document this code
     21 ;
     22 ;
     23 ; Revision History:
     24 ;
     25 ; v0.2.2q - 2017/08/12
     26 ;        Reverse engineering the code; added a lot of labels
     27 ;        and comments to the source code. Still a work in progress.
     28 ;
     29 ; v0.2.2p - 2017/07/25
     30 ;        Ported to Simple 65816 computer by TBW. Recoded so ACME
     31 ;        assembler can assemble it; changes made to I/O calls
     32 ;        and warm boot vector; and implement input line hook.
     33 ;        Also modified the startup code to avoid video memory
     34 ;        area. One difficulty: The BIOS's PRCH treats CR as if
     35 ;        it is a CR/LF sequence, which may play havoc with Tiny
     36 ;        Basic in its current form. We'll see...
     37 ;
     38 ; v0.2.2 - 2011/11/11
     39 ;        Reduced version containing only a terminal monitor
     40 ;        for a 6850 ACIA and Tom Pitman's Tiny Basic
     41 ;
     42 ; v0.2.1 - 2011/05/18
     43 ;        Ported to Michal Kowalski's macro assembler
     44 ;
     45 ; v0.2.0 - 2011/01/04
     46 ;        Corrected some label problems
     47 ;        Added/corrected some comments
     48 ;
     49 ; v0.1.3 - 2009/11/28
     50 ;        Changed the look-up table for the IL op-code
     51 ;          handlers to use labels instead of literal addresses
     52 ;          this helps make the code re-locatable.
     53 ;        Added some comments to source
     54 ;
     55 ; v0.1.2 - 2009/01/12
     56 ;        Added BREAK routine
     57 ;        Fixed my bad reference to error string " AT "
     58 ;        Compressed gaps in monitor code
     59 ;        Added some comments to source
     60 ;
     61 ; v0.1.1 - 2008/12/15
     62 ;        Initial working version
     63 ; 
     64 ;
     65 ; Notes:
     66 ;  - I changed the prompt character from a ":" ($3A) to a ">" ($3E) for no
     67 ;    other reason than I think it looks a bit better. The prompt character
     68 ;    is the second byte of the IL program table.
     69 ;
     70 ;  - This version is to run in Simple 65816. The memory map is as follows.
     71 ;
     72 ;    $0000-$CFFF     RAM (was: $0000-$7FFF)
     73 ;    $D000-$EFFF     Video RAM, I/O and microRAM area
     74 ;    ($F000-$F7FF     I/O - ACIA is at $F000 ... will be deleted)
     75 ;    $F000-$FBFF     ROM - Tiny Basic (was: $8000-$EFFF)
     76 ;    $FC00-$FFFF     ROM - Simple monitor
     77 ;
     78 ;  - Starting address in this version (referred to as "S" in the EXPERIMENTER'S
     79 ;    KIT) is $F000 (was: $8000)
     80 
     81 	.include "os.inc"
     82 	
     83 
     84 ;
     85 ; Tiny Basic starts here
     86 ;
     87 
     88 ; Zero page variables
     89 
     90 LOWEST   =        $20               ; Lowest address of user program area
     91 HIGHST   =        $22               ; Highest address of user program area
     92 STACK    =        $24               ; End of user program area plus stack reserve
     93 RETPTR   =        $26               ; Top of GOSUB stack
     94 LINNUM   =        $28               ; Current line number of BASIC line
     95 
     96 PGMPTR   =        $2A               ; Pointer to TBIL program table
     97 TXTPTR   =        $2C               ; Pointer to program text area
     98 
     99 INPLIN   =        $30               ; Input line buffer and computation stack ($30-$7F)
    100 RNDNUM   =        $80               ; Random number generator workspace
    101 VARS     =        $82               ; Variable "A" at $82-$83, "B" at $84-$85, etc. ($82-$B5)
    102 TEMPS    =        $B6               ; Interpreter temporaries ($B6-$C7)
    103 
    104 WORK     =        $BC               ; Working register (two byte pair)
    105 RUNNIN   =        $BE               ; Running status flag
    106 
    107 CSTOP    =        $C0               ; Computation stack pointer boundary variable
    108 CSPTR    =        $C1               ; Computation stack pointer (points to $0030-$007F area)
    109                                     ; Note that CSPTR+1 is set to zero (in WARM_S routine) so that
    110                                     ;   (CSPTR) actually points to $0030-$007F stack area as well,
    111                                     ;   which is used in XCHBYT routine
    112 
    113 TERMPOS  =        $BF               ; Terminal position
    114 
    115 TXTBGN   =        tiny_basic_end    ; Start of available RAM area
    116 ENDMEM   =        $E000             ; Barrier against video RAM area in Simple 65816
    117 
    118 START
    119 
    120          jmp      FBLK              ; Jump to initialization code. So load address is start address.
    121 
    122 CV       jmp      COLD_S            ; Cold start vector
    123 WV       jmp      WARM_S            ; Warm start vector
    124 IN_V     jmp      RCCHR             ; Input routine address. 
    125 OUT_V    jmp      SNDCHR            ; Output routine address.
    126 BV       jmp      CHKBREAK          ; Begin check break routine
    127 
    128 ;
    129 ; Some codes
    130 ;
    131 BSC      .byte $5f                   ; Backspace code
    132 LSC      .byte $18                   ; Line cancel code
    133 PCC      .byte $80                   ; Pad character control
    134 TMC      .byte $00                   ; Tape mode control
    135 SSS      .byte $04                   ; Spare Stack size. (was $04 but documentation suggests $20)
    136 
    137 ;
    138 ; Code fragment for 'PEEK' and 'POKE'
    139 ;
    140 PEEK     stx $C3                   ; 'PEEK' - store X in $C3
    141          bcc LBL008                ; On carry clear goto LBL008
    142          stx $C3                   ; 'POKE' - store X in $C3
    143          sta ($C2),y               ; Store A in location pointed to by $C3 (hi) and Y (lo)
    144          rts                       ; Return
    145 LBL008   lda ($C2),y               ; Load A with value pointed to by $C3 (hi) and Y (lo)
    146          ldy #$00                  ; Reset Y
    147          rts                       ; Return
    148 
    149 ;
    150 ; The following table contains the addresses for the ML handlers for the IL opcodes.
    151 ;
    152                                      ; ($30-$3F) (need to annotate that)
    153 SRVT     .word  IL_BBR               ; ($40-$5F) Backward Branch Relative
    154          .word  IL_FBR               ; ($60-$7F) Forward Branch Relative
    155          .word  IL__BC               ; ($80-$9F) String Match Branch
    156          .word  IL__BV               ; ($A0-$BF) Branch if not Variable
    157          .word  IL__BN               ; ($C0-$DF) Branch if not a Number
    158          .word  IL__BE               ; ($E0-$FF) Branch if not End of line
    159          ; ($00-$07) opcodes are used for stack exchange; no addresses needed here
    160          .word  IL__NO               ; ($08) No Operation
    161          .word  IL__LB               ; ($09) Push Literal Byte onto Stack
    162          .word  IL__LN               ; ($0A) Push Literal Number
    163          .word  IL__DS               ; ($0B) Duplicate Top two bytes on Stack
    164          .word  IL__SP               ; ($0C) Stack Pop
    165          .word  IL__NO               ; ($0D) (Reserved)
    166          .word  IL__NO               ; ($0E) (Reserved)
    167          .word  IL__NO               ; ($0F) (Reserved)
    168          .word  IL__SB               ; ($10) Save Basic Pointer
    169          .word  IL__RB               ; ($11) Restore Basic Pointer
    170          .word  IL__FV               ; ($12) Fetch Variable
    171          .word  IL__SV               ; ($13) Store Variable
    172          .word  IL__GS               ; ($14) Save GOSUB line
    173          .word  IL__RS               ; ($15) Restore saved line
    174          .word  IL__GO               ; ($16) GOTO
    175          .word  IL__NE               ; ($17) Negate
    176          .word  IL__AD               ; ($18) Add
    177          .word  IL__SU               ; ($19) Subtract
    178          .word  IL__MP               ; ($1A) Multiply
    179          .word  IL__DV               ; ($1B) Divide
    180          .word  IL__CP               ; ($1C) Compare
    181          .word  IL__NX               ; ($1D) Next BASIC statement
    182          .word  IL__NO               ; ($1E) (Reserved)
    183          .word  IL__LS               ; ($1F) List the program
    184          .word  IL__PN               ; ($20) Print Number
    185          .word  IL__PQ               ; ($21) Print BASIC string
    186          .word  IL__PT               ; ($22) Print Tab
    187          .word  IL__NL               ; ($23) New Line
    188          .word  IL__PC               ; ($24) Print Literal String
    189          .word  IL__NO               ; ($25) (Reserved)
    190          .word  IL__NO               ; ($26) (Reserved)
    191          .word  IL__GL               ; ($27) Get input Line
    192          .word  ILRES1               ; ($28) (Seems to be reserved - No IL opcode calls this)
    193          .word  ILRES2               ; ($29) (Seems to be reserved - No IL opcode calls this)
    194          .word  IL__IL               ; ($2A) Insert BASIC Line
    195          .word  IL__MT               ; ($2B) Mark the BASIC program space Empty
    196          .word  IL__XQ               ; ($2C) Execute
    197          .word  WARM_S               ; ($2D) Stop (Warm Start)
    198          .word  IL__US               ; ($2E) Machine Language Subroutine Call
    199          .word  IL__RT               ; ($2F) IL subroutine return
    200 
    201 ERRSTR   .text   " AT "               ; " AT " string used in error reporting.  Tom was right about this.
    202          .text   $80                  ; String terminator
    203 
    204 PGMADR   .word  ILTBL                ; Address of IL program table
    205 
    206 ;
    207 ; Begin Cold Start
    208 ;
    209 ; Load start of free ram (TXTBGN; was: $0200) into LOWEST
    210 ; and initialize the address for end of free ram (HIGHST)
    211 ;
    212 COLD_S   lda #<TXTBGN               ; Load accumulator with TXTBGN
    213          sta LOWEST                 ; Store $00 in $20
    214          sta HIGHST                 ; Store $00 in $22
    215          lda #>TXTBGN               ; Load accumulator with TXTBGN
    216          sta LOWEST+1               ; Store TXTBGN in $21
    217          sta HIGHST+1               ; Store TXTBGN in $23
    218 ;
    219 ;
    220 ; Begin test for free RAM
    221 ;
    222 
    223          ldy #1                     ; Load register Y with 1
    224 MEM_T    lda (HIGHST),y             ; Load accumulator With the contents of a byte of memory
    225          tax                        ; Save it to X
    226          eor #$FF                   ; Next 4 instuctions test to see if this memory location
    227          sta (HIGHST),y             ;   is RAM by trying to write something new to it - new value
    228          cmp (HIGHST),y             ;   gets created by XORing the old value with $FF - store the
    229          php                        ;   result of the test on the stack to look at later
    230          txa                        ; Retrieve the old memory value
    231          sta (HIGHST),y             ; Put it back where it came from
    232          inc HIGHST                 ; Increment HIGHST (for next memory location)
    233          bne SKP_PI                 ; Skip if we don't need to increment page
    234          inc HIGHST+1               ; Increment HIGHST+1 (for next memory page)
    235 SKP_PI   lda HIGHST+1               ; Get high byte of memory address
    236          cmp #>ENDMEM               ; Did we reach start address of Tiny Basic?
    237          bne PULL                   ; Branch if not
    238          lda HIGHST                 ; Get low byte of memory address
    239          cmp #<ENDMEM               ; Did we reach start address of Tiny Basic?
    240          beq TOP                    ; If so, stop memory test so we don't overwrite ourselves
    241 PULL
    242          plp                        ; Now look at the result of the memory test
    243          beq MEM_T                  ; Go test the next memory location if the last one was RAM
    244 TOP
    245          dey                        ; If last memory location did not test as RAM, decrement Y (should be zero now)
    246 ;
    247 ; TBIL MT (Mark the BASIC program space Empty)
    248 ;
    249 IL__MT   cld                        ; Make sure we're not in decimal mode
    250          lda LOWEST                 ; Load up the low order byte of the start of free ram
    251          adc SSS                    ; Add to the spare stack size
    252          sta $24                    ; Store the result in $0024
    253          tya                        ; Y is zero
    254          adc LOWEST+1               ; And add it to the high order byte of the start of free RAM
    255          sta $25                    ; Store the result in $0025
    256          tya                        ; Retrieve Y again
    257          sta (LOWEST),y             ; Store A in the first byte of program memory
    258          iny                        ; Increment Y
    259          sta (LOWEST),y             ; Store A in the second byte of program memory
    260 ;
    261 ; Begin Warm Start
    262 ;
    263 WARM_S   lda HIGHST                 ; Set $C6 and RETPTR to HIGHST
    264          sta $C6
    265          sta RETPTR
    266          lda HIGHST+1
    267          sta $C7
    268          sta RETPTR+1
    269          jsr P_NWLN                 ; Go print CR, LF and pad characters
    270 ;
    271 ; Restart the interpreter state
    272 ;
    273 RESTRT   lda PGMADR                 ; Reset the start of the IL Table
    274          sta PGMPTR                 ;   by setting PGMPTR to PGMADR
    275          lda PGMADR+1               ;
    276          sta PGMPTR+1
    277          lda #$80                   ; Reset the computation stack pointer
    278          sta CSPTR                  ;   to bottom
    279          lda #$30
    280          sta CSTOP                  ; Set computation stack top boundary to $30
    281          ldx #$00                   ; Set RUNNIN to zero
    282          stx RUNNIN
    283          stx CSPTR+1                ; CSPTR+1 is permanently set to zero
    284          dex
    285          txs                        ; Reset system stack pointer to $FF (bottom)
    286 
    287 ;
    288 ; IL execution loop
    289 ;
    290 loop    cld                        ; Make sure we're in binary mode 
    291          jsr PGMBYT                 ; Go read a byte from the IL program table
    292          jsr EXECUT                 ; Go decide what to do with it
    293          jmp loop                  ; Repeat
    294 ;
    295 ;
    296 ;
    297          .byte $83                  ; No idea about this
    298          .byte $65                  ; No idea about this
    299 ;
    300 ;
    301 ; Routine to service the TBIL Instructions
    302 ;
    303 EXECUT   cmp #$30                   ;
    304          bcs LBL011                 ; If it's $30 or higher, it's a Branch or Jump - go handle it
    305          cmp #$08                   ; 
    306          bcc XCHBYT                 ; If it's less than $08, it's a stack exchange - go handle it
    307          asl a                        ; Multiply the OP code by 2 
    308          tax                        ;   and make it an index
    309 EXEC     lda SRVT-$03,x             ; Get the high byte of the OP Code handling routine
    310          pha                        ;   and save it on the stack
    311          lda SRVT-$04,x             ; Get the low byte
    312          pha                        ;   and save it on the stack
    313          php                        ; Save the processor status too
    314          rti                        ; Now go execute the OP Code handling routine
    315 ;
    316 ;
    317 ; Routine to handle the stack exchange
    318 ; Exchange the low byte of TOS with the low byte of CSPTR+n,
    319 ;   where n is passed in accumulator
    320 ;
    321 XCHBYT   adc CSPTR                  ; Add index number (should be even number) to
    322          tax                        ;   CSPTR so that it points to CSPTR+n
    323          lda (CSPTR),y              ; Get low byte of TOS
    324          pha
    325          lda $00,x                  ; Get low byte of CSPTR+n and
    326          sta (CSPTR),y              ;   write into low byte of TOS
    327          pla
    328          sta $00,x                  ; Write original low byte of TOS into
    329          rts                        ;   low byte of CSPTR+n and exit
    330 ;
    331 ; Print error message?
    332 ;
    333 PRERR    jsr P_NWLN                 ; Go print CR, LF and pad characters
    334          lda #'!'                   ; '!' character
    335          jsr OUT_V                  ; Go print it
    336          lda PGMPTR                 ; Load the current TBIL pointer (low) 
    337          sec                        ; Set the carry flag
    338          sbc PGMADR                 ; Subtract the TBIL table origin (low)
    339          tax                        ; Move the difference to X
    340          lda PGMPTR+1               ; Load the current TBIL pointer (high)
    341          sbc PGMADR+1               ; Subtract the TBIL table origin (high)
    342          jsr PRAXNM
    343          lda RUNNIN                 ; Was the program in running state?
    344          beq serr                  ; No, just a simple error (bell)
    345          lda #<ERRSTR               ; Get low byte of error string address
    346          sta PGMPTR                 ; Put in PGMPTR
    347          lda #>ERRSTR               ; Get high byte of error string address
    348          sta PGMPTR+1               ; Put in PGMPTR+1
    349          jsr IL__PC                 ; Go report an error has been detected
    350          ldx LINNUM                 ; Print the current line number
    351          lda LINNUM+1
    352          jsr PRAXNM
    353 serr    lda #$07                   ; ASCII Bell
    354          jsr OUT_V                  ; Go ring Bell
    355          jsr P_NWLN                 ; Go print CR, LF and pad characters
    356 CLRSTK   lda RETPTR                 ; Set $C6 to RETPTR
    357          sta $C6
    358          lda RETPTR+1
    359          sta $C7
    360          jmp RESTRT
    361 ;
    362 ; Pop computation stack pointer
    363 ;
    364 POPNBR   ldx #$7C                   ; Does the computation stack have at
    365 POPNB1   cpx CSPTR                  ;   least two items (four bytes)?
    366 PRERR1   bcc PRERR                  ; No, error
    367          ldx CSPTR                  ; Load old computation stack pointer
    368          inc CSPTR                  ;   into X and increment computation
    369          inc CSPTR                  ;   stack pointer by two
    370          clc                        ; Carry cleared for use by math routines
    371          rts
    372 ;
    373 ; TBIL Backward Branch Relative
    374 ;
    375 IL_BBR   dec WORK+1                 ; Entry point for
    376 ;
    377 ; TBIL Forward Branch Relative
    378 ;
    379 IL_FBR   lda WORK+1                 ; Entry point for
    380          beq PRERR
    381 LBL017   lda WORK                   ; Set PGMPTR to WORK
    382          sta PGMPTR
    383          lda WORK+1
    384          sta PGMPTR+1
    385          rts
    386 ;
    387 ; Jump handling routine
    388 ;
    389 LBL011   cmp #$40
    390          bcs LBL016                 ; If it's not a Jump, go to branch handler
    391          pha
    392          jsr PGMBYT                 ; Go read a byte from the TBIL table
    393          adc PGMADR
    394          sta WORK
    395          pla
    396          pha
    397          and #$07
    398          adc PGMADR+1
    399          sta WORK+1
    400          pla
    401          and #$08
    402          bne LBL017
    403          lda WORK                   ; Swap WORK and PGMPTR
    404          ldx PGMPTR
    405          sta PGMPTR
    406          stx WORK
    407          lda WORK+1
    408          ldx PGMPTR+1
    409          sta PGMPTR+1
    410          stx WORK+1
    411 LBL126   lda $C6                    ; Decrement $C6 by 1
    412          sbc #$01
    413          sta $C6
    414          bcs skip
    415          dec $C7
    416 skip    cmp $24                    ; Is $C6 < $24?
    417          lda $C7
    418          sbc $25
    419          bcc PRERR1                 ; Yes, error (go to PRERR)
    420          lda WORK
    421          sta ($C6),y
    422          iny
    423          lda WORK+1
    424          sta ($C6),y
    425          rts
    426 ;
    427 ;
    428 ; Branch Handler
    429 ;
    430 LBL016   pha
    431          lsr a
    432          lsr a
    433          lsr a
    434          lsr a
    435          and #$0E
    436          tax
    437          pla
    438          cmp #$60                   ; Is it a forward branch IL code?
    439          and #$1F
    440          bcs LBL020                 ; Yes, go and add its offset
    441          ora #$E0                   ; Create a negative offset
    442 LBL020   clc
    443          beq LBL021                 ; Offset is zero, so skip the addition
    444          adc PGMPTR                 ; Add offset to PGMPTR and save to WORK
    445          sta WORK
    446          tya
    447          adc PGMPTR+1
    448 LBL021   sta WORK+1
    449          jmp EXEC                   ; And go to IL table dispatcher
    450 ;
    451 ; TBIL BC (String Match Branch)
    452 ;
    453 IL__BC   lda TXTPTR                 ; Save TXTPTR into $B8
    454          sta $B8
    455          lda TXTPTR+1
    456          sta $B9
    457 match   jsr CHRGOT
    458          jsr CHRGET
    459          eor (PGMPTR),y             ; Test for char match and end of
    460          tax                        ;   string (high bit), then save it
    461          jsr PGMBYT                 ; Go read a byte from the TBIL table
    462          txa                        ; Is it a plain match?
    463          beq match                 ; Yes, continue checking for a match
    464          asl a                        ; Mask out high bit, then is it a final match?
    465          beq BCEXIT                 ; Yes, exit
    466          lda $B8                    ; Restore TXTPTR from $B8
    467          sta TXTPTR
    468          lda $B9
    469          sta TXTPTR+1
    470 DO_FBR   jmp IL_FBR                 ; Match failed, so do a (forward) branch
    471 ;
    472 ; TBIL BE (Branch if not End of line)
    473 ;
    474 IL__BE   jsr CHRGOT                 ; Check that CR is there
    475          cmp #$0D
    476          bne DO_FBR                 ; Else do a (forward) branch
    477 BCEXIT   rts
    478 ;
    479 ; TBIL BV (Branch if not Variable)
    480 ;
    481 IL__BV   jsr CHRGOT                 ; Get current char from program area
    482          cmp #'Z'+1                 ; Is it a letter ('A' to 'Z')?
    483          bcs DO_FBR                 ; No, do a (forward) branch
    484          cmp #'A'
    485          bcc DO_FBR                 ; No, do a (forward) branch
    486          asl a                        ; Yes, so create an index out of it
    487          jsr PSHACC                 ;   and push it on stack
    488 CHRGET   ldy #$00
    489          lda (TXTPTR),y             ; Get a char from program text
    490          inc TXTPTR                 ;   and increment TXTPTR by one
    491          bne chk
    492          inc TXTPTR+1
    493 chk     cmp #$0D                   ; CR?
    494          clc
    495          rts
    496 ;
    497 ; CHRGOT - Starting with current character in the program area, skip
    498 ;          any blanks until a nonblank character is reached, and return
    499 ;          with carry clear (nondigit) or set (digit)
    500 ;
    501 chgot1   jsr CHRGET
    502 CHRGOT   lda (TXTPTR),y             ; Get a char from program text
    503          cmp #' '                   ; Space?
    504          beq chgot1                 ; Yes, skip it
    505          cmp #':'                   ; Colon?
    506          clc
    507          bpl exit                  ; Yes, exit with carry flag clear
    508          cmp #'0'                   ; Digit char? (carry set if yes)
    509 exit    rts
    510 ;
    511 ; TBIL BN (Branch if not a Number)
    512 ;
    513 IL__BN   jsr CHRGOT                 ; Get current char from program area
    514          bcc DO_FBR                 ; Not a digit, so do a (forward) branch
    515          sty WORK                   ; Set WORK to zero
    516          sty WORK+1
    517 loop1   lda WORK                   ; Set WORK to 10*WORK
    518          ldx WORK+1
    519          asl WORK
    520          rol WORK+1
    521          asl WORK
    522          rol WORK+1
    523          clc
    524          adc WORK
    525          sta WORK
    526          txa
    527          adc WORK+1
    528          asl WORK
    529          rol a
    530          sta WORK+1
    531          jsr CHRGET                  ; Get next char from program area
    532          and #$0F                    ; Assuming it is a digit, get the value
    533          adc WORK                    ;   and add it to WORK
    534          sta WORK
    535          tya
    536          adc WORK+1
    537          sta WORK+1
    538          jsr CHRGOT                  ; Get the same char again
    539          bcs loop1                  ; It is a digit, so continue adding it to WORK
    540          jmp PSHWRK
    541 ;
    542 ; Find BASIC line with target line number
    543 ;
    544 FINDLN   jsr IL__SP                 ; Pop the number into WORK
    545          lda WORK                   ; Is WORK zero?
    546          ora WORK+1
    547          beq PQERR                  ; Yes, print error
    548 FNDLN1   lda LOWEST                 ; Set TXTPTR to LOWEST
    549          sta TXTPTR
    550          lda LOWEST+1
    551          sta TXTPTR+1
    552 LBL040   jsr GETNUM
    553          beq LBL038
    554          lda LINNUM                 ; Is LINNUM >= WORK?
    555          cmp WORK
    556          lda LINNUM+1
    557          sbc WORK+1
    558          bcs LBL038                 ; Yes, ...
    559 skip5   jsr CHRGET                 ; Skip the BASIC program line
    560          bne skip5                 ;   by searching for $00 sentinel
    561          jmp LBL040                 ; Continue looking for ...
    562 LBL038   lda LINNUM                 ; Test whether LINNUM = WORK
    563          eor WORK
    564          bne skip6
    565          lda LINNUM+1
    566          eor WORK+1
    567 skip6   rts
    568 ;
    569 ; TBIL PC (Print Literal String)
    570 ;
    571 pcloop   jsr CPRCHR
    572 IL__PC   jsr PGMBYT                 ; Go read a byte from the TBIL table
    573          bpl pcloop                 ; ...else fall thru to ...
    574 ;
    575 ; Counted printing a character
    576 ;
    577 CPRCHR   inc TERMPOS                ; Update terminal position
    578          bmi nopr                  ; 127 is maximum allowed; won't print beyond that
    579          jmp OUT_V                  ; Go print it
    580 nopr    dec TERMPOS                ; Keep TERMPOS at its maximum
    581 prexit   rts
    582 ;
    583 ;
    584 ;
    585 LBL046   cmp #'"'                   ; Is it a quote?
    586          beq prexit                 ; No, quit
    587          jsr CPRCHR
    588 ;
    589 ; TBIL PQ (Print BASIC string)
    590 ;
    591 IL__PQ   jsr CHRGET                 ; Entry point for
    592          bne LBL046
    593 PQERR    jmp PRERR
    594 ;
    595 ; TBIL PT (Print Tab)
    596 ;
    597 IL__PT   lda #' '                   ; Print a space
    598          jsr CPRCHR
    599          lda TERMPOS
    600          and #$87                   ; Do a modulo of 8, plus see if it it has gone past 127
    601          bmi prexit                 ; Yes, it went past 127, so quit
    602          bne IL__PT                 ; It is not divisible by 8, so continue printing spaces
    603          rts                        ; Else it's all done
    604 ;
    605 ; TBIL CP (Compare)
    606 ;
    607 IL__CP   ldx #$7B                   ; Make sure the computation stack has
    608          jsr POPNB1                 ;   at least 5 bytes, then decrement
    609          inc CSPTR                  ;   CSPTR by 5 bytes (POPNB1 already
    610          inc CSPTR                  ;   decremented it by 2)
    611          inc CSPTR
    612          sec                        ; Subtract TOS from $03 and store into TOS
    613          lda $03,x
    614          sbc $00,x
    615          sta $00,x
    616          lda $04,x
    617          sbc $01,x
    618          bvc LBL052                 ; No overflow
    619          eor #$80                   ; No idea what it does
    620          ora #$01
    621 LBL052   bmi LBL053                 ; It's negative, so that means TOS < $03
    622          bne LBL054
    623          ora $00,x
    624          beq LBL049
    625 LBL054   lsr $02,x
    626 LBL049   lsr $02,x
    627 LBL053   lsr $02,x
    628          bcc LBL050
    629 PGMBYT   ldy #$00                   ; Read a byte from the TBIL Table
    630          lda (PGMPTR),y             ;
    631          inc PGMPTR                 ; Increment TBIL Table pointer as required
    632          bne skip0                 ;
    633          inc PGMPTR+1               ;
    634 skip0   ora #$00                   ; Check for $00 and set the 'Z' flag acordingly
    635 LBL050   rts                        ; Return
    636 ;
    637 ; TBIL NX (Next BASIC statement)
    638 ;
    639 IL__NX   lda RUNNIN                 ; Is the program running?
    640          beq QUIT                   ; No, go to inputting
    641 skip7   jsr CHRGET                 ; Skip rest of BASIC statement until it hits $00
    642          bne skip7
    643          jsr GETNUM                 ; Get BASIC line number
    644          beq RPERR                  ; It's zero, so error
    645 DOSTMT   jsr LBL058                 ; Set RUNNIN to 1
    646          jsr BV                     ; Test for break
    647          bcs RESETP                 ; Break invoked, so quit running
    648          lda $C4                    ; Set PGMPTR to $C4
    649          sta PGMPTR
    650          lda $C5
    651          sta PGMPTR+1
    652          rts
    653 ;
    654 ; Reset IL program pointer and go to error
    655 ;
    656 RESETP   lda PGMADR                 ; Reset PGMPTR back to the beginning of
    657          sta PGMPTR                 ;   the IL program table (PGMADR)
    658          lda PGMADR+1
    659          sta PGMPTR+1
    660 RPERR    jmp PRERR                  ; And go to error
    661 ;
    662 ;
    663 ;
    664 QUIT     sta TERMPOS                ; Set TERMPOS to zero,
    665          jmp CLRSTK                 ;   clear stack and resume inputting
    666 ;
    667 ; TBIL XQ (Execute)
    668 ;
    669 IL__XQ   lda LOWEST                 ; Set TXTPTR to LOWEST
    670          sta TXTPTR
    671          lda LOWEST+1
    672          sta TXTPTR+1
    673          jsr GETNUM                 ; Get line number
    674          beq RPERR                  ; Error if it's zero
    675          lda PGMPTR                 ; Set $C4 to PGMPTR
    676          sta $C4
    677          lda PGMPTR+1
    678          sta $C5
    679 LBL058   lda #$01                   ; Set RUNNIN to 1
    680          sta RUNNIN
    681          rts
    682 ;
    683 ; TBIL GO (GOTO)
    684 ;
    685 IL__GO   jsr FINDLN                 ; Find BASIC line with target line number
    686          beq DOSTMT                 ; Found; execute it
    687 GOERR    lda WORK                   ; Otherwise set LINNUM to WORK
    688          sta LINNUM
    689          lda WORK+1
    690          sta LINNUM+1
    691          jmp PRERR                  ;   and print error
    692 ;
    693 ; TBIL RS (Restore saved line)
    694 ;
    695 IL__RS   jsr LBL063                 ; Entry point for
    696          jsr LBL064
    697          jsr FNDLN1
    698          bne GOERR
    699          rts
    700 ;
    701 ; Read line number into LINNUM
    702 ;
    703 GETNUM   jsr CHRGET                 ; Read next two bytes in program area
    704          sta LINNUM                 ;   into LINNUM, and return with zero flag
    705          jsr CHRGET                 ;   set according to whether LINNUM is zero
    706          sta LINNUM+1
    707          ora LINNUM
    708          rts
    709 ;
    710 ; TBIL DS (Duplicate Top two bytes on Stack)
    711 ;
    712 IL__DS   jsr IL__SP                 ; Pop TOS onto WORK then push WORK twice
    713          jsr PSHWRK
    714 PSHWRK   lda WORK+1                 ; Push WORK onto computation stack
    715 PSHWKA   jsr PSHACC                 ; Push WORK(low)/Accum(high) onto
    716          lda WORK                   ;   computation stack
    717 PSHACC   ldx CSPTR                  ; Push accumulator onto computation
    718          dex                        ;   stack
    719          sta $00,x
    720          stx CSPTR                  ; Update computation stack pointer
    721          cpx CSTOP                  ; Has it hit the top boundary of
    722          bne IL__NO                 ;   computation stack area? No
    723 LBL068   jmp PRERR                  ; Error: computation stack overflow
    724 ;
    725 ; Pop a byte from computation stack
    726 ;
    727 POPBYT   ldx CSPTR                  ; Load computation stack pointer
    728          cpx #$80                   ; Is the stack empty?
    729          bpl LBL068                 ; Yes, error
    730          lda $00,x                  ; Pop a byte from the stack
    731          inc CSPTR                  ;   and update the pointer
    732 ;
    733 ; TBIL NO (No Operation)
    734 ;
    735 IL__NO   rts                        ; Just that...no operation :-)
    736 ;
    737 ; Print acc/X as (unsigned) number
    738 ;
    739 PRAXNM   sta WORK+1                 ; Copy accumulator and X register
    740          stx WORK                   ;   to WORK
    741          jmp PRNUM                  ; Go print (unsigned) number
    742 ;
    743 ; TBIL PN (Print Number)
    744 ;
    745 IL__PN   ldx CSPTR                  ; Load computation stack pointer
    746          lda $01,x                  ; See whether the number is
    747          bpl skip1                 ;   negative...no, skip it
    748          jsr IL__NE                 ; Else negate the number on stack
    749          lda #'-'                   ; Print a '-' to show minus sign
    750          jsr CPRCHR
    751 skip1   jsr IL__SP
    752 PRNUM    lda #$1F
    753          sta $B8
    754          sta $BA
    755          lda #$2A
    756          sta $B9
    757          sta $BB
    758          ldx WORK
    759          ldy WORK+1
    760          sec
    761 sub10k  inc $B8
    762          txa                        ; Subtract 10000 ($2710) from Y/X register pair
    763          sbc #$10
    764          tax
    765          tya
    766          sbc #$27
    767          tay
    768          bcs sub10k
    769 add1k   dec $B9
    770          txa                        ; Add 1000 ($03E8) to Y/X register pair
    771          adc #$E8
    772          tax
    773          tya
    774          adc #$03
    775          tay
    776          bcc add1k
    777          txa
    778 sub100  sec                        ; Subtract 100 ($64) from accumulator
    779          inc $BA
    780          sbc #$64
    781          bcs sub100
    782          dey
    783          bpl sub100
    784 add10   dec $BB                    ; Add 10 ($0A) to accumulator
    785          adc #$0A
    786          bcc add10
    787          ora #$30                   ; Convert it to ASCII digit
    788          sta WORK
    789          lda #$20
    790          sta WORK+1
    791          ldx #$FB
    792 LBL199   stx $C3
    793          lda WORK+1,x
    794          ora WORK+1
    795          cmp #$20
    796          beq LBL076
    797          ldy #$30
    798          sty WORK+1
    799          ora WORK+1
    800          jsr CPRCHR
    801 LBL076   ldx $C3
    802          inx
    803          bne LBL199
    804          rts
    805 ;
    806 ; TBIL LS (List the program)
    807 ;
    808 IL__LS   lda TXTPTR+1               ; Save TXTPTR on system stack
    809          pha
    810          lda TXTPTR
    811          pha
    812          lda LOWEST                 ; Set TXTPTR to LOWEST
    813          sta TXTPTR
    814          lda LOWEST+1
    815          sta TXTPTR+1
    816          lda $24
    817          ldx $25
    818          jsr LBL077
    819          beq LBL078
    820          jsr LBL077
    821 LBL078   lda TXTPTR                 ; Is TXTPTR >= $B6?
    822          sec
    823          sbc $B6
    824          lda TXTPTR+1
    825          sbc $B7
    826          bcs LBL079                 ; Yes, exiting
    827          jsr GETNUM
    828          beq LBL079                 ; Reach the end of program area, exiting
    829          ldx LINNUM                 ; Print line number and ...
    830          lda LINNUM+1
    831          jsr PRAXNM
    832          lda #' '                   ;   a blank after that number
    833 LBL080   jsr CPRCHR
    834          jsr BV                     ; Test for break
    835          bcs LBL079                 ; Break hit, so exiting
    836          jsr CHRGET                 ; Get a char from program area
    837          bne LBL080                 ;   and print it until it hits a $00
    838          jsr IL__NL                 ; Print a new line
    839          jmp LBL078                 ; Loop back to LIST
    840 ;
    841 ;
    842 ;
    843 LBL077   sta $B6
    844          inc $B6
    845          bne LBL082
    846          inx
    847 LBL082   stx $B7
    848          ldy CSPTR                  ; Load computation stack pointer
    849          cpy #$80
    850          beq LBL083
    851          jsr FINDLN                 ; Find BASIC line with target line number
    852 ;
    853 ;
    854 ;
    855 LBL099   lda TXTPTR                 ; Decrement TXTPTR by 2
    856          ldx TXTPTR+1
    857          sec
    858          sbc #$02
    859          bcs skip2
    860          dex
    861 skip2   sta TXTPTR
    862          jmp LBL085                 ;
    863 LBL079   pla                        ; Restore TXTPTR from system stack
    864          sta TXTPTR
    865          pla
    866          sta TXTPTR+1
    867 LBL083   rts
    868 ;
    869 ; TBIL NL (New Line)
    870 ;
    871 IL__NL   lda TERMPOS                ; Is the terminal position past 127?
    872          bmi LBL083                 ; Yes, exit. Otherwise fall thru to ...
    873 ;
    874 ; Routine to print a new line.  It handles CR, LF
    875 ; and adds pad characters to the ouput
    876 ;
    877 P_NWLN   lda #$0D                   ; Load up a CR
    878          jsr OUT_V                  ; Go print it
    879          lda PCC                    ; Load the pad character code
    880          and #$7F                   ; Test to see - 
    881          sta TERMPOS                ;   how many pad characters to print
    882          beq prlf                  ; Skip if 0
    883 prpad   jsr LBL087                 ; Go print pad character
    884          dec TERMPOS                ; One less
    885          bne prpad                 ; Loop until 0
    886 prlf    lda #$0A                   ; Load up a LF
    887          jmp LBL089                 ; Go print it
    888 ;
    889 ;
    890 ;
    891 LBL092   ldy TMC
    892 LBL091   sty TERMPOS
    893          bcs LBL090
    894 ;
    895 ; TBIL GL (Get input Line)
    896 ;
    897 IL__GL   lda #$30                   ; Set TXTPTR and CSTOP to $0030
    898          sta TXTPTR
    899          sta CSTOP
    900          sty TXTPTR+1
    901          jsr PSHWRK
    902 LBL090   eor $80
    903          sta $80
    904          jsr IN_V
    905          ldy #$00
    906          ldx CSTOP
    907          and #$7F
    908          beq LBL090                 ; It is a NUL
    909          cmp #$7F                   ; Is it a rubout?
    910          beq LBL090
    911          cmp #$13                   ; Is it a ...?
    912          beq LBL091
    913          cmp #$0A                   ; Is it a line feed?
    914          beq LBL092
    915          cmp LSC                    ; Is it a line cancel?
    916          beq cancl
    917          cmp BSC                    ; Is it a backspace?
    918          bne back
    919          cpx #$30                   ; Has it reached the end of input buffer?
    920          bne LBL095                 ; No, ...
    921 cancl   ldx TXTPTR
    922          sty TERMPOS                ; Reset TERMPOS to zero
    923          lda #$0D
    924 back    cpx CSPTR                  ; ... computation stack pointer
    925          bmi LBL096
    926          lda #$07                   ; ASCII Bell
    927          jsr CPRCHR                 ; Ring the bell
    928          jmp LBL090
    929 LBL096   sta $00,x                  ; Append a char to the buffer
    930          inx
    931          inx
    932 LBL095   dex
    933          stx CSTOP                  ; Set CSTOP to current buffer position
    934          cmp #$0D                   ; Is it a CR?
    935          bne LBL090                 ; No, continue inputting
    936          jsr IL__NL                 ; Print a new line and ...
    937 ;
    938 ; TBIL SP (Stack Pop)
    939 ;
    940 IL__SP   jsr POPBYT                 ; Pop value from computation
    941          sta WORK                   ;   stack onto WORK
    942          jsr POPBYT
    943          sta WORK+1
    944          rts
    945 ;
    946 ; TBIL IL (Insert BASIC Line)
    947 ;
    948 IL__IL   jsr LBL098                 ; Entry point for
    949          jsr FINDLN                 ; Find BASIC line with target line number
    950          php
    951          jsr LBL099
    952          sta $B8                    ; Set $B8 to TXTPTR
    953          stx $B9
    954          lda WORK                   ; Set $B6 to WORK
    955          sta $B6
    956          lda WORK+1
    957          sta $B7
    958          ldx #$00
    959          plp
    960          bne LBL100
    961          jsr GETNUM
    962          dex
    963          dex
    964 LBL101   dex
    965          jsr CHRGET
    966          bne LBL101
    967 LBL100   sty LINNUM
    968          sty LINNUM+1
    969          jsr LBL098
    970          lda #$0D
    971          cmp (TXTPTR),y
    972          beq LBL102
    973          inx
    974          inx
    975          inx
    976 LBL103   inx
    977          iny
    978          cmp (TXTPTR),y
    979          bne LBL103
    980          lda $B6                    ; Set LINNUM to $B6
    981          sta LINNUM
    982          lda $B7
    983          sta LINNUM+1
    984 LBL102   lda $B8                    ; Set WORK to $B8
    985          sta WORK
    986          lda $B9
    987          sta WORK+1
    988          clc
    989          ldy #$00
    990          txa
    991          beq LBL104
    992          bpl LBL105
    993          adc $2E
    994          sta $B8
    995          lda $2F
    996          sbc #$00
    997          sta $B9
    998 LBL109   lda ($2E),y
    999          sta ($B8),y
   1000          ldx $2E
   1001          cpx $24
   1002          bne LBL106
   1003          lda $2F
   1004          cmp $25
   1005          beq LBL107
   1006 LBL106   inx
   1007          stx $2E
   1008          bne LBL108
   1009          inc $2F
   1010 LBL108   inc $B8
   1011          bne LBL109
   1012          inc $B9
   1013          bne LBL109
   1014 LBL105   adc $24
   1015          sta $B8
   1016          sta $2E
   1017          tya
   1018          adc $25
   1019          sta $B9
   1020          sta $2F
   1021          lda $2E
   1022          sbc $C6
   1023          lda $2F
   1024          sbc $C7
   1025          bcc LBL110
   1026          dec PGMPTR
   1027          jmp PRERR
   1028 LBL110   lda ($24),y
   1029          sta ($2E),y
   1030          ldx $24                    ; Decrement $24 by 1
   1031          bne LBL111
   1032          dec $25
   1033 LBL111   dec $24
   1034          ldx $2E                    ; Decrement $2E by 1
   1035          bne LBL112
   1036          dec $2F
   1037 LBL112   dex
   1038          stx $2E
   1039          cpx WORK                   ; Is $2E = WORK?
   1040          bne LBL110                 ; No, go to ...
   1041          ldx $2F
   1042          cpx WORK+1
   1043          bne LBL110                 ; No, go to ...
   1044 LBL107   lda $B8                    ; Set $24 to $B8
   1045          sta $24
   1046          lda $B9
   1047          sta $25
   1048 LBL104   lda LINNUM                 ; Is LINNUM zero?
   1049          ora LINNUM+1
   1050          beq LBL113                 ; Yes, ...
   1051          lda LINNUM                 ; Else write LINNUM to (WORK)
   1052          sta (WORK),y
   1053          iny
   1054          lda LINNUM+1
   1055          sta (WORK),y
   1056 LBL114   iny
   1057          sty $B6
   1058          jsr CHRGET
   1059          php
   1060          ldy $B6
   1061          sta (WORK),y
   1062          plp
   1063          bne LBL114
   1064 LBL113   jmp RESTRT
   1065 ;
   1066 ; TBIL DV (Divide)
   1067 ;
   1068 IL__DV   jsr POPNBR                 ; Entry point for
   1069          lda $03,x
   1070          and #$80
   1071          beq LBL116
   1072          lda #$FF
   1073 LBL116   sta WORK
   1074          sta WORK+1
   1075          pha
   1076          adc $02,x
   1077          sta $02,x
   1078          pla
   1079          pha
   1080          adc $03,x
   1081          sta $03,x
   1082          pla
   1083          eor $01,x
   1084          sta $BB
   1085          bpl LBL117
   1086          jsr LBL118
   1087 LBL117   ldy #$11
   1088          lda $00,x
   1089          ora $01,x
   1090          bne LBL119
   1091          jmp PRERR
   1092 LBL119   sec
   1093          lda WORK
   1094          sbc $00,x
   1095          pha
   1096          lda WORK+1
   1097          sbc $01,x
   1098          pha
   1099          eor WORK+1
   1100          bmi LBL120
   1101          pla
   1102          sta WORK+1
   1103          pla
   1104          sta WORK
   1105          sec
   1106          jmp LBL121
   1107 LBL120   pla
   1108          pla
   1109          clc
   1110 LBL121   rol $02,x
   1111          rol $03,x
   1112          rol WORK
   1113          rol WORK+1
   1114          dey
   1115          bne LBL119
   1116          lda $BB
   1117          bpl LBL122
   1118 ;
   1119 ; TBIL NE (Negate)
   1120 ;
   1121 IL__NE   ldx CSPTR                  ; Load computation stack pointer
   1122 LBL118   sec                        ; Negates the TOS by subtracting
   1123          tya                        ;   it from zero (Y is zero) and
   1124          sbc $00,x                  ;   replacing TOS with it
   1125          sta $00,x
   1126          tya
   1127          sbc $01,x
   1128          sta $01,x
   1129 LBL122   rts
   1130 ;
   1131 ; TBIL SU (Subtract)
   1132 ;
   1133 IL__SU   jsr IL__NE                 ; Negate the TOS and falls thru to...
   1134 ;
   1135 ; TBIL AD (Add)
   1136 ;
   1137 IL__AD   jsr POPNBR                 ; Add TOS to NOS and NOS becomes TOS
   1138          lda $00,x
   1139          adc $02,x
   1140          sta $02,x
   1141          lda $01,x
   1142          adc $03,x
   1143          sta $03,x
   1144          rts
   1145 ;
   1146 ; TBIL MP (Multiply)
   1147 ;
   1148 IL__MP   jsr POPNBR
   1149          ldy #$10                   ; Loop 16 times
   1150          lda $02,x                  ; Copy NOS to WORK
   1151          sta WORK
   1152          lda $03,x
   1153          sta WORK+1
   1154 mult    asl $02,x                  ; Shift WORK/NOS unit left by 1
   1155          rol $03,x
   1156          rol WORK
   1157          rol WORK+1
   1158          bcc skip3
   1159          clc                        ; Add TOS to NOS
   1160          lda $02,x
   1161          adc $00,x
   1162          sta $02,x
   1163          lda $03,x
   1164          adc $01,x
   1165          sta $03,x
   1166 skip3   dey
   1167          bne mult
   1168          rts
   1169 ;
   1170 ; TBIL FV (Fetch Variable)
   1171 ;
   1172 IL__FV   jsr POPBYT                 ; Pop a variable index into X
   1173          tax
   1174          lda $00,x
   1175          ldy $01,x
   1176          dec CSPTR
   1177          ldx CSPTR
   1178          sty $00,x
   1179          jmp PSHACC
   1180 ;
   1181 ; TBIL SV (Store Variable)
   1182 ;
   1183 IL__SV   ldx #$7D                   ; Make sure the computation stack
   1184          jsr POPNB1                 ;   has at least three bytes on it
   1185          lda $01,x                  ; Pop value and stask it on system stack
   1186          pha
   1187          lda $00,x
   1188          pha
   1189          jsr POPBYT                 ; Pop a variable index into X
   1190          tax
   1191          pla                        ; Retrieve saved value and write it
   1192          sta $00,x                  ;   into variable pointed to by X
   1193          pla
   1194          sta $01,x
   1195          rts
   1196 ;
   1197 ; TBIL RT (IL subroutine return)
   1198 ;
   1199 IL__RT   jsr LBL063                 ; Entry point for
   1200          lda WORK                   ; Set PGMPTR to WORK
   1201          sta PGMPTR
   1202          lda WORK+1
   1203          sta PGMPTR+1
   1204          rts
   1205 ;
   1206 ; TBIL SB (Save Basic Pointer)
   1207 ;
   1208 IL__SB   ldx #$2C                   ; Entry point for
   1209          bne LBL125                 ; go to common routine
   1210 ;
   1211 ; TBIL RB (Restore Basic Pointer)
   1212 ;
   1213 IL__RB   ldx #$2E                   ; Entry point for
   1214 LBL125   lda $00,x
   1215          cmp #$80
   1216          bcs LBL098
   1217          lda $01,x
   1218          bne LBL098
   1219          lda TXTPTR                 ; Set $2E to TXTPTR
   1220          sta $2E
   1221          lda TXTPTR+1
   1222          sta $2F
   1223          rts
   1224 ;
   1225 ; Swap TXTPTR and $2E
   1226 ;
   1227 LBL098   lda TXTPTR                 ; Swap TXTPTR and $2E
   1228          ldy $2E
   1229          sty TXTPTR
   1230          sta $2E
   1231          lda TXTPTR+1
   1232          ldy $2F
   1233          sty TXTPTR+1
   1234          sta $2F
   1235          ldy #$00
   1236          rts
   1237 ;
   1238 ; TBIL GS (Save GOSUB line)
   1239 ;
   1240 IL__GS   lda LINNUM                 ; Set WORK to LINNUM
   1241          sta WORK
   1242          lda LINNUM+1
   1243          sta WORK+1
   1244          jsr LBL126
   1245          lda $C6                    ; Set RETPTR to $C6
   1246          sta RETPTR
   1247          lda $C7
   1248 LBL064   sta RETPTR+1
   1249 LBL129   rts
   1250 ;
   1251 ;
   1252 ;
   1253 LBL063   lda ($C6),y                ; Set WORK to ($C6)
   1254          sta WORK
   1255          jsr check
   1256          lda ($C6),y
   1257          sta WORK+1
   1258 check   inc $C6                    ; Increment $C6 by 1
   1259          bne skip4
   1260          inc $C7
   1261 skip4   lda HIGHST                 ; Is HIGHST < $C6?
   1262          cmp $C6
   1263          lda HIGHST+1
   1264          sbc $C7
   1265          bcs LBL129                 ; No, exit
   1266          jmp PRERR                  ; Error
   1267 ;
   1268 ; TBIL US (Machine Language Subroutine Call)
   1269 ;
   1270 IL__US   jsr dousr                 ; Execute USR() function, then
   1271          sta WORK                   ;   push the accumulator onto
   1272          tya                        ;   the computation stack
   1273          jmp PSHWKA
   1274 dousr   jsr IL__SP                 ; Copy low byte of third argument
   1275          lda WORK                   ;   ("A" register value) to $B6
   1276          sta $B6
   1277          jsr IL__SP                 ; Copy high byte of second argument
   1278          lda WORK+1                 ;   ("X" register value) to $B7
   1279          sta $B7
   1280          ldy WORK
   1281          jsr IL__SP                 ; Copy first argument (machine
   1282          ldx $B7                    ;   code address) to WORK
   1283          lda $B6                    ; Load accumulator and X register with values
   1284          clc
   1285          jmp (WORK)                 ; Invoke the machine routine
   1286 ;
   1287 ; TBIL LN (Push Literal Number)
   1288 ;
   1289 IL__LN   jsr IL__LB                 ; Read two bytes from the IL program table and push it
   1290 ;
   1291 ; TBIL LB (Push Literal Byte onto Stack) - Go read a byte from the IL table
   1292 ;
   1293 IL__LB   jsr PGMBYT                 ; Read a byte from the IL program table
   1294          jmp PSHACC                 ;   and push it on stack
   1295 LBL085   stx TXTPTR+1
   1296          cpx #$00
   1297          rts
   1298 ;
   1299 ;
   1300 ;
   1301 ILRES2   ldy #$02                   ; These two entry points are for code that
   1302 ILRES1   sty WORK                   ;  does not seem to get called.  Need more research.
   1303          ldy #$29                   ; My analysis: Set WORK to $2902, fetch a
   1304          sty WORK+1                 ;   byte from it and if it is $08, go to
   1305          ldy #$00                   ;   some code inside IL__DV (Divide) routine...?!?
   1306          lda (WORK),y               ; Why this code? Beats me
   1307          cmp #$08
   1308          bne LBL133
   1309          jmp LBL117
   1310 LBL133   rts
   1311 ;
   1312 ; Subroutine to decide which pad characters to print
   1313 ;
   1314 LBL089   jsr OUT_V                  ; Entry point with a character to print first
   1315 LBL087   lda #$FF                   ; Normal entry point - Set pad to $FF
   1316          bit PCC                    ; Check if the pad flag is on
   1317          bmi LBL134                 ; Skip it if not
   1318          lda #$00                   ; set pad to $00
   1319 LBL134   jmp OUT_V                  ; Go print it
   1320 
   1321 
   1322 ;
   1323 ; TBIL program table
   1324 ;
   1325 ILTBL    .byte $24, '>', $91, $27, $10, $E1, $59, $C5, $2A, $56, $10, $11, $2C
   1326          .byte $8B, 'L', 'E', 'T'+$80, $A0, $80, '='+$80, $30, $BC, $E0, $13, $1D
   1327          .byte $94, 'G', 'O'+$80
   1328          .byte $88, 'T', 'O'+$80, $30, $BC, $E0, $10, $11, $16
   1329          .byte $80, 'S', 'U', 'B'+$80, $30, $BC, $E0, $14, $16
   1330          .byte $90, 'P', 'R'+$80, $83, 'I', 'N', 'T'+$80, $E5, $71, $88, ';'+$80, $E1, $1D, $8F
   1331          .byte $A2, $21, $58, $6F, $83, ','+$80, $22, $55, $83, ':'+$80, $24, $93, $E0, $23, $1D
   1332          .byte $30, $BC, $20, $48
   1333          .byte $91, 'I', 'F'+$80, $30, $BC, $31, $34, $30, $BC
   1334          .byte $84, 'T', 'H', 'E', 'N'+$80, $1C, $1D, $38, $0D
   1335          .byte $9A, 'I', 'N', 'P', 'U', 'T'+$80, $A0, $10
   1336          .byte $E7, $24, $3F, $20, $91, $27, $E1, $59, $81, ','+$80, $30, $BC, $13, $11
   1337          .byte $82, ','+$80, $4D, $E0, $1D
   1338          .byte $89, 'R', 'E', 'T', 'U', 'R', 'N'+$80, $E0, $15, $1D
   1339          .byte $85, 'E', 'N', 'D'+$80, $E0, $2D
   1340          .byte $98, 'L', 'I', 'S', 'T'+$80, $EC, $24, $00, $00, $00
   1341          .byte $00, $0A, $80, $1F, $24, $93, $23, $1D, $30, $BC, $E1, $50, $80, ','+$80, $59
   1342          .byte $85, 'R', 'U', 'N'+$80, $38, $0A
   1343          .byte $86, 'C', 'L', 'E', 'A', 'R'+$80, $2B
   1344          .byte $84, 'R', 'E', 'M'+$80, $1D, $A0
   1345          .byte $80, '='+$80, $38, $14
   1346          .byte $85, '-'+$80, $30, $D3, $17, $64
   1347          .byte $81, '+'+$80, $30, $D3
   1348          .byte $85, '+'+$80, $30, $D3, $18, $5A
   1349          .byte $85, '-'+$80, $30, $D3, $19, $54, $2F, $30, $E2
   1350          .byte $85, '*'+$80, $30, $E2, $1A, $5A
   1351          .byte $85, '/'+$80, $30, $E2, $1B, $54, $2F
   1352          .byte $98, 'R', 'N', 'D'+$80, $0A, $80, $80, $12, $0A, $09, $29, $1A, $0A, $1A
   1353          .byte $85, $18, $13, $09, $80, $12, $01, $0B, $31, $30, $61, $72, $0B, $04, $02
   1354          .byte $03, $05, $03, $1B, $1A, $19, $0B, $09, $06, $0A, $00, $00, $1C, $17, $2F
   1355          .byte $8F, 'U', 'S', 'R'+$80, $80, '('+$80, $30, $BC, $31, $2A, $31, $2A, $80, ')'+$80, $2E
   1356          .byte $2F, $A2, $12, $2F, $C1, $2F, $80, '('+$80, $30, $BC, $80, ')'+$80, $2F, $83, ','+$80
   1357          .byte $38, $BC, $0B, $2F, $80, '('+$80, $52, $2F, $84, '='+$80, $09, $02, $2F, $8E, '<'+$80
   1358          .byte $84, '='+$80, $09, $93, $2F, $84, '>'+$80, $09, $05, $2F, $09, $91, $2F, $80, '>'+$80
   1359          .byte $84, '='+$80, $09, $06, $2F, $84, '<'+$80, $09, $95, $2F, $09, $04, $2F, $00, $00
   1360          .byte $00
   1361 
   1362 ; ['24', '3E', '91',    '27', '10',   'E1', '59', 'C5', '2A', '56', '10',   '11',   '2C', '8B',    '4C', '45', 'D4', 'A0', '80',    'BD', '30', 'BC', 'E0', '13',   '1D',   '94',    '47', 'CF', '88',    '54', 'CF', '30', 'BC', 'E0', '10',   '11',   '16',   '80',    '53', '55', 'C2', '30', 'BC', 'E0', '14',   '16',   '90',    '50', 'D2', '83',    '49', '4E', 'D4', 'E5', '71', '88',    'BB', 'E1', '1D',   '8F',    'A2', '21', '58', '6F', '83',    'AC', '22', '55', '83',    'BA', '24', '93',    'E0', '23', '1D',   '30', 'BC', '20', '48', '91',    '49', 'C6', '30', 'BC', '31', '34', '30', 'BC', '84',    '54', '48', '45', 'CE', '1C',   '1D',   '38', '0D', '9A',    '49', '4E', '50', '55', 'D4', 'A0', '10',   'E7', '24', '3F', '20', '91',    '27', 'E1', '59', '81',    'AC', '30', 'BC', '13',   '11',   '82',   'AC', '4D', 'E0', '1D',   '89',  '52', '45', '54', '55', '52', 'CE', 'E0', '15',   '1D',   '85',    '45', '4E', 'C4', 'E0', '2D', '98',    '4C', '49', '53', 'D4', 'EC', '24', '00',   '00',   '00',   '00',   '0A', '80',    '1F',   '24', '93',    '23', '1D',   '30', 'BC', 'E1', '50', '80',    'AC', '59', '85',    '52', '55', 'CE', '38', '0A', '86',    '43', '4C', '45', '41', 'D2', '2B', '84',    '52', '45', 'CD', '1D',   'A0', '80',    'BD', '38', '14',   '85',    'AD', '30', 'D3', '17',   '64', '81',    'AB', '30', 'D3', '85',    'AB', '30', 'D3', '18',   '5A', '85',    'AD', '30', 'D3', '19',   '54', '2F', '30', 'E2', '85',    'AA', '30', 'E2', '1A',   '5A', '85',    'AF', '30', 'E2', '1B',   '54', '2F', '98',    '52', '4E', 'C4', '0A', '80',    '80',    '12',   '0A', '09', '29', '1A',   '0A', '1A',   '85',    '18',   '13',   '09', '80',    '12',   '01',   '0B',   '31', '30', '61', '72', '0B',   '04',   '02',   '03',   '05',   '03',   '1B',   '1A',   '19',   '0B',   '09', '06',   '0A', '00',   '00',   '1C',   '17',   '2F', '8F',    '55', '53', 'D2', '80',    'A8', '30', 'BC', '31', '2A', '31', '2A', '80',    'A9', '2E', '2F', 'A2', '12',   '2F', 'C1', '2F', '80',    'A8', '30', 'BC', '80',    'A9', '2F', '83',    'AC', '38', 'BC', '0B',   '2F', '80',    'A8', '52', '2F', '84',    'BD', '09', '02',   '2F', '8E',    'BC', '84',    'BD', '09', '93',    '2F', '84',    'BE', '09', '05',   '2F', '09', '91',    '2F', '80',    'BE', '84',    'BD', '09', '06',   '2F', '84',    'BC', '09', '95',    '2F', '09', '04',   '2F']
   1363 ; ['$',  '>',  '\x11*', "'",  '\x10', 'a*', 'Y',  'E*', '*',  'V',  '\x10', '\x11', ',',  '\x0b*', 'L',  'E',  'T*', ' *', '\x00*', '=*', '0',  '<*', '`*', '\x13', '\x1d', '\x14*', 'G',  'O*', '\x08*', 'T',  'O*', '0',  '<*', '`*', '\x10', '\x11', '\x16', '\x00*', 'S',  'U', 'B*',  '0',  '<*', '`*', '\x14', '\x16', '\x10*', 'P',  'R*', '\x03*', 'I',  'N',  'T*', 'e*', 'q',  '\x08*', ';*', 'a*', '\x1d', '\x0f*', '"*', '!',  'X',  'o',  '\x03*', ',*', '"',  'U',  '\x03*', ':*', '$',  '\x13*', '`*', '#',  '\x1d', '0',  '<*', ' ',  'H',  '\x11*', 'I',  'F*', '0',  '<*', '1',  '4',  '0',  '<*', '\x04*', 'T',  'H',  'E',  'N*', '\x1c', '\x1d', '8',  '\r', '\x1a*', 'I',  'N',  'P',  'U',  'T*', ' *', '\x10', 'g*', '$',  '?',  ' ',  '\x11*', "'",  'a*', 'Y',  '\x01*', ',*', '0',  '<*', '\x13', '\x11', '\x02*', ',*', 'M', '`*', '\x1d', '\t*', 'R',  'E',  'T',  'U',  'R',  'N*', '`*', '\x15', '\x1d', '\x05*', 'E',  'N',  'D*', '`*', '-',  '\x18*', 'L',  'I',  'S',  'T*', 'l*', '$',  '\x00', '\x00', '\x00', '\x00', '\n', '\x00*', '\x1f', '$',  '\x13*', '#',  '\x1d', '0',  '<*', 'a*', 'P',  '\x00*', ',*', 'Y',  '\x05*', 'R',  'U',  'N*', '8',  '\n', '\x06*', 'C',  'L',  'E',  'A',  'R*', '+',  '\x04*', 'R',  'E',  'M*', '\x1d', ' *', '\x00*', '=*', '8',  '\x14', '\x05*', '-*', '0',  'S*', '\x17', 'd',  '\x01*', '+*', '0',  'S*', '\x05*', '+*', '0',  'S*', '\x18', 'Z',  '\x05*', '-*', '0',  'S*', '\x19', 'T',  '/',  '0',  'b*', '\x05*', '**', '0',  'b*', '\x1a', 'Z',  '\x05*', '/*', '0',  'b*', '\x1b', 'T',  '/',  '\x18*', 'R',  'N',  'D*', '\n', '\x00*', '\x00*', '\x12', '\n', '\t', ')',  '\x1a', '\n', '\x1a', '\x05*', '\x18', '\x13', '\t', '\x00*', '\x12', '\x01', '\x0b', '1',  '0',  'a',  'r',  '\x0b', '\x04', '\x02', '\x03', '\x05', '\x03', '\x1b', '\x1a', '\x19', '\x0b', '\t', '\x06', '\n', '\x00', '\x00', '\x1c', '\x17', '/',  '\x0f*', 'U',  'S',  'R*', '\x00*', '(*', '0',  '<*', '1',  '*',  '1',  '*',  '\x00*', ')*', '.',  '/',  '"*', '\x12', '/',  'A*', '/',  '\x00*', '(*', '0',  '<*', '\x00*', ')*', '/',  '\x03*', ',*', '8',  '<*', '\x0b', '/',  '\x00*', '(*', 'R',  '/',  '\x04*', '=*', '\t', '\x02', '/',  '\x0e*', '<*', '\x04*', '=*', '\t', '\x13*', '/',  '\x04*', '>*', '\t', '\x05', '/',  '\t', '\x11*', '/',  '\x00*', '>*', '\x04*', '=*', '\t', '\x06', '/',  '\x04*', '<*', '\t', '\x15*', '/',  '\t', '\x04', '/']
   1364 ; http://www.nicholson.com/rhn/basic/basic.info.html#2
   1365 
   1366 ;
   1367 ; End of Tiny Basic
   1368 
   1369 ;
   1370 ; Begin base system initialization
   1371 ;
   1372 FBLK	jsr io.init_acia
   1373 	ldx #$00
   1374 	ldy #$00
   1375 delay:				; Wait for initialization of serial line
   1376 	dey
   1377 	bne delay
   1378 	dex
   1379 	bne delay
   1380 	jsr CLRSC                  ; Go clear the screen
   1381          ldx #$00                   ; Offset for welcome message and prompt
   1382          jsr SNDMSG                 ; Go print it
   1383 ST_LP    jsr RCCHR                  ; Go get a character from the console
   1384          cmp #'C'                   ; Check for 'C'
   1385          bne IS_WRM                 ; If not branch to next check
   1386          jmp COLD_S                 ; Otherwise cold-start Tiny Basic
   1387 IS_WRM   cmp #'W'                   ; Check for 'W'
   1388          bne PRMPT                  ; If not, branch to re-prompt them
   1389          jmp WARM_S                 ; Otherwise warm-start Tiny Basic
   1390 PRMPT    ldx #$22                   ; Offset of prompt in message block
   1391          jsr SNDMSG                 ; Go print the prompt	 
   1392          jmp ST_LP                  ; Go get the response
   1393 
   1394 ;
   1395 ; The message block. It terminates with an FF.
   1396 ;
   1397 MBLK
   1398          .text   "TINY BASIC - Copyright, Tom Pitman"
   1399          .text   $0D, $0A, $0D, $0A
   1400          .text   "Boot (C/W)? "
   1401          .text   $07, $FF
   1402 
   1403 ;
   1404 ; Begin BIOS subroutines
   1405 ;
   1406 
   1407 ;
   1408 ; Clear the screen
   1409 ;
   1410 CLRSC    jsr term.clear_screen
   1411         #term.SET_CURSOR #$01, #$01
   1412 	rts
   1413 
   1414 ;
   1415 ; Print a message.
   1416 ; This sub expects the message offset from MBLK in X.
   1417 ;
   1418 SNDMSG   lda MBLK,x                 ; Get a character from the message block
   1419          cmp #$FF                   ; Look for end of message marker
   1420          beq EXSM                   ; Finish up if it is
   1421          jsr SNDCHR                 ; Otherwise send the character
   1422          inx                        ; Increment the pointer
   1423          jmp SNDMSG                 ; Go get next character
   1424 EXSM     rts                        ; Return
   1425 
   1426 ;
   1427 ; Get a character from the keyboard
   1428 ; Runs into SNDCHR to provide echo
   1429 ;
   1430 RCCHR    sec                        ; Wait for keypress
   1431 	phx
   1432 	phy
   1433         jsr io.getc
   1434 	ply
   1435 	plx
   1436 
   1437 ;
   1438 ; Send a character to the screen
   1439 ;
   1440 SNDCHR   sta $FE                    ; Save the character to be printed
   1441          cmp #$FF                   ; Check for a bunch of characters
   1442          beq EXSC                   ; that we don't want to print to
   1443          cmp #$00                   ; the terminal and discard them to
   1444          beq EXSC                   ; clean up the output
   1445          cmp #$91                   ;
   1446          beq EXSC                   ;
   1447          cmp #$93                   ;
   1448          beq EXSC                   ;
   1449          cmp #$80                   ;
   1450         beq EXSC                   ;
   1451          beq EXSC                   ;
   1452 
   1453 GETSTS   pha
   1454 	phx
   1455 	phy
   1456 	jsr io.putc
   1457 	ply
   1458 	plx
   1459 	pla
   1460 	
   1461 EXSC     rts                        ; Return
   1462 
   1463 ;
   1464 ; Check break routine
   1465 ; Any keystroke will produce a break condition (carry set)
   1466 ; Note: BREAK is renamed CHKBREAK to prevent conflict with
   1467 ;       BREAK routine in SimpleMon program.
   1468 ;
   1469 CHKBREAK .block
   1470 	pha
   1471          txa
   1472          pha
   1473          clc                        ; set no waiting flag
   1474          jsr io.getc_nonblocking                  ; if key pressed, carry is set; otherwise it is clear
   1475 	bcc set_carry				  ; Since getc_nonblocking
   1476 	clc					  ; does it the other way
   1477 	jmp cont				  ; around, we have to
   1478 set_carry:					  ; reverse it.
   1479 	sec
   1480 cont:	
   1481         pla
   1482          tax
   1483          pla
   1484         rts
   1485 	.bend
   1486 
   1487 tiny_basic_end:
   1488