(back to project page)

IIc_16kb Disassembly

                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ;                                                                              ;
                   ; Apple //c firmware disassembly, of the original 16KB ROM.                    ;
                   ; Copyright Apple Computer, Inc.                                               ;
                   ;                                                                              ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ;                                                                              ;
                   ; Project created by Andy McFadden, using 6502bench SourceGen v1.9.2.  Some of ;
                   ; the text was copy & pasted from James Lewis' disassembly of the 32KB ROM     ;
                   ; because it was faster than typing it in again.                               ;
                   ;                                                                              ;
                   ; The labels and comments come from the listing in Appendix I of the _Apple    ;
                   ; IIc Reference Manual, Volume 2_ (1984).  Most spelling and grammatical       ;
                   ; errors have been faithfully reproduced, but a few glaring instances          ;
                   ; ("signiture") have been corrected.                                           ;
                   ;                                                                              ;
                   ; The original sources were divided into multiple files, which were chained    ;
                   ; together to essentially form a single large input (4406 lines).  The output  ;
                   ; appears to have been split into two chunks, one from $c100-cfff, the other   ;
                   ; from $f800-ffff, probably combined with Applesoft ($d000-$f7ff) in a         ;
                   ; separate step.  The filenames are identified in the notes.                   ;
                   ;                                                                              ;
                   ; The original assembler treated labels as case-insensitive, and the code was  ;
                   ; a mix of mixed-case and upper-case.  Labels have been defined here as they   ;
                   ; were in the original.  Symbols with '.' have been changed to use '_', e.g.   ;
                   ; M.MOUSE is now M_MOUSE.  Some addresses have more than one label (e.g. the   ;
                   ; text input buffer is referred to as "IN" and "inbuf"); both are defined,     ;
                   ; with the "secondary" label(s) defined as global constants.                   ;
                   ;                                                                              ;
                   ; Some BRK/NOP statements shown in the output were encoded as $FF or another   ;
                   ; value in the binary.  These have been called out in comments.                ;
                   ;                                                                              ;
                   ; Last updated 2025/07/07                                                      ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;

                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ;                                 ;
                   ; Apple //c                       ;
                   ; Video Firmware and              ;
                   ; Monitor ROM Source              ;
                   ;                                 ;
                   ; COPYRIGHT 1977-1983 BY          ;
                   ; APPLE COMPUTER, INC.            ;
                   ;                                 ;
                   ; ALL RIGHTS RESERVED             ;
                   ;                                 ;
                   ; S. WOZNIAK           1977       ;
                   ; A. BAUM              1977       ;
                   ; JOHN A           NOV 1978       ;
                   ; R. AURICCHIO     SEP 1982       ;
                   ; E. BEERNINK          1983       ;
                   ;                                 ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;

                   ; 
                   ; (Regarding $44-4F:)
                   ; Note: In Apple II, //e, both interrupts and BRK destroyed
                   ; location $45.  Now only BRK destroys $45 (ACC) and it
                   ; also destroys $44 (MACSTAT).
                   ; 
                   ; (Regarding IN at $0200:)
                   ; Characters read by GETLN are placed in
                   ; IN, terminated by a carriage return.
                   ; 
                   ; (Regarding VMODE at $4F8+3:)
                   ; BASIC VMODE Bits
                   ; 
                   ; 1....... - BASIC active
                   ; 0....... - Pascal active
                   ; .0......
                   ; .1......
                   ; ..0..... - Print control characters
                   ; ..1..... - Don't print ctrl chars
                   ; ...0.... -
                   ; ...1.... -
                   ; ....0... - Print control characters
                   ; ....1... - Don't print ctrl chars.
                   ; .....0.. -
                   ; .....1.. -
                   ; ......0. -
                   ; ......1. -
                   ; .......0 - Print mouse characters
                   ; .......1 - Don't print mouse characters
                   ; 
                   ; Pascal Mode Bits
                   ; 
                   ; 1....... - BASIC active
                   ; 0....... - Pascal active
                   ; .0......
                   ; .1......
                   ; ..0..... -
                   ; ..1..... -
                   ; ...0.... - Cursor always on
                   ; ...1.... - Cursor always off
                   ; ....0... - GOTOXY n/a
                   ; ....1... - GOTOXY in progress
                   ; .....0.. - Normal Video
                   ; .....1.. - Inverse Video
                   ; ......0. -
                   ; ......1. -
                   ; .......0 - Print mouse chars
                   ; .......1 - Don't print mouse chars
                   ; 
                   M_MOUSE         .eq     $01    {const}    ;Don't print mouse chars
                   movmode         .eq     $02    {const}    ;D1 mask
                   butmode         .eq     $04    {const}    ;D2 mask
                   M_VMODE         .eq     $04    {const}
                   GOODF8          .eq     $06    {const}    ;value of //e, lolly ID byte
                   M_CTL           .eq     $08    {const}    ;Don't print controls
                   M_GOXY          .eq     $08    {const}    ;GOTOXY IN PROGRESS
                   vblmode         .eq     $0c    {const}
                   M_CURSOR        .eq     $10    {const}    ;Don't print cursor
                   M_CTL2          .eq     $20    {const}    ;Don't print controls
                   movarm          .eq     $20    {const}
                   SLOTZ           .eq     $2b    {const}
                   LMNEM           .eq     $2c    {const}    ;temp for mnemonic decoding
                   RMNEM           .eq     $2d    {const}    ;temp for mnemonic decoding
                   FORMAT          .eq     $2e    {const}    ;temp for opcode decode
                   BOOTTMP         .eq     $3c    {const}
                   MACSTAT         .eq     $44    {const}    ;Machine state after BRK
                   ACC             .eq     $45    {const}    ;Acc after BRK
                   BOOTDEV         .eq     $4f    {const}
                   xon             .eq     $91    {const}    ;XON character
                   PICK            .eq     $95    {const}    ;CONTROL-U character
                   ESC             .eq     $9b    {const}    ;what ESC generates
                   termcur         .eq     $df    {const}    ;Cursor while in terminal mode ('_')
                   inbuf           .eq     $0200  {const}
                   TEMP1           .eq     $04f8  {const}    ;used by CTLCHAR
                   TEMPA           .eq     $0578  {const}    ;used by scroll
                   TEMPY           .eq     $05f8  {const}    ;used by scroll
                   IOADR           .eq     $c000  {const}    ;for IN#, PR# vector
                   iou             .eq     $c058  {const}    ;IOU interrupt switches
                   vblclr          .eq     $c070  {const}    ;Clear VBL interrupt
                   LOC0            .eq     $00               ;vector for autostart from disk
                   LOC1            .eq     $01
                   WNDLFT          .eq     $20               ;left edge of text window
                   WNDWDTH         .eq     $21               ;width of text window
                   WNDTOP          .eq     $22               ;top of text window
                   WNDBTM          .eq     $23               ;bottom+1 of text window
                   CH              .eq     $24               ;cursor horizontal position
                   CV              .eq     $25               ;cursor vertical position
                   GBASL           .eq     $26               ;lo-res graphics base addr.
                   GBASH           .eq     $27
                   BASL            .eq     $28               ;text base address
                   BASH            .eq     $29
                   BAS2L           .eq     $2a               ;temp base for scrolling
                   BAS2H           .eq     $2b
                   H2              .eq     $2c               ;temp for lo-res graphics
                   V2              .eq     $2d               ;temp for lo-res graphics
                   MASK            .eq     $2e               ;color mask for lo-res gr.
                   LENGTH          .eq     $2f               ;temp for opcode decode
                   COLOR           .eq     $30               ;color for lo-res graphics
                   MODE            .eq     $31               ;Monitor mode
                   INVFLG          .eq     $32               ;normal/inverse(/flash)
                   PROMPT          .eq     $33               ;prompt character
                   YSAV            .eq     $34               ;position in Monitor command
                   YSAV1           .eq     $35               ;temp for Y register
                   CSWL            .eq     $36               ;character output hook
                   CSWH            .eq     $37
                   KSWL            .eq     $38               ;character input hook
                   KSWH            .eq     $39
                   PCL             .eq     $3a               ;temp for program counter
                   PCH             .eq     $3b
                   A1L             .eq     $3c               ;Monitor temp
                   A1H             .eq     $3d               ;Monitor temp
                   A2L             .eq     $3e               ;Monitor temp
                   A2H             .eq     $3f               ;Monitor temp
                   A3L             .eq     $40               ;Monitor temp
                   A3H             .eq     $41               ;Monitor temp
                   A4L             .eq     $42               ;Monitor temp
                   A4H             .eq     $43               ;Monitor temp
                   A5L             .eq     $44               ;Monitor temp
                   A5H             .eq     $45               ;Monitor temp
                   XREG            .eq     $46               ;X reg after break
                   YREG            .eq     $47               ;Y reg after break
                   STATUS          .eq     $48               ;P reg after break
                   SPNT            .eq     $49               ;SP after break
                   RNDL            .eq     $4e               ;random counter low
                   RNDH            .eq     $4f               ;random counter high
                   IN              .eq     $0200  {addr/256} ;input buffer for GETLN
                   binl            .eq     $0214             ;Temp for binary conversion
                   binh            .eq     $0215
                   NBUF1           .eq     $0300  {addr/86}
                   DNIBL           .eq     $0356
                   sermode         .eq     $03b8             ;D7=1 if in cmd; D6=1 if term 479 & 47a
                   BRKV            .eq     $03f0  {addr/2}   ;vectors here after break
                   SOFTEV          .eq     $03f2  {addr/2}   ;vector for warm start
                   PWREDUP         .eq     $03f4             ;THIS MUST = EOF #$A5 OF SOFTEV+1
                   USRADR          .eq     $03f8  {addr/3}   ;APPLESOFT USR function vector
                   NMI             .eq     $03fb  {addr/3}   ;NMI vector
                   LINE1           .eq     $0400             ;first line of text screen
                   astat           .eq     $0438             ;Acia status from int 4F9 & 4FA
                   minl            .eq     $0478
                   moutemp         .eq     $0478             ;Temporary storage
                   ROMSTATE        .eq     $0478             ;temp store of ROM state
                   OLDCH           .eq     $047b             ;($478+3) last value of CH
                   mouxl           .eq     $047c             ;X position low byte
                   minxl           .eq     $047d
                   number          .eq     $047f             ;Number accumulated in command
                   pwdth           .eq     $04b8             ;Printer width 579 & 57a
                   maxl            .eq     $04f8
                   VMODE           .eq     $04fb             ;($4F8+3) OPERATING MODE
                   mouyl           .eq     $04fc             ;Y position low byte
                   aciabuf         .eq     $04ff             ;Owner of serial buffer
                   extint          .eq     $0538             ;exint & typbed enable 5F9 & 5FA
                   minh            .eq     $0578
                   OURCH           .eq     $057b             ;($578+3) 80-COL CH
                   mouxh           .eq     $057c             ;X position high byte
                   minxh           .eq     $057d
                   twser           .eq     $057f             ;Storage pointer for serial buffer
                   maxh            .eq     $05f8
                   extint2         .eq     $05f9
                   typhed          .eq     $05fa
                   OURCV           .eq     $05fb             ;($5f8+3) CURSOR VERTICAL
                   mouyh           .eq     $05fc             ;Y position high byte
                   twkey           .eq     $05ff             ;Storage pointer for type ahead buffer
                   eschar          .eq     $0638             ;Current escape character 6F9 & 6FA
                   oldcur          .eq     $0679             ;Saves cursor while in command
                   oldcur2         .eq     $067a             ;Saves cursor while in terminal mode
                   VFACTV          .eq     $067b             ;($678+3) Bit7=video firmware inactive
                   mouarm          .eq     $067c             ;Arm interrupts from movement or button
                   maxxl           .eq     $067d
                   trser           .eq     $067f             ;Retrieve pointer for serial buffer
                   flags           .eq     $06b8             ;D7 = Video echo D6 = CRLF 779 & 77A
                   temp            .eq     $06f8             ;Temp storage
                   XCOORD          .eq     $06fb             ;($6f8+3) X-COORD (GOTOXY)
                   ttrkey          .eq     $06ff             ;Retrieve buffer for type ahead buffer
                   col             .eq     $0738             ;Current printer column 7F9 & 7FA
                   NXTCUR          .eq     $077b             ;($778+3) next cursor to display
                   moustat         .eq     $077c             ;Mouse status
                   maxxh           .eq     $077d
                   BOOTSCRN        .eq     $07db
                   MSLOT           .eq     $07f8             ;owner of $C8 space
                   CURSOR          .eq     $07fb             ;($7f8+3) the current cursor char
                   moumode         .eq     $07fc             ;Mouse mode
                   thbuf           .eq     $0800             ;Buffer in alt ram space
                   sdata           .eq     $bff8             ;+$N0+$90 is output port
                   sstat           .eq     $bff9             ;ACIA status register
                   scomd           .eq     $bffa             ;ACIA command register
                   scntl           .eq     $bffb             ;ACIA control register
                   CLR80COL        .eq     $c000             ;disable 80 column store
                   KBD             .eq     $c000             ;>127 if keystroke
                   SET80COL        .eq     $c001             ;enable 80 column store
                   RDMAINRAM       .eq     $c002             ;read from main 48K RAM
                   RDCARDRAM       .eq     $c003             ;read from alt. 48K RAM
                   WRMAINRAM       .eq     $c004             ;write to main 48K RAM
                   WRCARDRAM       .eq     $c005             ;write to alt. 48K RAM
                   SETSTDZP        .eq     $c008             ;use main zero page/stack
                   SETALTZP        .eq     $c009             ;use alt. zero page/stack
                   CLR80VID        .eq     $c00c             ;disable 80 column hardware
                   SET80VID        .eq     $c00d             ;enable 80 column hardware
                   CLRALTCHAR      .eq     $c00e             ;normal LC, flashing UC
                   SETALTCHAR      .eq     $c00f             ;normal inverse, LC; no flash
                   KBDSTRB         .eq     $c010             ;turn off key pressed flag
                   RDLCBNK2        .eq     $c011             ;>127 if LC bank 2 is in
                   RDLCRAM         .eq     $c012             ;>127 if LC RAM read enabled
                   RDRAMRD         .eq     $c013             ;>127 if reading main 48K
                   RDRAMWRT        .eq     $c014             ;>127 if writing main 48K
                   mouxint         .eq     $c015             ;D7 = x interrupt
                   RDALTZP         .eq     $c016             ;>127 if Alt ZP and LC switched in
                   mouyint         .eq     $c017             ;D7 = y interrupt
                   RD80COL         .eq     $c018             ;>127 if 80 column store
                   vblint          .eq     $c019             ;D7 = vbl interrupt
                   RDTEXT          .eq     $c01a             ;>127 if text (not graphics)
                   RDPAGE2         .eq     $c01c             ;>127 if TXTPAGE2 switched in
                   ALTCHARSET      .eq     $c01e             ;>127 if alternate char set in use
                   RD80VID         .eq     $c01f             ;>127 if 80 column hardware in
                   SPKR            .eq     $c030             ;clicks the speaker
                   mouclr          .eq     $c048             ;Clear mouse interrupt
                   TXTCLR          .eq     $c050             ;switch in graphics (not text)
                   TXTSET          .eq     $c051             ;switch in text (not graphics)
                   MIXSET          .eq     $c053             ;set mixed-mode (4 lines text)
                   TXTPAGE1        .eq     $c054             ;switch in text page 1
                   TXTPAGE2        .eq     $c055             ;switch in text page 2
                   LORES           .eq     $c056             ;low-resolution graphics
                   SETAN3          .eq     $c05f
                   BUTN0           .eq     $c061             ;open apple key
                   BUTN1           .eq     $c062             ;closed apple key
                   moubut          .eq     $c063             ;D7 = Mouse button
                   PADDL0          .eq     $c064             ;read paddle 0
                   moux1           .eq     $c066             ;D7 = X1
                   mouy1           .eq     $c067             ;D7 = Y1
                   ioudsbl         .eq     $c078             ;Disable iou access
                   iouenbl         .eq     $c079             ;Enable iou access
                   ROMIN           .eq     $c081             ;switch in $D000-$FFFF ROM
                   LCBANK2         .eq     $c083             ;switch in LC bank 2
                   LCBANK1         .eq     $c08b             ;switch in LC bank 1
                   BASIC           .eq     $e000             ;BASIC entry point
                   BASIC2          .eq     $e003             ;BASIC warm entry point

                   ; 
                   ; This is part of the ROM image, but is not addressable because it overlaps with
                   ; memory-mapped I/O at $C000.  It's not part of the source listing.
                   ; 
                                   .addrs  NA
0000: 50 65 74 65+                 .str    ‘Peter Quinn, Rick Rice, Joe Ennis, J MacDougall, Ken Victor, E’
                                    +      ‘ Beernink, JR Huston, RC Williams, S DesJardin, Randy Bleske, ’
                                    +      ‘Rob Gemmell, Stan Robbins, Donna Keyes, Doug Farrar, Rich Jord’
                                    +      ‘an, Jerry Devlin, John Medica, B Etheredge, Dave Downey, Conra’
                                    +      ‘d Rogers’
                                   .adrend ↑ NA

                   NOTE: file SERIAL (equates), file SER
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ;                                                                              ;
                   ; Apple Lolly communications driver                                            ;
                   ;                                                                              ;
                   ; By                                                                           ;
                   ; Rich Williams                                                                ;
                   ; August 1983                                                                  ;
                   ; November 5 - j.r.huston                                                      ;
                   ;                                                                              ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ;                                                                              ;
                   ; Command codes                                                                ;
                   ;                                                                              ;
                   ; Default command char is ctrl-A (^A)                                          ;
                   ;                                                                              ;
                   ;     ^AnnB: Set baud rate to nn                                               ;
                   ;     ^AnnD: Set data format bits to nn                                        ;
                   ;     ^AI:   Enable video echo                                                 ;
                   ;     ^AK:   Disable CRLF                                                      ;
                   ;     ^AL:   Enable CRLF                                                       ;
                   ;     ^AnnN: Disable video echo & set printer width                            ;
                   ;     ^AnnP: Set parity bits to nn                                             ;
                   ;     ^AQ    Quit terminal mode                                                ;
                   ;     ^AR    Reset the ACIA, IN#0, PR#0                                        ;
                   ;     ^AS    Send a 233 ms break character                                     ;
                   ;     ^AT    Enter terminal mode                                               ;
                   ;     ^AZ:   Zap control commands                                              ;
                   ;     ^Ax:   Set command char to ^x                                            ;
                   ;     ^AnnCR:Set printer width (CR = carriage return)                          ;
                   ;                                                                              ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                                   .addrs  $c100
c100: 2c 58 ff     serslot         bit     IORTS             ;Set V to indicate initial entry
c103: 70 0c                        bvs     entrl             ;Always taken
c105: 38                           sec                       ;Input entry point
c106: 90                           .dd1    $90               ;BCC opcode
c107: 18                           clc
c108: b8                           clv                       ;V = 0 since not initial entry
c109: 50 06                        bvc     entrl             ;always taken

c10b: 01                           .dd1    $01               ;pascal signature byte
c10c: 31                           .dd1    $31               ;device signature
c10d: e4                           .dd1    <plinit
c10e: ee                           .dd1    <plread
c10f: f6                           .dd1    <plwrite
c110: fb                           .dd1    <plstatus

c111: da           entrl           phx                       ;Save the reg
c112: a2 c1                        ldx     #>serslot         ;X = Cn
c114: 4c 33 c2                     jmp     setup             ;Set mslot, etc

c117: 90 05        serport         bcc     serisout          ;Only output allowed
c119: 20 4d ce                     jsr     ZZQUIT            ;Reset the hooks
c11c: 80 6a                        bra     done

c11e: 0a           serisout        asl     A                 ;A = flags
c11f: 7a                           ply                       ;Get Char
c120: 5a                           phy
c121: bd b8 04                     lda     pwdth,x           ;Formatting enabled?
c124: f0 42                        beq     prnow
c126: a5 24                        lda     CH                ;Get current horiz position
c128: b0 1c                        bcs     servid            ;Branch if video echo
c12a: dd b8 04                     cmp     pwdth,x           ;If CH >= PWIDTH, then CH = COL
c12d: 90 03                        bcc     chok
c12f: bd 38 07                     lda     col,x
c132: dd 38 07     chok            cmp     col,x             ;Must be > col for valid tab
c135: b0 0b                        bcs     fixch             ;Branch if ok
c137: c9 11                        cmp     #$11              ;8 or 16?
c139: b0 11                        bcs     prnt              ;If > forget it
c13b: 09 f0                        ora     #$f0              ;Find next comma cheaply
c13d: 3d 38 07                     and     col,x             ;Don't blame me it's Dick's trick
c140: 65 24                        adc     CH
c142: 85 24        fixch           sta     CH                ;Save the new position
c144: 80 06                        bra     prnt

c146: c5 21        servid          cmp     WNDWDTH           ;If ch >= wndwdth go back to start of line
c148: 90 02                        bcc     prnt
c14a: 64 24                        stz     CH                ;Go back to left edge
                   ; We have a char to print
c14c: 7a           prnt            ply
c14d: 5a                           phy
c14e: bd 38 07                     lda     col,x             ;Have we exceeded width?
c151: dd b8 04                     cmp     pwdth,x
c154: b0 08                        bcs     toofar
c156: c5 24                        cmp     CH                ;Are we tabbing?
c158: b0 0e                        bcs     prnow
c15a: a9 40                        lda     #$40              ;Space * 2
c15c: 80 02                        bra     tab

c15e: a9 1a        toofar          lda     #$1a              ;CR * 2
c160: c0 80        tab             cpy     #$80              ;C = High bit
c162: 6a                           ror     A                 ;Shift it into char
c163: 20 9d c1                     jsr     serout3           ;Out it goes
c166: 80 e4                        bra     prnt

c168: 98           prnow           tya
c169: 20 8c c1                     jsr     serout            ;Print the actual char
c16c: bd b8 04                     lda     pwdth,x           ;Formatting enabled
c16f: f0 17                        beq     done
c171: 3c b8 06                     bit     flags,x           ;In video echo?
c174: 30 12                        bmi     done
c176: bd 38 07                     lda     col,x             ;Check if within 8 chars of right edge
c179: fd b8 04                     sbc     pwdth,x           ;So BASIC can format output
c17c: c9 f8                        cmp     #$f8
c17e: 90 04                        bcc     setch             ;If not within 8, we're done
c180: 18                           clc
c181: 65 21                        adc     WNDWDTH
c183: ac                           .dd1    $ac               ;Dummy LDY to skip next two bytes
c184: a9 00        setch           lda     #0                ;Keep cursor at 0 if video off
c186: 85 24                        sta     CH
c188: 68           done            pla                       ; Restore regs
c189: 7a                           ply
c18a: fa                           plx
c18b: 60           socmd           rts

c18c: 20 eb c9     serout          jsr     command           ;Serial output; check if command
c18f: 90 fa                        bcc     socmd             ;All done if it is
c191: 3c b8 06     serout2         bit     flags,x           ;N=1 iff video on
c194: 10 07                        bpl     serout3
c196: c9 91                        cmp     #xon              ;Don't echo ^Q
c198: f0 03                        beq     serout3
c19a: 20 f0 fd                     jsr     COUT1             ;Echo it
c19d: bc 85 c8     serout3         ldy     devno,x           ;Y points to ACIA
c1a0: 48                           pha                       ;Save the char
c1a1: 2c 58 ff                     bit     IORTS             ;Control char?
c1a4: f0 03                        beq     sordy             ;Don't inc column if so
c1a6: fe 38 07                     inc     col,x
c1a9: 08           sordy           php                       ;can't have real interrupts for a while
c1aa: 78                           sei
c1ab: b9 f9 bf                     lda     sstat,y           ;Check XMIT empty & DCD
c1ae: 10 11                        bpl     sordy2            ;branch if not clearing an interupt
c1b0: 48                           pha                       ;save original status
c1b1: 5a                           phy
c1b2: 2c 14 c0                     bit     RDRAMWRT          ;Save state of aux ram
c1b5: 08                           php
c1b6: 20 1c c9                     jsr     aitst2
c1b9: 28                           plp
c1ba: 10 03                        bpl     somain            ;Branch if was main
c1bc: 8d 05 c0                     sta     WRCARDRAM         ;Was alt ram
c1bf: 7a           somain          ply
c1c0: 68                           pla
c1c1: 28           sordy2          plp
c1c2: 29 30                        and     #$30
c1c4: c9 10                        cmp     #$10
c1c6: d0 e1                        bne     sordy
c1c8: 68                           pla
c1c9: 48                           pha                       ;Get char to XMIT
c1ca: 99 f8 bf                     sta     sdata,y           ;Out it goes
c1cd: 3c b8 06                     bit     flags,x           ;V=1 if LF after CR
c1d0: 49 0d                        eor     #$0d              ;check for CR.
c1d2: 0a                           asl     A                 ;preserve bit 7
c1d3: d0 0d                        bne     sodone            ;branch if not CR
c1d5: 50 06                        bvc     clrcol            ;branch if no LF after CR
c1d7: a9 14                        lda     #$14              ;Get LF*2
c1d9: 6a                           ror     A                 ;no shift in high bit
c1da: 20 9d c1                     jsr     serout3           ;Output the LF but don't echo it
c1dd: 64 24        clrcol          stz     CH                ;0 position & column
c1df: 9e 38 07                     stz     col,x
c1e2: 68           sodone          pla                       ;Get the char back
c1e3: 60                           rts

                   ; 
                   ; Pascal support stuff
                   ; 
c1e4: 48           plinit          pha
c1e5: 20 c8 c2                     jsr     default           ;set defaults, enable acia
c1e8: 9e b8 06                     stz     flags,x
c1eb: 68                           pla
c1ec: 80 05                        bra     plread2           ;all done...

c1ee: 20 c5 c8     plread          jsr     XRDSER            ;read data from serial port (or buffer)
c1f1: 90 fb                        bcc     plread            ;Branch if data not ready
c1f3: a2 00        plread2         ldx     #0
c1f5: 60                           rts

c1f6: 20 8c c1     plwrite         jsr     serout            ;Go output character
c1f9: 80 f8                        bra     plread2

c1fb: 80 1a        plstatus        bra     p2status

c1fd: 00 00 00                     .align  $0100 (3 bytes)

                   NOTE: file COMM
c200: 2c 58 ff     comslot         bit     IORTS             ;Set V to indicate initial entry
c203: 70 2b                        bvs     entr
c205: 38           sin             sec                       ;Input entry point
c206: 90                           .dd1    $90               ;BCC opcode to skip next byte
c207: 18           sout            clc                       ;Output entry point
c208: b8                           clv                       ;Mark not initial entry
c209: 50 25                        bvc     entr              ;Branch around pascal entry stuff

c20b: 01                           .dd1    $01               ;pascal signature byte
c20c: 31                           .dd1    $31               ;device signature
c20d: 11                           .dd1    <p2init
c20e: 13                           .dd1    <p2read
c20f: 15                           .dd1    <p2write
c210: 17                           .dd1    <p2status

                   ; 
                   ; Pascal support stuff
                   ; 
c211: 80 d1        p2init          bra     plinit

c213: 80 d9        p2read          bra     plread

c215: 80 df        p2write         bra     plwrite

c217: a2 40        p2status        ldx     #$40              ;anticipate bad status request
c219: 4a                           lsr     A                 ;shift request to carry
c21a: d0 12                        bne     notrdy
c21c: aa                           tax                       ;clear x for no error return code
c21d: a9 08                        lda     #8                ;anticipate input ready request
c21f: b0 01                        bcs     pstat2            ;branch if good guess.
c221: 0a                           asl     A
c222: 09 20        pstat2          ora     #$20              ;include DCD in test
c224: 39 89 c0                     and     sstat+144,y
c227: f0 05                        beq     notrdy            ;branch if not ready for I/O
c229: 49 20                        eor     #$20
c22b: 38                           sec                       ;assume port is ready
c22c: d0 01                        bne     isrdy             ;branch if good assumption
c22e: 18           notrdy          clc                       ;indicate acia not ready for I/O
c22f: 60           isrdy           rts

c230: da           entr            phx
c231: a2 c2                        ldx     #>comslot         ;X = <CN00
c233: 5a           setup           phy
c234: 48                           pha
c235: 8e f8 07                     stx     MSLOT
c238: 50 22                        bvc     sudone            ;First call?
c23a: a5 36                        lda     CSWL              ;If both hooks CN00 setup defaults
c23c: 45 38                        eor     KSWL
c23e: f0 06                        beq     sudodef
c240: a5 37                        lda     CSWH              ;If both hooks CN then don't do def
c242: c5 39                        cmp     KSWH              ;since it has already been done
c244: f0 03                        beq     sunodef
c246: 20 c8 c2     sudodef         jsr     default           ;Set up defaults
c249: 8a           sunodef         txa
c24a: 45 39                        eor     KSWH              ;Input call?
c24c: 05 38                        ora     KSWL
c24e: d0 07                        bne     suout             ;Must be Cn00
c250: a9 05                        lda     #<sin             ;Fix the input hook
c252: 85 38                        sta     KSWL
c254: 38                           sec                       ;C = 1 for input call
c255: 80 05                        bra     sudone

c257: a9 07        suout           lda     #<sout            ;Fix output hook
c259: 85 36                        sta     CSWL              ;Note c might not be 0
c25b: 18                           clc                       ;C=0 for output
c25c: bd b8 06     sudone          lda     flags,x           ;Check if serial or comm port
c25f: 89 01                        bit     #1                ;Leave flags in A for serport
c261: d0 03                        bne     commport
c263: 4c 17 c1     comout          jmp     serport

c266: 90 fb        commport        bcc     comout            ;Output?
c268: 68                           pla                       ;Get the char
c269: 80 28                        bra     term1             ;Input

c26b: 3c b8 03     noesc           bit     sermode,x         ;In temrinal mode?
c26e: 50 1c                        bvc     exit1             ;If not, return key
c270: 20 91 c1                     jsr     serout2           ;Out it goes
c273: 80 1e                        bra     term1

c275: 68           testkbd         pla                       ;Get current char
c276: 20 70 cc                     jsr     UPDATE            ;Update cursor & check keyboard
c279: 10 1b                        bpl     serin             ;N=0 if no new key
c27b: 20 eb c9                     jsr     command           ;Test for command
c27e: b0 eb                        bcs     noesc             ;Branch if not
c280: 29 5f                        and     #$5f              ;upshift for following tests
c282: c9 51                        cmp     #‘Q’              ;Quit?
c284: f0 04                        beq     exitX
c286: c9 52                        cmp     #‘R’              ;Reset?
c288: d0 09                        bne     term1             ;Go check serial
c28a: a9 98        exitX           lda     #$98              ;return a CTRL-X
c28c: 7a           exit1           ply
c28d: fa                           plx
c28e: 60                           rts

c28f: 18           goremote        clc                       ;Into remote mode
c290: 20 cd ca     goterm          jsr     setterm           ;Into terminal mode
c293: 20 4c cc     term1           jsr     SHOWCUR           ;Get current char on screen
c296: 48           serin           pha
c297: 20 c5 c8                     jsr     XRDSER            ;Is it ready?
c29a: 90 d9                        bcc     testkbd           ;If not, try the keyboard
c29c: a8                           tay                       ;Save new input in y for now
c29d: 68                           pla
c29e: 5a                           phy                       ;Save new char on stack
c29f: 20 b8 c3                     jsr     STORCH            ;Fix the screen
c2a2: 68                           pla                       ;Get the new data
c2a3: bc 38 06                     ldy     eschar,x          ;If 0, don't modify char
c2a6: f0 16                        beq     sinomod
c2a8: 09 80                        ora     #$80              ;Apple loves the high bit
c2aa: c9 8a                        cmp     #$8a              ;Ignore line feed
c2ac: f0 e5                        beq     term1
c2ae: c9 91                        cmp     #xon
c2b0: f0 e1                        beq     term1             ;Ignore ^Q
c2b2: c9 ff                        cmp     #$ff              ;Ignore FFs
c2b4: f0 dd                        beq     term1
c2b6: c9 92                        cmp     #$92              ;^R for remote?
c2b8: f0 d5                        beq     goremote
c2ba: c9 94                        cmp     #$94              ;^T for terminal mode?
c2bc: f0 d2                        beq     goterm
c2be: 3c b8 03     sinomod         bit     sermode,x         ;In terminal mode?
c2c1: 50 c9                        bvc     exit1             ;Return to user if not A = char
c2c3: 20 ed fd                     jsr     COUT              ;Onto the screen with it
c2c6: 80 cb                        bra     term1

                   ; Set up the defaults.
c2c8: 20 a2 c8     default         jsr     moveirq           ;make sure irq vectors ok
c2cb: bc 3b c2                     ldy     defidx-193,x      ;Index into alt screen. Table in command
c2ce: 20 7c c3     defloop         jsr     GETALT            ;Get default from alt screen
c2d1: 48                           pha
c2d2: 88                           dey
c2d3: 30 04                        bmi     defff             ;Done if minus
c2d5: c0 03                        cpy     #3
c2d7: d0 f5                        bne     defloop           ;Or if 2
c2d9: 20 a2 c8     defff           jsr     moveirq           ;Jam irq vector into LC
c2dc: 68                           pla                       ;Command, control & flags on stack
c2dd: bc 85 c8                     ldy     devno,x
c2e0: 99 fb bf                     sta     scntl,y           ;Set command reg
c2e3: 68                           pla
c2e4: 99 fa bf                     sta     scomd,y
c2e7: 68                           pla
c2e8: 9d b8 06                     sta     flags,x           ;And the flags
c2eb: 29 01                        and     #1                ;A = $01 (^A) if comm mode
c2ed: d0 02                        bne     defcom
c2ef: a9 09                        lda     #9                ;^I for serial port
c2f1: 9d 38 06     defcom          sta     eschar,x
c2f4: 68                           pla                       ;Get printer width
c2f5: 9d b8 04                     sta     pwdth,x
c2f8: 9e b8 03                     stz     sermode,x
c2fb: 60                           rts

c2fc: 03 07        defidx          .bulk   $03,$07
c2fe: 00 00                        .align  $0100 (2 bytes)

                   NOTE: file C3SPACE
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ;                                                                              ;
                   ; THIS IS THE $C3XX ROM SPACE:                                                 ;
                   ;                                                                              ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
c300: 48           C3ENTRY         pha                       ;save regs
c301: da                           phx
c302: 5a                           phy
c303: 80 12                        bra     BASICINIT         ;and init video firmware

c305: 38           C3KEYIN         sec                       ;Pascal 1.1 ID byte
c306: 90                           .dd1    $90               ;BCC OPCODE (NEVER TAKEN)
c307: 18           C3COUT1         clc                       ;Pascal 1.1 ID byte
c308: 80 1a                        bra     BASICENT          ;=>go print/read char

c30a: ea                           nop
                   ; 
                   ; PASCAL 1.1 FIRMWARE PROTOCOL TABLE
                   ; 
c30b: 01                           .dd1    $01               ;GENERIC SIGNATURE BYTE
c30c: 88                           .dd1    $88               ;DEVICE SIGNATURE BYTE
                   ; 
c30d: 2c                           .dd1    <JPINIT           ;PASCAL INIT
c30e: 2f                           .dd1    <JMPREAD          ;PASCAL READ
c30f: 32                           .dd1    <JPWRITE          ;PASCAL WRITE
c310: 35                           .dd1    <JPSTAT           ;PASCAL STATUS

                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ;                                                                              ;
                   ; 128K SUPPORT ROUTINE ENTRIES:                                                ;
                   ;                                                                              ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
c311: 4c 86 cf                     jmp     MOVEAUX           ;MEMORY MOVE ACROSS BANKS

c314: 4c cd cf                     jmp     XFER              ;TRANSFER ACROSS BANKS

                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ;                                                                              ;
                   ; BASIC I/O ENTRY POINT:                                                       ;
                   ;                                                                              ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
c317: 20 20 ce     BASICINIT       jsr     HOOKUP            ;COPYROM if needed, sethooks
c31a: 20 be cd                     jsr     SET80             ;setup 80 columns
c31d: 20 58 fc                     jsr     HOME              ;clear screen
c320: 7a                           ply
c321: fa                           plx                       ;restore x
c322: 68                           pla                       ;restore char
c323: 18                           clc                       ;output a char
                   ; 
c324: b0 03        BASICENT        bcs     BINPUT            ;=>carry me to input
c326: 4c f6 fd     BPRINT          jmp     COUTZ             ;print a character

c329: 4c 1b fd     BINPUT          jmp     KEYIN             ;get a keystroke

c32c: 4c 41 cf     JPINIT          jmp     PINIT             ;pascal init

c32f: 4c 35 cf     JMPREAD         jmp     PASREAD           ;pascal read

c332: 4c c2 ce     JPWRITE         jmp     PWRITE            ;pascal write

c335: 4c b1 ce     JPSTAT          jmp     PSTATUS           ;pascal status call

                   ; 
                   ; COPYROM is called when the video firmware is
                   ; initialized.  If the language card is switched
                   ; in for reading, it copies the F8 ROM to the
                   ; language card and restores the state of the
                   ; language card.
                   ; 
c338: a9 06        COPYROM         lda     #GOODF8           ;get the ID byte
                   ; 
                   ; Compare ID bytes to whatever is readable.  If it
                   ; Matches, all is ok.  If not, need to copy.
                   ; 
c33a: cd b3 fb                     cmp     F8VERSION         ;does it match?
c33d: f0 3c                        beq     ROMOK
c33f: 20 60 c3                     jsr     SETROM            ;read ROM, write RAM, save state
c342: a9 f8                        lda     #$f8              ;from F800-FFFF
c344: 85 37                        sta     CSWH
c346: 64 36                        stz     CSWL
c348: b2 36        COPYROM2        lda     (CSWL)            ;get a byte
c34a: 92 36                        sta     (CSWL)            ;and save a byte
c34c: e6 36                        inc     CSWL
c34e: d0 f8                        bne     COPYROM2
c350: e6 37                        inc     CSWH
c352: d0 f4                        bne     COPYROM2          ;fall into RESETLC
                   ; 
                   ; RESETLC resets the langauge card to the state
                   ; determined by SETROM.  It always leaves the card
                   ; write enabled.
                   ; 
c354: da           RESETLC         phx                       ;save X
c355: ae 78 04                     ldx     ROMSTATE          ;get the state
c358: 3c 81 c0                     bit     ROMIN,x           ;set bank & ROM/RAM read
c35b: 3c 81 c0                     bit     ROMIN,x           ;set write enable
c35e: fa                           plx                       ;restore X
c35f: 60                           rts

                   ; 
                   ; SETROM switches in the ROM for reading, the RAM
                   ; for writing, and it saves the state of the
                   ; language card.  It does not save the write
                   ; protect status of the card.
                   ; 
c360: da           SETROM          phx                       ;save x
c361: a2 00                        ldx     #$00              ;assume write enable,bank2,ROMRD
c363: 2c 11 c0                     bit     RDLCBNK2          ;is bank2 switched in?
c366: 30 02                        bmi     NOT1              ;=>yes
c368: a2 08                        ldx     #$08              ;indicate bank 1
c36a: 2c 12 c0     NOT1            bit     RDLCRAM           ;is LC RAM readable?
c36d: 10 02                        bpl     NOREAD            ;=>no
c36f: e8                           inx                       ;indicate RAM read
c370: e8                           inx
c371: 2c 81 c0     NOREAD          bit     $c081             ;ROM read
c374: 2c 81 c0                     bit     $c081             ;RAM write
c377: 8e 78 04                     stx     ROMSTATE          ;save state
c37a: fa                           plx                       ;restore X
c37b: 60           ROMOK           rts

                   ; 
                   ; GETALT reads a byte from aux memory screenholes.
                   ; Y is the index to the byte (0-7) indexed off of
                   ; address $478.
                   ; 
c37c: ad 13 c0     GETALT          lda     RDRAMRD           ;save state of aux memory
c37f: 0a                           asl     A
c380: ad 18 c0                     lda     RD80COL           ;and of the 80STORE switch
c383: 08                           php
c384: 8d 00 c0                     sta     CLR80COL          ;no 80STORE to get page 1
c387: 8d 03 c0                     sta     RDCARDRAM         ;pop in the other half of RAM
c38a: b9 78 04                     lda     $0478,y           ;read the desired byte
c38d: 28                           plp
c38e: b0 03                        bcs     GETALT1
c390: 8d 02 c0                     sta     RDMAINRAM
c393: 10 03        GETALT1         bpl     GETALT2
c395: 8d 01 c0                     sta     SET80COL
c398: 60           GETALT2         rts

c399: 09 80        UPSHIFT0        ora     #$80              ;set high bit for execs
c39b: c9 fb        UPSHIFT         cmp     #$fb
c39d: b0 06                        bcs     X_UPSHIFT
c39f: c9 e1                        cmp     #$e1
c3a1: 90 02                        bcc     X_UPSHIFT
c3a3: 29 df                        and     #$df
c3a5: 60           X_UPSHIFT       rts

                   ; 
                   ; GETOUT performs COUT for GETLN.  It disables the
                   ; echoing of control characters by clearing the
                   ; M.CTL mode bit, prints the char, the restores
                   ; M.CLT.  NOESC is used by the RDKEY routine to
                   ; disable escape sequences.
                   ; 
c3a6: 48           GETCOUT         pha                       ;save char to print
c3a7: a9 08                        lda     #M_CTL            ;disable control chars
c3a9: 1c fb 04                     trb     VMODE             ;by clearing M_CTL
c3ac: 68                           pla                       ;restore character
c3ad: 20 ed fd                     jsr     COUT              ;and print it
c3b0: 4c 44 fd                     jmp     NOESCAPE          ;enable control characters

                   ; 
                   ; STORCH determines loads the current cursor position,
                   ;        inverts the character, and displays it
                   ; STORCHAR inverts the character and displays it at the
                   ;        position stored in Y.
                   ; STORY  determines the current cursor position, and
                   ;        displays the character without inverting it
                   ; STORE  displays the car at the position in Y
                   ; 
                   ; If mouse characters are enabled (VMODE bit 0 = 0)
                   ; then mouse characters ($40-$5F) are displayed when
                   ; the alternate character set is switched in.  Normally
                   ; values $40-$5F are shifted to $0-$1F before display.
                   ; 
                   ; Calls to GETCUR trash Y
                   ; 
c3b3: 20 9d cc     STORY           jsr     GETCUR            ;get newest cursor into Y
c3b6: 80 09                        bra     STORE

c3b8: 20 9d cc     STORCH          jsr     GETCUR            ;first, get cursor position
c3bb: 24 32                        bit     INVFLG            ;normal or inverse?
c3bd: 30 02                        bmi     STORE             ;=>normal, store it
c3bf: 29 7f                        and     #$7f              ;inverse it
c3c1: 5a           STORE           phy                       ;save real Y
c3c2: 09 00                        ora     #0                ;does char have high bit set?
c3c4: 30 15                        bmi     STORE1            ;=>yes, don't do mouse check
c3c6: 48                           pha                       ;save char
c3c7: ad fb 04                     lda     VMODE             ;is mouse bit set?
c3ca: 6a                           ror     A
c3cb: 68                           pla                       ;restore char
c3cc: 90 0d                        bcc     STORE1            ;=>no, don't do mouse shift
c3ce: 2c 1e c0                     bit     ALTCHARSET        ;no shift if ][ char set
c3d1: 10 08                        bpl     STORE1            ;=> it is!
c3d3: 49 40                        eor     #$40              ;$40-$5F=>0-$1f
c3d5: 89 60                        bit     #$60
c3d7: f0 02                        beq     STORE1
c3d9: 49 40                        eor     #$40
c3db: 2c 1f c0     STORE1          bit     RD80VID           ;80 columns?
c3de: 10 19                        bpl     STORE5            ;=>no, store char
c3e0: 48                           pha                       ;save (shifted) char
c3e1: 8d 01 c0                     sta     SET80COL          ;hit 80 store
c3e4: 98                           tya                       ;get proper Y
c3e5: 45 20                        eor     WNDLFT            ;C=1 if char in main ram
c3e7: 4a                           lsr     A
c3e8: b0 04                        bcs     STORE2            ;=>yes, main RAM
c3ea: ad 55 c0                     lda     TXTPAGE2          ;else flip in aux RAM
c3ed: c8                           iny                       ;do this for odd left, aux bytes
c3ee: 98           STORE2          tya                       ;divide pos'n by 2
c3ef: 4a                           lsr     A
c3f0: a8                           tay
c3f1: 68                           pla                       ;get (shifted) char
c3f2: 91 28        STORE3          sta     (BASL),y          ;stuff it
c3f4: 2c 54 c0                     bit     TXTPAGE1          ;else restore page1
c3f7: 7a           STORE4          ply                       ;restore real Y
c3f8: 60                           rts                       ;und exit

c3f9: 91 28        STORE5          sta     (BASL),y          ;do 40 column store
c3fb: 7a                           ply                       ;restore y
c3fc: 60                           rts                       ;and exit

c3fd: 00 00 00                     .align  $0100 (3 bytes)

                   NOTE: file MOUSE (equates), file MCODE
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ;                                      ;
                   ; Mouse firmware for the Chels         ;
                   ;                                      ;
                   ;  by Rich Williams                    ;
                   ;  July, 1983                          ;
                   ;                                      ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;

                   ; (Regarding moustat $77c:)
                   ; Moustat provides the following
                   ;  D7= Button pressed
                   ;  D6= Status of button on last read
                   ;  D5= Moved since last read
                   ;  D4= Reserved
                   ;  D3= Interrupt from VBL
                   ;  D2= Interrupt from button
                   ;  D1= Interrupt from movement
                   ;  D0= Reserved
                   ; 
                   ; (Regarding moumode $7fc:)
                   ;  D7-D4= Unused
                   ;  D3= VBL active
                   ;  D2= VBL interrupt on button
                   ;  D1= VBL interrupt on movement
                   ;  D0= Mouse active

                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ;                                      ;
                   ; Entry points for mouse firmware      ;
                   ;                                      ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
c400: 80 05        mbasic          bra     outent

c402: a2 03        pnull           ldx     #3
c404: 60                           rts                       ;Null for pascal entry

c405: 38           inent           sec                       ;Signature bytes
c406: 90                           .dd1    $90
c407: 18           outent          clc
c408: 4c 80 c7                     jmp     xmbasic           ;Go do basic entry

c40b: 01                           .dd1    $01               ;More signature stuff
c40c: 20                           .dd1    $20
c40d: 02                           .dd1    <pnull
c40e: 02                           .dd1    <pnull
c40f: 02                           .dd1    <pnull
c410: 02                           .dd1    <pnull
c411: 00                           .dd1    $00
c412: 3d                           .dd1    <xsetmou          ;SETMOUSE
c413: fc                           .dd1    <xmtstint         ;SERVEMOUSE
c414: 95                           .dd1    <xmread           ;READMOUSE
c415: 84                           .dd1    <xmclear          ;CLEARMOUSE
c416: 6b                           .dd1    <noerror          ;POSMOUSE
c417: b0                           .dd1    <xmclamp          ;CLAMPMOUSE
c418: 6d                           .dd1    <xmhome           ;HOMEMOUSE
c419: 1c                           .dd1    <initmouse        ;INITMOUSE
c41a: 02                           .dd1    <pnull
c41b: cf                           .dd1    <xmint

                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ;                                                                              ;
                   ; Initmouse - resets the mouse                                                 ;
                   ;  Also clears all of the mouse holes                                          ;
                   ; note that iou access fires pdlstrb & makes mouse happy                       ;
                   ;                                                                              ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
c41c: 9c 7c 07     initmouse       stz     moustat           ;Clear status
c41f: a2 80                        ldx     #$80
c421: a0 01                        ldy     #1
c423: 9e 7d 04     xrloop          stz     minxl,x           ;Minimum = $0000
c426: 9e 7d 05                     stz     minxh,x
c429: a9 ff                        lda     #$ff              ;Maximum = $03FF
c42b: 9d 7d 06                     sta     maxxl,x
c42e: a9 03                        lda     #3
c430: 9d 7d 07                     sta     maxxh,x
c433: a2 00                        ldx     #0
c435: 88                           dey
c436: 10 eb                        bpl     xrloop
c438: 20 6d c4                     jsr     xmhome            ;Clear the mouse holes
c43b: a9 00                        lda     #0                ;Fall into SETMOU
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ;                                                                              ;
                   ; XSETMOU - Sets the mouse mode to A                                           ;
                   ;                                                                              ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
c43d: aa           xsetmou         tax
c43e: 20 a2 c8                     jsr     moveirq           ;Make sure interrupt vector is right
c441: 8a                           txa                       ;Only x preserved by moveirq
c442: 8d 78 04                     sta     moutemp
c445: 4a                           lsr     A                 ;D0 = 1 if mouse active
c446: 0d 78 04                     ora     moutemp           ;D2 = 1 if vbl active
c449: c9 10                        cmp     #$10              ;If >=$10 then invalid mode
c44b: b0 1f                        bcs     sminvalid
c44d: 29 05                        and     #5                ;Extract VBL & Mouse
c44f: f0 01                        beq     xsoff             ;Turning it off?
c451: 58                           cli                       ;If not, ints active
c452: 69 55        xsoff           adc     #$55              ;Make iou byte C=0
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ;                                                                              ;
                   ; SETIOU - Sets the IOU interrupt modes to A                                   ;
                   ;  Inputs: A - Bits to change                                                  ;
                   ;  D7 = Y int on falling edge                                                  ;
                   ;  D6 = Y int on rising edge                                                   ;
                   ;  D5 = X int on falling edge                                                  ;
                   ;  D4 = X int on rising edge                                                   ;
                   ;  D3 = Enable VBL int                                                         ;
                   ;  D2 = Disable VBL int                                                        ;
                   ;  D1 = Enable mouse int                                                       ;
                   ;  D0 = Disable mouse int                                                      ;
                   ;                                                                              ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
c454: 08           setiou          php
c455: 78                           sei                       ;Don't allow ints while iou enabled
c456: 8e fc 07                     stx     moumode
c459: 8d 79 c0                     sta     iouenbl           ;Enable iou access
c45c: a2 08                        ldx     #8
c45e: ca           siloop          dex
c45f: 0a                           asl     A                 ;Get a bit to check
c460: 90 03                        bcc     sinoch            ;No change if C=0
c462: 9d 58 c0                     sta     iou,x             ;Set it
c465: d0 f7        sinoch          bne     siloop            ;Any bits left in A?
c467: 8d 78 c0                     sta     ioudsbl           ;Turn off iou access
c46a: 28                           plp
c46b: 18           noerror         clc
c46c: 60           sminvalid       rts

                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ;                                                                              ;
                   ; XMHOME- Clears mouse position & status                                       ;
                   ;                                                                              ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
c46d: a2 80        xmhome          ldx     #$80              ;Point mouse to upper left
c46f: 80 02                        bra     xmh2

c471: a2 00        xmhloop         ldx     #0
c473: bd 7d 04     xmh2            lda     minxl,x
c476: 9d 7c 04                     sta     mouxl,x
c479: bd 7d 05                     lda     minxh,x
c47c: 9d 7c 05                     sta     mouxh,x
c47f: ca                           dex
c480: 10 ef                        bpl     xmhloop
c482: 80 0c                        bra     xmcdone

                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ;                                                                              ;
                   ; XMCLEAR - Sets the mouse to 0,0                                              ;
                   ;                                                                              ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
c484: 9c 7c 04     xmclear         stz     mouxl
c487: 9c 7c 05                     stz     mouxh
c48a: 9c fc 04                     stz     mouyl
c48d: 9c fc 05                     stz     mouyh
c490: 9c 7c 06     xmcdone         stz     mouarm
c493: 18                           clc
c494: 60                           rts

                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ;                                                                              ;
                   ; XMREAD - Updates the scren holes                                             ;
                   ;                                                                              ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
c495: a9 20        xmread          lda     #movarm           ;Has mouse moved?
c497: 2d 7c 06                     and     mouarm
c49a: 1c 7c 06                     trb     mouarm            ;Clear arm bit
c49d: 2c 63 c0                     bit     moubut            ;Button pressed?
c4a0: 30 02                        bmi     xrbut
c4a2: 09 80                        ora     #$80
c4a4: 2c 7c 07     xrbut           bit     moustat           ;Pressed last time?
c4a7: 10 02                        bpl     xrbut2
c4a9: 09 40                        ora     #$40
c4ab: 8d 7c 07     xrbut2          sta     moustat
c4ae: 18                           clc
c4af: 60                           rts

                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ;                                                                              ;
                   ; XMCLAMP - Store new bounds                                                   ;
                   ;  Inputs A = 1 for Y, 0 for X axis                                            ;
                   ;    minl, minh, maxl, maxh = new bounds                                       ;
                   ;                                                                              ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
c4b0: 6a           xmclamp         ror     A
c4b1: 6a                           ror     A                 ;1 -> 80
c4b2: 29 80                        and     #$80
c4b4: aa                           tax
c4b5: ad 78 04                     lda     minl
c4b8: 9d 7d 04                     sta     minxl,x
c4bb: ad 78 05                     lda     minh
c4be: 9d 7d 05                     sta     minxh,x
c4c1: ad f8 04                     lda     maxl
c4c4: 9d 7d 06                     sta     maxxl,x
c4c7: ad f8 05                     lda     maxh
c4ca: 9d 7d 07                     sta     maxxh,x
c4cd: 18                           clc                       ;No error
c4ce: 60                           rts

                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ;                                                                              ;
                   ; Mouse interrupt handler                                                      ;
                   ;                                                                              ;
                   ; MOUSEINT - Monitor's interrupt handler                                       ;
                   ; XMINT - Interrupt handler the user can use                                   ;
                   ; XMTSTINT - Checks mouse status bits                                          ;
                   ;                                                                              ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
c4cf: ae 66 c0     xmint           ldx     moux1             ;Get X1 & Y1 asap
c4d2: ac 67 c0                     ldy     mouy1
c4d5: a9 0e        mouseint        lda     #$0e              ;Entry point if X & Y set up; Clear status bits
c4d7: 1c 7c 07                     trb     moustat
c4da: 38                           sec                       ;Assume interrupt not handled
                   ; Check for vertical blanking interrupt
c4db: ad 19 c0                     lda     vblint            ;VBL interrupt?
c4de: 10 48                        bpl     chkmou
c4e0: 8d 79 c0                     sta     iouenbl           ;Enable iou access & clear VBL interrupt
c4e3: a9 0c                        lda     #vblmode          ;Should we leave vbl active?
c4e5: 2c fc 07                     bit     moumode
c4e8: d0 03                        bne     cvnovbl
c4ea: 8d 5a c0                     sta     iou+2             ;Disable VBL
c4ed: 09 02        cvnovbl         ora     #movmode
c4ef: 80 1b                        bra     xmskip

c4f1: a9 0e        mistat          lda     #$0e
c4f3: 2d 7c 07                     and     moustat
c4f6: d0 01                        bne     nostat2
c4f8: 38                           sec
c4f9: 68           nostat2         pla
c4fa: 60                           rts

c4fb: d6                           .dd1    $d6               ;Signature byte

c4fc: 48           xmtstint        pha
c4fd: 18                           clc
c4fe: 80 f1                        bra     mistat            ;Go check status

c500: ff                           .dd1    $ff

c501: 20 4d ce                     jsr     ZZQUIT            ;Get out of the hooks
c504: a2 ff                        ldx     #$ff
c506: 20 24 cb     qloop           jsr     zznm2
c509: 10 fb                        bpl     qloop
c50b: 60                           rts

c50c: 8d 78 c0     xmskip          sta     ioudsbl
c50f: 2c 7c 06                     bit     mouarm            ;VBL bit in arm isn't used
c512: d0 02                        bne     cvmoved
c514: a9 0c                        lda     #vblmode          ;Didn't move
c516: 2c 63 c0     cvmoved         bit     moubut            ;Button pressed?
c519: 10 02                        bpl     cvbut
c51b: 49 04                        eor     #butmode          ;Clear the button bit
c51d: 2d fc 07     cvbut           and     moumode           ;Which bits were set in the mode
c520: 0c 7c 07                     tsb     moustat
c523: 1c 7c 06                     trb     mouarm
c526: 69 fe                        adc     #$fe              ;C=1 if int passes to user
                   ; Check & update mouse movement
c528: ad 15 c0     chkmou          lda     mouxint           ;Mouse interrupt?
c52b: 0d 17 c0                     ora     mouyint
c52e: 10 6a                        bpl     xmdone            ;If not return with C from vbl
c530: 8a                           txa                       ;Get X1 in A
c531: a2 00                        ldx     #0
c533: 2c 15 c0                     bit     mouxint           ;X movement?
c536: 30 0a                        bmi     cmxmov
c538: 98           cmloop          tya                       ;Get Y1 into A
c539: 49 80                        eor     #$80              ;Complement direction
c53b: a2 80                        ldx     #$80
c53d: 2c 17 c0                     bit     mouyint
c540: 10 39                        bpl     cmnoy
c542: 0a           cmxmov          asl     A
c543: bd 7c 04                     lda     mouxl,x           ;A = current low byte
c546: b0 1a                        bcs     cmrght            ;Which way?
c548: dd 7d 04                     cmp     minxl,x           ;Move left
c54b: d0 08                        bne     cmlok
c54d: bd 7c 05                     lda     mouxh,x
c550: dd 7d 05                     cmp     minxh,x
c553: f0 22                        beq     cmnoint
c555: bd 7c 04     cmlok           lda     mouxl,x
c558: d0 03                        bne     cmnt0             ;Borrow from high byte?
c55a: de 7c 05                     dec     mouxh,x
c55d: de 7c 04     cmnt0           dec     mouxl,x
c560: 80 15                        bra     cmnoint

c562: dd 7d 06     cmrght          cmp     maxxl,x           ;At high bound?
c565: d0 08                        bne     cmrok
c567: bd 7c 05                     lda     mouxh,x
c56a: dd 7d 07                     cmp     maxxh,x
c56d: f0 08                        beq     cmnoint
c56f: fe 7c 04     cmrok           inc     mouxl,x           ;Move right
c572: d0 03                        bne     cmnoint
c574: fe 7c 05                     inc     mouxh,x
c577: e0 00        cmnoint         cpx     #0
c579: f0 bd                        beq     cmloop
c57b: 8d 48 c0     cmnoy           sta     mouclr
c57e: a9 02                        lda     #movmode          ;Should we enable VBL?
c580: 2d fc 07                     and     moumode
c583: f0 09                        beq     cmnovbl           ;Branch if not
c585: 8d 79 c0                     sta     iouenbl
c588: 8d 5b c0                     sta     iou+3             ;Enable VBL int
c58b: 8d 78 c0                     sta     ioudsbl
c58e: 09 20        cmnovbl         ora     #movarm           ;Mark that we moved
c590: 0c 7c 06                     tsb     mouarm
c593: a9 0e                        lda     #$0e
c595: 2d 7c 07                     and     moustat
c598: 69 fe                        adc     #$fe              ;C=1 iff any bits were 1
c59a: 60           xmdone          rts

                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ;                                                                              ;
                   ; HEXTODEC - Puts +0000, into the input buffer                                 ;
                   ;  inputs: A = Low byte of number                                              ;
                   ;          X = High byte of number                                             ;
                   ;          Y = Position of ones digit                                          ;
                   ;                                                                              ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
c59b: e0 80        hextodec        cpx     #$80              ;Is it a negative number?
c59d: 90 0d                        bcc     hexdec2
c59f: 49 ff                        eor     #$ff              ;Form two's complement
c5a1: 69 00                        adc     #0                ;C = 1 from compare
c5a3: 48                           pha                       ;Save it
c5a4: 8a                           txa
c5a5: 49 ff                        eor     #$ff
c5a7: 69 00                        adc     #0
c5a9: aa                           tax
c5aa: 68                           pla
c5ab: 38                           sec
c5ac: 8d 14 02     hexdec2         sta     binl              ;Store the number to convert
c5af: 8e 15 02                     stx     binh
c5b2: a9 ab                        lda     #“+”              ;Store the sign in the buffer
c5b4: 90 02                        bcc     hdpos2
c5b6: a9 ad                        lda     #“-”
c5b8: 48           hdpos2          pha                       ;Save the sign
c5b9: a9 ac                        lda     #“,”              ;Store a comma after the number
c5bb: 99 01 02                     sta     inbuf+1,y
                   ; 
                   ; Divide BINH,L by 10 and leave remainder in A
                   ; 
c5be: a2 11        hdloop          ldx     #17               ;16 bits and first time do nothing
c5c0: a9 00                        lda     #0
c5c2: 18                           clc                       ;C=0 so first EOL leaves A=0
c5c3: 2a           dv10loop        rol     A
c5c4: c9 0a                        cmp     #10               ;A >= 10?
c5c6: 90 02                        bcc     dv10lt            ;Branch if <
c5c8: e9 0a                        sbc     #10               ;C = 1 from compare and is left set
c5ca: 2e 14 02     dv10lt          rol     binl
c5cd: 2e 15 02                     rol     binh
c5d0: ca                           dex
c5d1: d0 f0                        bne     dv10loop
c5d3: 09 b0                        ora     #“0”              ;Make a ascii char
c5d5: 99 00 02                     sta     inbuf,y
c5d8: 88                           dey
c5d9: f0 08                        beq     hddone            ;Stop on 0,6,12
c5db: c0 07                        cpy     #7
c5dd: f0 04                        beq     hddone
c5df: c0 0e                        cpy     #14
c5e1: d0 db                        bne     hdloop
c5e3: 68           hddone          pla                       ;Get the sign
c5e4: 99 00 02                     sta     inbuf,y
c5e7: 60                           rts

c5e8: df 67 37 1c+ qtbl            .bulk   $df,$67,$37,$1c,$07,$0c,$45,$62
c5f0: 6e 7e 3b 0a+                 .bulk   $6e,$7e,$3b,$0a,$0b,$48,$77,$7b
c5f8: 66 2b 0c 08+                 .bulk   $66,$2b,$0c,$08,$16,$53,$68,$c5

                   NOTE: 5.25" disk drive boot code
c600: a2 20                        ldx     #$20
c602: a0 00                        ldy     #$00
c604: 64 03                        stz     $03
c606: 64 3c                        stz     $3c
c608: a9 60                        lda     #$60
c60a: aa                           tax
c60b: 86 2b        DRV2ENT         stx     SLOTZ
c60d: 85 4f                        sta     RNDH
c60f: 5a                           phy                       ;Y=1 if DRIVE 2 BOOT, ELSE Y=0
c610: bd 8e c0                     lda     $c08e,x
c613: bd 8c c0                     lda     $c08c,x
c616: 7a                           ply
c617: b9 ea c0                     lda     $c0ea,y           ;SELECT DRIVE 1 OR 2
c61a: bd 89 c0                     lda     $c089,x
c61d: a0 50                        ldy     #$50
c61f: bd 80 c0     SEEKZERO        lda     $c080,x
c622: 98                           tya
c623: 29 03                        and     #$03
c625: 0a                           asl     A
c626: 05 2b                        ora     SLOTZ
c628: aa                           tax
c629: bd 81 c0                     lda     $c081,x
c62c: a9 56                        lda     #$56
c62e: 20 a8 fc                     jsr     WAIT
c631: 88                           dey
c632: 10 eb                        bpl     SEEKZERO
c634: 85 26                        sta     $26
c636: 85 3d                        sta     $3d
c638: 85 41                        sta     $41
c63a: 20 09 c7                     jsr     MAKTBL
c63d: 64 03        EXTENT1         stz     $03
c63f: 18           RDADR           clc
c640: 08                           php
c641: 28           RETRY1          plp
c642: a6 2b        RDDHDR          ldx     SLOTZ             ;RESTORE X TO $60
c644: c6 03                        dec     $03               ;UPDATE RETRY COUNT
c646: d0 0e                        bne     RDHD0             ;BRANCH IF NOT OUT OF RETRIES
c648: bd 88 c0     FUGIT           lda     $c088,x           ;SHUT OFF DISK AND QUIT!
c64b: bd cf c6     FUG1            lda     MSG-96,x          ;(X STARTS AT $60)
c64e: 10 fe        HANGING         bpl     HANGING           ;HANG, HANG, HANG!
c650: 9d 7b 07                     sta     BOOTSCRN-96,x
c653: e8                           inx
c654: 80 f5                        bra     FUG1

c656: 08           RDHD0           php
c657: 88           RETRY           dey
c658: d0 04                        bne     RDHD1
c65a: f0 e5                        beq     RETRY1

c65c: 80 df        EXTENT          bra     EXTENT1

                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ; The following code is sacred in it's  ;
                   ; present form.  To change it would     ;
                   ; cause volcanos to erupt, the ground   ;
                   ; to shake, and ProDOS not to boot!     ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
c65e: bd 8c c0     RDHD1           lda     $c08c,x
c661: 10 fb                        bpl     RDHD1
c663: 49 d5        ISMRK1          eor     #$d5
c665: d0 f0                        bne     RETRY
c667: bd 8c c0     RDHD2           lda     $c08c,x
c66a: 10 fb                        bpl     RDHD2
c66c: c9 aa                        cmp     #$aa
c66e: d0 f3                        bne     ISMRK1
c670: ea                           nop
c671: bd 8c c0     RDHD3           lda     $c08c,x
c674: 10 fb                        bpl     RDHD3
c676: c9 96                        cmp     #$96
c678: f0 09                        beq     RDSECT
c67a: 28                           plp
c67b: 90 c2                        bcc     RDADR
c67d: 49 ad                        eor     #$ad
c67f: f0 25                        beq     RDATA
c681: d0 bc                        bne     RDADR

c683: a0 03        RDSECT          ldy     #$03
c685: 85 40        RDSEC1          sta     $40
c687: bd 8c c0     RDSEC2          lda     $c08c,x
c68a: 10 fb                        bpl     RDSEC2
c68c: 2a                           rol     A
c68d: 85 3c                        sta     BOOTTMP
c68f: bd 8c c0     RDSEC3          lda     $c08c,x
c692: 10 fb                        bpl     RDSEC3
c694: 25 3c                        and     BOOTTMP
c696: 88                           dey
c697: d0 ec                        bne     RDSEC1
c699: 28                           plp
c69a: c5 3d                        cmp     $3d
c69c: d0 a1                        bne     RDADR
c69e: a5 40                        lda     $40
c6a0: c5 41                        cmp     $41
c6a2: d0 9b        BADRD1          bne     RDADR
c6a4: b0 9c                        bcs     RDDHDR
c6a6: a0 56        RDATA           ldy     #$56
c6a8: 84 3c        RDAT0           sty     BOOTTMP
c6aa: bc 8c c0     RDAT1           ldy     $c08c,x
c6ad: 10 fb                        bpl     RDAT1
c6af: 59 d6 02                     eor     DNIBL-128,y
c6b2: a4 3c                        ldy     BOOTTMP
c6b4: 88                           dey
c6b5: 99 00 03                     sta     NBUF1,y
c6b8: d0 ee                        bne     RDAT0
c6ba: 84 3c        RDAT2           sty     BOOTTMP
c6bc: bc 8c c0     RDAT3           ldy     $c08c,x
c6bf: 10 fb                        bpl     RDAT3
c6c1: 59 d6 02                     eor     DNIBL-128,y
c6c4: a4 3c                        ldy     BOOTTMP
c6c6: 91 26                        sta     ($26),y
c6c8: c8                           iny
c6c9: d0 ef                        bne     RDAT2
c6cb: bc 8c c0     RDAT4           ldy     $c08c,x
c6ce: 10 fb                        bpl     RDAT4
c6d0: 59 d6 02                     eor     DNIBL-128,y
c6d3: d0 cd        BADREAD         bne     BADRD1
c6d5: a0 00                        ldy     #$00
c6d7: a2 56        DENIBL          ldx     #$56
c6d9: ca           DENIB1          dex
c6da: 30 fb                        bmi     DENIBL
c6dc: b1 26                        lda     ($26),y
c6de: 5e 00 03                     lsr     NBUF1,x
c6e1: 2a                           rol     A
c6e2: 5e 00 03                     lsr     NBUF1,x
c6e5: 2a                           rol     A
c6e6: 91 26                        sta     ($26),y
c6e8: c8                           iny
c6e9: d0 ee                        bne     DENIB1
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ; Code beyond this point is not ;
                   ; sacred... It may be perverted ;
                   ; in any manner by any pervert. ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
c6eb: e6 27                        inc     $27
c6ed: e6 3d                        inc     $3d
c6ef: a5 3d                        lda     $3d
c6f1: cd 00 08                     cmp     $0800
c6f4: a6 4f                        ldx     BOOTDEV
c6f6: 90 db                        bcc     BADREAD
c6f8: 4c 01 08                     jmp     $0801

c6fb: 4c 0b c6     DODRV2          jmp     DRV2ENT

c6fe: 00 00                        .align  $0100 (2 bytes)
c700: ff                           .dd1    $ff               ;MAKE IT LOOK LIKE NOTHING IN SLOT

c701: a9 e0                        lda     #$e0              ;FOR DEVICE #2
c703: a0 01                        ldy     #1                ;TO SELECT DRIVE 2
c705: a2 60                        ldx     #$60
c707: 80 f2                        bra     DODRV2

c709: a2 03        MAKTBL          ldx     #$03
c70b: a0 00                        ldy     #0
c70d: 86 3c        TBLLOOP         stx     BOOTTMP
c70f: 8a                           txa
c710: 0a                           asl     A
c711: 24 3c                        bit     BOOTTMP
c713: f0 10                        beq     NOPATRN
c715: 05 3c                        ora     BOOTTMP
c717: 49 ff                        eor     #$ff
c719: 29 7e                        and     #$7e
c71b: b0 08        TBLLOOP2        bcs     NOPATRN
c71d: 4a                           lsr     A
c71e: d0 fb                        bne     TBLLOOP2
c720: 98                           tya
c721: 9d 56 03                     sta     DNIBL,x
c724: c8                           iny
c725: e8           NOPATRN         inx
c726: 10 e5                        bpl     TBLLOOP
c728: a9 08                        lda     #$08
c72a: 85 27                        sta     $27
c72c: a0 7f                        ldy     #$7f
c72e: 60                           rts

c72f: c3 e8 e5 e3+ MSG             .str    “Check Disk Drive.”
                   ; 
                   ; The following code is Teri's memory and
                   ; soft switch exercise program.  The only
                   ; purpose is exercise, not diagnostic
                   ; functions.  This code is activated on
                   ; a system without a keyboard, or when
                   ; both open and closed apple keys are
                   ; pressed during the reset sequence.
                   ; 
c740: 08 50 52     TBL1            .bulk   $08,$50,$52       ;These are low order
c743: 00 02 04                     .bulk   $00,$02,$04       ; addresses of $C0XX
c746: 8b 8b e8                     .bulk   $8b,$8b,$e8       ;that must be re-selected
c749: 09 50 52     TBL2            .bulk   $09,$50,$52       ; after each page write
c74c: 00 03 05                     .bulk   $00,$03,$05       ; (especially $C000!)
c74f: 83 83 e8                     .bulk   $83,$83,$e8

c752: 64 00        XLOOP1          stz     $00               ;Reset low address to 2
c754: e6 00                        inc     $00               ;HI addr assumed to = 0
c756: e6 00                        inc     $00
c758: 92 00        XPAGE           sta     ($00)             ;Write entire page with
c75a: 9d 00 c0                     sta     CLR80COL,x        ; shifted data... BUT
c75d: 6a                           ror     A                 ; restore Z-page after
c75e: e6 00                        inc     $00               ; write in case $c008-9
c760: d0 f6                        bne     XPAGE             ; is current pointer
c762: 18                           clc                       ;Indicates regular pass
c763: 98           XMODE           tya                       ;Get settings, each bit
c764: a0 08                        ldy     #$08              ;Specifies main/alt set
c766: be 40 c7     XRSET           ldx     TBL1,y            ;Assume Main $C000 setting
c769: 90 03                        bcc     XRST1             ;Branch if Main setting
c76b: be 49 c7                     ldx     TBL2,y            ;Else get Alternate index
c76e: 9d 00 c0     XRST1           sta     $c000,x
c771: 2a                           rol     A                 ;Accumulator makes full
c772: 88                           dey                       ; circle
c773: 10 f1                        bpl     XRSET
c775: a8                           tay                       ;Preserve settings in Y
c776: b0 da                        bcs     XLOOP1            ;Branch if new setting
c778: e6 01                        inc     $01
c77a: d0 dc                        bne     XPAGE             ;Loop til all pages written
c77c: 38           BANGER          sec                       ;Indicate new settings,
c77d: c8                           iny                       ; reset mem pointer after
c77e: 80 e3                        bra     XMODE             ; after new settings

                   NOTE: file MBASIC
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ;                                                                              ;
                   ; XMBASIC - Basic call to the mouse                                            ;
                   ;                                                                              ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
c780: 5a           xmbasic         phy
c781: b0 1c                        bcs     basicin           ;Input?
c783: a0 c4                        ldy     #>mbasic          ;Input from $C400?
c785: c4 39                        cpy     KSWH
c787: d0 04                        bne     xmbout
c789: a4 38                        ldy     KSWL
c78b: f0 12                        beq     basicin
c78d: da           xmbout          phx                       ;Save X too
c78e: 48                           pha
c78f: 29 7f                        and     #$7f              ;We don't care about high bit
c791: c9 02                        cmp     #2
c793: b0 06                        bcs     mbbad             ;Only 0,1 valid
c795: 20 3d c4                     jsr     xsetmou
c798: 20 6d c4                     jsr     xmhome
c79b: 68           mbbad           pla
c79c: fa                           plx
c79d: 7a                           ply
c79e: 60                           rts

                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ;                                                                              ;
                   ; BASICIN - Input from basic                                                   ;
                   ;                                                                              ;
                   ; Creates  +XXXXX,+YYYYY,+SS                                                   ;
                   ;  XXXXX = X position                                                          ;
                   ;  YYYYY = Y position                                                          ;
                   ;  SS = Status                                                                 ;
                   ;       - = Key pressed                                                        ;
                   ;       1 = Button pressed                                                     ;
                   ;       2 = Button just pressed                                                ;
                   ;       3 = Button just released                                               ;
                   ;       4 = Button not pressed                                                 ;
                   ;                                                                              ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
c79f: 91 28        basicin         sta     (BASL),y          ;Fix flashing char
c7a1: a9 05                        lda     #<inent           ;Fix input entry
c7a3: 85 38                        sta     KSWL
c7a5: ad 00 c0                     lda     KBD               ;test the keyboard
c7a8: 0a                           asl     A
c7a9: 08                           php                       ;Save kbd and int stat for later
c7aa: 78                           sei                       ;No interrupts while getting position
c7ab: 20 95 c4                     jsr     xmread
c7ae: a0 05                        ldy     #5                ;Move x position into the buffer
c7b0: ae 7c 05                     ldx     mouxh
c7b3: ad 7c 04                     lda     mouxl
c7b6: 20 9b c5                     jsr     hextodec          ;Convert it
c7b9: a0 0c                        ldy     #12
c7bb: ae fc 05                     ldx     mouyh
c7be: ad fc 04                     lda     mouyl
c7c1: 20 9b c5                     jsr     hextodec
c7c4: ad 7c 07                     lda     moustat
c7c7: 2a                           rol     A
c7c8: 2a                           rol     A
c7c9: 2a                           rol     A
c7ca: 29 03                        and     #3
c7cc: 49 03                        eor     #3
c7ce: 1a                           inc     A
c7cf: 28                           plp                       ;Restore int & kbd status
c7d0: a0 10                        ldy     #16
c7d2: 20 ac c5                     jsr     hexdec2           ;X=0 from last div10
c7d5: 7a                           ply
c7d6: a2 11                        ldx     #17               ;X = EOL
c7d8: a9 8d                        lda     #$8d              ;Carriage return
c7da: 9d 00 02     putinbuf        sta     inbuf,x
c7dd: 60                           rts

                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ;                                                                              ;
                   ; PADDLE patch                                                                 ;
                   ;                                                                              ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
c7de: ad fc 07     MPADDLE         lda     moumode           ;Is the mouse active?
c7e1: c9 01                        cmp     #$01              ;Only transparent mode
c7e3: f0 06                        beq     pdon
c7e5: ad 70 c0                     lda     vblclr            ;Fire the strobe
c7e8: 4c 21 fb                     jmp     $fb21

c7eb: e0 01        pdon            cpx     #1                ;C=1 if X=1
c7ed: 6a                           ror     A                 ;A=80 or 0
c7ee: a8                           tay
c7ef: b9 7c 05                     lda     mouxh,y           ;Get high byte
c7f2: f0 02                        beq     pdok
c7f4: a9 ff                        lda     #$ff
c7f6: 19 7c 04     pdok            ora     mouxl,y
c7f9: a8                           tay
c7fa: 60                           rts

c7fb: 5d e8 c5     zznml           eor     qtbl,x
c7fe: 80 da                        bra     putinbuf

                   NOTE: file IRQBUF
                   ; 
                   ; this is the main (only) IRQ handling routines
                   ; 
c800: 4c e4 c1                     jmp     plinit            ;Pascal 1.0 Initialization

c803: 48           NEWIRQ          pha                       ;SAVE ACC ON STACK, NOT $45
c804: 68                           pla                       ;LEGAL BECAUSE IF IRQ, IRQ DISABLED
c805: 68                           pla                       ;GET STATUS REGISTER
c806: 48           IRQ1            pha
c807: d8                           cld                       ;CLEAR DEC MODE, ELSE THINGS GET SCREWED.
c808: 29 10                        and     #$10              ;SET CARRY TO INDICATE BRK
c80a: 69 f0                        adc     #$f0
c80c: 8a                           txa                       ;SAVE X IN A WHILE
c80d: ba                           tsx                       ; FUTZING WITH THE STACK
c80e: ca                           dex                       ; RECOVER A-REG AT TOP...
c80f: 9a                           txs
c810: 48                           pha                       ;SAVE X ON STACK (ON TOP OF A)
c811: 5a                           phy                       ; AND Y ALSO
c812: ae 66 c0                     ldx     moux1             ;Get mouse info
c815: ac 67 c0                     ldy     mouy1
c818: ad 18 c0                     lda     RD80COL           ;TEST FOR 80-STORE WITH
c81b: 2d 1c c0                     and     RDPAGE2           ; PAGE 2 TEXT.
c81e: 29 80                        and     #$80              ; MAKE IT ZERO OR $80
c820: f0 05                        beq     IRQ2
c822: 8d 54 c0                     sta     TXTPAGE1
c825: a9 40                        lda     #$40              ;SET PAGE 2 RESET BIT.
c827: 2c 13 c0     IRQ2            bit     RDRAMRD
c82a: 10 05                        bpl     IRQ3              ;BRANCH IF MAIN RAM READ
c82c: 8d 02 c0                     sta     RDMAINRAM         ;ELSE, SWITCH IT IN
c82f: 09 20                        ora     #$20              ; AND RECORD THE EVENT!
c831: 2c 14 c0     IRQ3            bit     RDRAMWRT          ;DO THE SAME FOR RAM WRITE.
c834: 10 05                        bpl     IRQ4
c836: 8d 04 c0                     sta     WRMAINRAM
c839: 09 10                        ora     #$10
c83b: b0 13        IRQ4            bcs     IRQ5              ;BRANCH IF BREAK, NOT INTERRUPT
c83d: 48                           pha                       ;SAVE MACHINE STATES SO FAR...
c83e: 20 d5 c4                     jsr     mouseint          ;GO TEST THE MOUSE
c841: 90 3f                        bcc     IRQDONE           ;BRANCH IF IT WAS THE MOUSE
c843: 20 00 c9                     jsr     aciaint           ;GO TEST ACIA AND KEYBOARD INTERRUPTS
c846: 90 3a                        bcc     IRQDONE           ;BRANCH IF INTERRUPT SERVICED
c848: 68                           pla                       ;RESTORE STATES RECORDED SO FAR
c849: 18                           clc                       ;RESET BREAK/INTERRUPT INDICATOR
c84a: 80 04                        bra     IRQ5              ;Skip around pascal 1.0 stuff

c84c: 34                           .junk   1

c84d: 4c ee c1                     jmp     plread

c850: 2c 12 c0     IRQ5            bit     RDLCRAM           ;DETERMINE IF LANGUAGE CARD ACTIVE
c853: 10 0c                        bpl     IRQ7
c855: 09 0c                        ora     #$0c              ;SET TWO BITS SO RESTORED
c857: 2c 11 c0                     bit     RDLCBNK2          ; LANGUAGE CARD IS WRITE ENABLED
c85a: 10 02                        bpl     IRQ6              ;BRANCH IF NOT PAGE 2 OF $D000
c85c: 49 06                        eor     #$06              ;ENABLE READ FOR PAGE 2 ON EXIT
c85e: 8d 81 c0     IRQ6            sta     ROMIN
c861: 2c 16 c0     IRQ7            bit     RDALTZP           ;LAST...AND VERY IMPORTANT!
c864: 10 0d                        bpl     IRQ8              ; UNLESS IT IS NOT ENABLED
c866: ba                           tsx                       ;SAVE CURRENT STACK POINTER
c867: 8e 01 01                     stx     $0101             ;AT BOTTOM OF STACK
c86a: ae 00 01                     ldx     $0100             ;GET MAIN STACK POINTER
c86d: 9a                           txs
c86e: 8d 08 c0                     sta     SETSTDZP
c871: 09 80                        ora     #$80
c873: b0 2a        IRQ8            bcs     GOBREAK
c875: 48                           pha
c876: a9 c8                        lda     #>IRQDONE
c878: 48                           pha
c879: a9 82                        lda     #<IRQDONE         ;SAVE RETURN IRQ ADDR
c87b: 48                           pha
c87c: a9 04                        lda     #4                ; SO WHEN INTERRUPT DOES RTI
c87e: 48                           pha                       ; IT RETURNS TO IRQDONE.
c87f: 6c fe 03                     jmp     ($03fe)           ;PROCESS EXTERNAL INTERRUPT

c882: 68           IRQDONE         pla                       ;RECOVER MACHINE STATE
c883: 10 07                        bpl     IRQDNE1           ;BRANCH IF MAIN ZP WAS ACTIVE
c885: 8d 09 c0     devno           sta     SETALTZP          ;[devno is defined at $c946]
c888: ae 01 01                     ldx     $0101             ;RESTORE ALTERNATE STACK POINTER
c88b: 9a                           txs
c88c: 0a           IRQDNE1         asl     A
c88d: a0 05                        ldy     #$05
c88f: be 89 c9     IRQDNE2         ldx     IRQTBLE,y
c892: 88                           dey
c893: 0a                           asl     A
c894: 90 03                        bcc     IRQDNE3           ;BRANCH IF SWITCH IS OK.
c896: 9d 00 c0                     sta     $c000,x
c899: d0 f4        IRQDNE3         bne     IRQDNE2           ;BRANCH IF MORE SWITCHES
c89b: 7a                           ply
c89c: fa                           plx                       ;RESTORE ALL REGISTERS
c89d: 68                           pla
c89e: 40                           rti                       ;DO THE REAL RTI!

c89f: 4c 47 fa     GOBREAK         jmp     NEWBRK            ;PASS THE BREAKER THROUGH

                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ;                                                                              ;
                   ; MOVEIRQ - This routine transfers the roms interrupt vector into              ;
                   ;  both language cards                                                         ;
                   ;                                                                              ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
c8a2: 20 60 c3     moveirq         jsr     SETROM            ;Read ROM and Write to RAM
c8a5: ad 16 c0                     lda     RDALTZP           ;Which language card?
c8a8: 0a                           asl     A                 ;C=1 if alternate card
c8a9: a0 01                        ldy     #1                ;Move two bytes
c8ab: b9 fe ff     MIRQLP          lda     IRQVECT,y         ;Get byte from ROM
c8ae: 8d 09 c0                     sta     SETALTZP          ;Set alternate card
c8b1: 99 fe ff                     sta     IRQVECT,y         ;Store it in the RAM card
c8b4: 8d 08 c0                     sta     SETSTDZP          ;Set main card
c8b7: 99 fe ff                     sta     IRQVECT,y
c8ba: 88                           dey
c8bb: 10 ee                        bpl     MIRQLP            ;Go do the second byte
c8bd: 90 03                        bcc     MIRQSTD           ;Is the card set right?
c8bf: 8d 09 c0                     sta     SETALTZP          ;No, it wasn't
c8c2: 4c 54 c3     MIRQSTD         jmp     RESETLC           ;Clean up & go home

                   ; 
                   ;   This is the serial interrupt routine.  Carry
                   ; flag set indicates that returned data is
                   ; valid.
                   ; 
                   ; GETBUF- Gets a byte from the buffer & updates pointers
                   ;  On entry Y=0 for Serial buffer Y=$80 for Keyboard buffer
                   ; 
c8c5: ec ff 04     XRDSER          cpx     aciabuf           ;is serial input buffered?
c8c8: d0 26                        bne     XNOSBUF           ;(in english "NO SERIAL BUFFER")
c8ca: a0 00                        ldy     #0                ;Y=0 for serial buffer
c8cc: b9 7f 06     GETBUF          lda     trser,y           ;Test for data in buffer
c8cf: d9 7f 05                     cmp     twser,y           ;If = then no data
c8d2: f0 24                        beq     GBEMPTY
c8d4: 48                           pha                       ;Save current value
c8d5: 1a                           inc     A                 ;Update the pointer
c8d6: 89 7f                        bit     #$7f              ;Overflow
c8d8: d0 01                        bne     GBNOOVR
c8da: 98                           tya
c8db: 99 7f 06     GBNOOVR         sta     trser,y           ;Store the updated pointer
c8de: 7a                           ply                       ;Get the old value of the pointer
c8df: ad 13 c0                     lda     RDRAMRD           ;Are we in main ram
c8e2: 0a                           asl     A                 ;C=1 for Aux ram
c8e3: 8d 03 c0                     sta     RDCARDRAM         ;Force Aux ram
c8e6: b9 00 08                     lda     thbuf,y           ;Get byte from buffer
c8e9: b0 14                        bcs     XRDSNO            ;Branch if we were in aux bank
c8eb: 8d 02 c0                     sta     RDMAINRAM         ;Set back to main
c8ee: 38                           sec
c8ef: 60                           rts                       ;Note C=1

c8f0: bc 85 c8     XNOSBUF         ldy     devno,x           ;Get index to ACIA
c8f3: b9 f9 bf                     lda     sstat,y           ;Test ACIA directly for data
c8f6: 29 08                        and     #$08
c8f8: 18           GBEMPTY         clc                       ;indicate no data
c8f9: f0 04                        beq     XRDSNO            ;Branch if no data!
c8fb: b9 f8 bf                     lda     sdata,y           ;get serial input
c8fe: 38           notacia         sec                       ;indicate valid data returned.
c8ff: 60           XRDSNO          rts

                   ;   This routine will determine if the source of
                   ; is either of the built in ACIAs.  If neither port
                   ; generated the interrupt, or the interrupt was due
                   ; to a transmit buffer empty, protocol converter, or
                   ; 'unbuffered' receiver full, the carry is set indi-
                   ; cating an externally serviced interrupt.
                   ;   If the interrupt source was keyboard, 'buffered'
                   ; serial input, or the DCD, the interrupt is serviced
                   ; and the carry is cleared indicating interrupt was
                   ; serviced.  (DCD handshake replaces CTS.)
                   ;   Location "ACIABUF" specifies which (if either) re-
                   ; receiver data is buffered.  For port 1 it must contain
                   ; $C1, for port 2 a $C2.  Any other values are cause
                   ; interrupts to pass to external (RAM based) routines.
                   ;   Location "TYPHED" specifies whether Keyboard in-
                   ; put should be buffered, ignored, or processed by 
                   ; RAM based rountines.  If bit 7=1 and bit 6=0, key-
                   ; board data is placed in the type-ahead buffer.  If
                   ; bit 6 is set the interrupt is cleared, but must
                   ; be recognized and serviced by a RAM routine.  If
                   ; both bits = 0, the interrupt is serviced, but the
                   ; keyboard data is ignored.
                   ;   While using type-ahead, Open-Apple CTRL-X will
                   ; flush the buffer.  No other code is recognized.
                   ;   If the source was an ACIA that has the transmit
                   ; interrupt enabled, the original value of the ACIAs
                   ; status registers is preserved. Automatic serial input
                   ; buffering is not serviced from a port so configured.
                   ; Interrupts originating from the protocol converter or
                   ; keyboard (RAM serviced) do not inhibit serial buffering
                   ; and are passed thru.  The RAM service routine can rec-
                   ; ognize the interrupt source by a 1 state in bit 6 of
                   ; the ACIAs status register.  The RAM service routine must
                   ; cause the clearing of DSR (bit 6) AND make a second ac-
                   ; cess to the status register before returning.
c900: a2 c2        aciaint         ldx     #>comslot         ;Test port 2 first
c902: 20 08 c9                     jsr     aciast            ;Check for interrupt
c905: 90 f8                        bcc     XRDSNO            ;Return if interrupt done
c907: ca                           dex                       ;Try port 1
c908: bc 85 c8     aciast          ldy     devno,x           ;Get index for acia
c90b: a9 04                        lda     #$04              ;If xmit ints enabled pass to user
c90d: 59 fa bf                     eor     scomd,y           ;Check if D<3>, D<2> = 01
c910: 29 0c                        and     #$0c
c912: f0 ea                        beq     notacia           ;User better take it!
c914: b9 f9 bf                     lda     sstat,y           ;Get status
c917: 9d 38 04                     sta     astat,x           ;Save it away
c91a: 10 e2                        bpl     notacia           ;No interrupt
c91c: e0 c2        aitst2          cpx     #>comslot         ;C=1 if com port
c91e: b0 02                        bcs     aiport2           ;Invert DSR if port1
c920: 49 40                        eor     #$40
c922: 3c 38 05     aiport2         bit     extint,x          ;Is DSR enabled?
c925: 70 26                        bvs     aipass            ;Yes, user wants it
c927: 10 22                        bpl     aieatit           ;No, eat it
c929: 90 20                        bcc     aieatit           ;Yes but I don't want it for port 1
c92b: 89 40                        bit     #$40              ;Is DSR 1?
c92d: f0 1e                        beq     aipass            ;If not, skip it
                   ; It's a keyboard interrupt
c92f: ad 00 c0                     lda     KBD               ;Get the key
c932: a0 80                        ldy     #$80
c934: 20 67 c9                     jsr     putbuf            ;Put it in the buffer
c937: c9 98                        cmp     #$98              ;Is it a ^x?
c939: d0 08                        bne     ainoflsh
c93b: ad 62 c0                     lda     BUTN1             ;And the closed apple?
c93e: 10 03                        bpl     ainoflsh
c940: 20 1b cb                     jsr     flush             ;Flush the buffer
c943: ad 10 c0     ainoflsh        lda     KBDSTRB           ;Clear the keyboard
                   ; $A0 $B0 table needed by serial firmware
                   ; [ sltdmy equ <serslot
                   ;   devno  equ *-sltdmy  --> $c885 ]
c946: a0 b0                        ldy     #$b0              ;Restore y
c948: b9 f9 bf                     lda     sstat,y           ;Read status to clear int
c94b: 29 bf        aieatit         and     #$bf              ;Clear the DSR bit
c94d: 0a           aipass          asl     A                 ;Shift DSR into C
c94e: 0a                           asl     A
c94f: 29 20                        and     #$20              ;Is the receiver full?
c951: f0 35                        beq     aciadone          ;If not, we're done
c953: b9 fa bf                     lda     scomd,y           ;Are receive interrupts enabled?
c956: 49 01                        eor     #1                ;Check for D<1>,D<0> = 01
c958: 29 03                        and     #3
c95a: d0 2c                        bne     aciadone          ;If not, we're done
c95c: 8a                           txa                       ;Is this acia buffered?
c95d: 4d ff 04                     eor     aciabuf
c960: d0 9c                        bne     notacia           ;The user better handle it!
c962: b9 f8 bf                     lda     sdata,y           ;It's mine
c965: a0 00                        ldy     #0
c967: da           putbuf          phx
c968: 48                           pha
c969: b9 7f 05                     lda     twser,y           ;Get buffer pointer
c96c: aa                           tax                       ;Save it for later
c96d: 1a                           inc     A                 ;Bump it to next free byte
c96e: 89 7f                        bit     #$7f              ;Overflow?
c970: d0 01                        bne     pbok
c972: 98                           tya                       ;Wrap pointer
c973: 08           pbok            php                       ;Save DSR status
c974: d9 7f 06                     cmp     trser,y           ;Buffer full?
c977: f0 03                        beq     pbfull
c979: 99 7f 05                     sta     twser,y           ;Save the new pointer
c97c: 28           pbfull          plp
c97d: 68                           pla                       ;Get the data
c97e: 8d 05 c0                     sta     WRCARDRAM         ;It goes to aux ram
c981: 9d 00 08                     sta     thbuf,x
c984: 8d 04 c0                     sta     WRMAINRAM
c987: fa                           plx
c988: 60           aciadone        rts

c989: 83           IRQTBLE         .dd1    <LCBANK2
c98a: 8b                           .dd1    <LCBANK1
c98b: 8b                           .dd1    <LCBANK1
c98c: 05                           .dd1    <WRCARDRAM
c98d: 03                           .dd1    <RDCARDRAM
c98e: 55                           .dd1    <TXTPAGE2

                   ; 
                   ;   The following two routines are for reading key-
                   ; board and serial input from buffers or directly.
                   ;   Type-ahead buffering only occurs for non auto-
                   ; repeat keypresses.  When a key is pressed for
                   ; auto-repeat the bufer is first emptied, then the
                   ; repeated characters are returned.
                   ;   The minus flag is used to indicate if a keystroke
                   ; is being returned
                   ; 
c98f: 20 ad c9     XRDKBD          jsr     XBITKBD           ;is keyboard input ready?
c992: 10 14                        bpl     XNOKEY            ;Branch if not.
c994: 90 0a                        bcc     XRKBD1            ;Branch if direct KBD input.
c996: 5a                           phy                       ;Save Y
c997: a0 80                        ldy     #$80              ;Y=$80 for keyboard buffer
c999: 20 cc c8                     jsr     GETBUF            ;Get data from buffer
c99c: 7a                           ply
c99d: 09 00                        ora     #0                ;Set minus flag
c99f: 60                           rts

c9a0: ad 00 c0     XRKBD1          lda     KBD               ;test keyboard directly
c9a3: 10 ea                        bpl     XRDKBD            ;loop if buffered since test.
c9a5: 8d 10 c0                     sta     KBDSTRB           ;Clear keyboard strobe.
c9a8: 60           XNOKEY          rts                       ;Minus flag indicates valid character

c9a9: 34                           .junk   1

c9aa: 4c f6 c1                     jmp     plwrite           ;Pascal 1.0 entry point

c9ad: 2c fa 05     XBITKBD         bit     typhed            ;This routine replaces "BIT KBD" intrucs
c9b0: 10 10                        bpl     XBKB2             ; so as to funciton with type-ahead.
c9b2: 38                           sec                       ;anticipate data in buffer is ready
c9b3: 08                           php                       ;save carry and minus flags
c9b4: 48                           pha                       ;preserve accumulator
c9b5: ad ff 06                     lda     ttrkey
c9b8: cd ff 05                     cmp     twkey             ;is there data to be read?
c9bb: f0 03                        beq     XBKB1             ;branch if type-ahead buffer empty
c9bd: 68                           pla
c9be: 28                           plp
c9bf: 60                           rts                       ;Carry and minus flag already set.

c9c0: 68           XBKB1           pla
c9c1: 28                           plp                       ;restore ACC and Status
c9c2: 2c 00 c0     XBKB2           bit     KBD               ;test KBD Directly
c9c5: 18                           clc                       ;indicate direct test
c9c6: 60                           rts

                   NOTE: file COMMAND
c9c7: 66           cmdtable        .dd1    <cmdi-1
c9c8: 66                           .dd1    <cmdi-1           ;[cmdk]
c9c9: 66                           .dd1    <cmdi-1           ;[cmdl]
c9ca: 5c                           .dd1    <cmdn-1
c9cb: 5c                           .dd1    <cmdn-1           ;[cmdcr]
c9cc: 7c                           .dd1    <cmdb-1
c9cd: 78                           .dd1    <cmdd-1
c9ce: 77                           .dd1    <cmdp-1
c9cf: c3                           .dd1    <cmdq-1
c9d0: b4                           .dd1    <cmdr-1
c9d1: 98                           .dd1    <cmds-1
c9d2: c5                           .dd1    <cmdt-1
c9d3: 54                           .dd1    <cmdz-1
c9d4: 7f bf bf 7f+ mask1           .bulk   $7f,$bf,$bf,$7f,$ff
c9d9: 80 00 40 00+ mask2           .bulk   $80,$00,$40,$00,$00
c9de: 49 4b 4c 4e  cmdlist         .str    ‘IKLN’
c9e2: 0d                           .dd1    $0d               ;Carriage return
c9e3: 42 44 50 51+                 .str    ‘BDPQRSTZ’

c9eb: 48           command         pha                       ;Check for command to firmware
c9ec: 3c b8 03                     bit     sermode,x         ;Already in command?
c9ef: 30 1b                        bmi     incmd             ;If so,go do it
c9f1: bc 38 06                     ldy     eschar,x          ;If eschar = 0 ignore commands
c9f4: f0 13                        beq     nocmd
c9f6: 5d 38 06                     eor     eschar,x          ;Is it the command char?
c9f9: 0a                           asl     A                 ;Ignore high bit
c9fa: d0 0d                        bne     nocmd
c9fc: ac fb 07                     ldy     CURSOR            ;Save the cursor
c9ff: 8c 79 06                     sty     oldcur
ca02: a0 bf                        ldy     #$bf              ;Set command cursor
ca04: 8c fb 07                     sty     CURSOR
ca07: 80 2d                        bra     cominit

ca09: 38           nocmd           sec                       ;Mark char not handled
ca0a: 68                           pla                       ;Restore char
ca0b: 60                           rts

ca0c: bc 85 c8     incmd           ldy     devno,x           ;Command mode; Get index for ACIA
ca0f: 29 5f                        and     #$5f              ;Ignore hi bit: just upshift lowercase
ca11: da                           phx                       ;Save slot
ca12: a2 0c                        ldx     #12               ;Check 13 commands
ca14: dd de c9     cmdloop         cmp     cmdlist,x
ca17: f0 34                        beq     cmfound           ;Right char?
ca19: ca                           dex
ca1a: 10 f8                        bpl     cmdloop
ca1c: fa                           plx                       ;We didn't find it
ca1d: 68                           pla
ca1e: 48                           pha
ca1f: 29 7f                        and     #$7f              ;if char is cntl char
ca21: c9 20                        cmp     #$20              ;it can be the new comd char
ca23: b0 03                        bcs     ckdig             ;branch if not cntl character
ca25: 9d 38 06     cmdz2           sta     eschar,x          ;Save comd char, drop through ckdig to cdone
ca28: 49 30        ckdig           eor     #$30              ;Is it a number?
ca2a: c9 0a                        cmp     #$0a
ca2c: b0 0e                        bcs     cdone             ;If so, branch
ca2e: a0 0a                        ldy     #10               ;A = A + 10 * current number
ca30: 6d 7f 04     digloop         adc     number            ;C=0 on first entry
ca33: 88                           dey
ca34: d0 fa                        bne     digloop
ca36: 8d 7f 04     cominit         sta     number
ca39: 38                           sec                       ;Make in command mode
ca3a: 80 07                        bra     cmset

ca3c: 18           cdone           clc                       ;Out of command mode
ca3d: ad 79 06                     lda     oldcur            ;Restore the cursor
ca40: 8d fb 07                     sta     CURSOR
ca43: 08           cmset           php
ca44: 1e b8 03                     asl     sermode,x         ;set command mode according to carry
ca47: 28                           plp
ca48: 7e b8 03                     ror     sermode,x         ;leaves carry clear
ca4b: 68                           pla                       ;character handled
ca4c: 60                           rts                       ;because carry clear...

ca4d: a9 ca        cmfound         lda     #>cmdn            ;[#>cmdcr]
ca4f: 48                           pha                       ;do JMP via RTS
ca50: bd c7 c9                     lda     cmdtable,x
ca53: 48                           pha
ca54: 60                           rts                       ;Go to it

ca55: fa           cmdz            plx                       ;Zero escape character
ca56: 9e b8 04                     stz     pwdth,x           ;And the width
ca59: a9 00                        lda     #$00
ca5b: 80 c8                        bra     cmdz2

ca5d: 7a           cmdn            ply                       ;[also cmdcr]
ca5e: ad 7f 04                     lda     number            ;Get number inputted
ca61: f0 05                        beq     cmdi2             ;Don't change printer width if 0
ca63: 99 b8 04                     sta     pwdth,y           ;Update printer width
ca66: f0                           .dd1    $f0               ;BEQ opcode to skip next byte
ca67: 7a           cmdi            ply                       ;[also cmdk and cmdl]
ca68: b9 b8 06     cmdi2           lda     flags,y
ca6b: 3d d4 c9                     and     mask1,x           ;Mask off bit we'll change
ca6e: 1d d9 c9                     ora     mask2,x           ;Change it
ca71: 99 b8 06                     sta     flags,y           ;Back it goes
ca74: 98                           tya                       ;Put slow back in x
ca75: aa                           tax
ca76: 80 c4        cdone2          bra     cdone             ;Good bye

ca78: 88           cmdp            dey                       ;Make y point to command reg
ca79: a9 1f        cmdd            lda     #$1f              ;Mask off high three bits
ca7b: 38                           sec                       ;C=1 means high 3 bits
ca7c: 90                           .dd1    $90               ;BCC opcode to skip next byte
ca7d: a9 f0        cmdb            lda     #$f0              ;mask off lower 4 bits F0 = BNE [BEQ]
ca7f: 18                           clc                       ;F0 will skip this if cmdp or cmdd
ca80: 39 fb bf                     and     scntl,y           ;Mask off bits being changed
ca83: 8d f8 06                     sta     temp              ;Save it
ca86: fa                           plx
ca87: ad 7f 04                     lda     number            ;Get inputed number
ca8a: 29 0f                        and     #$0f              ;Only lower nibble valid
ca8c: 90 05                        bcc     noshift           ;If C=1 shift to upper 3 bits
ca8e: 0a                           asl     A
ca8f: 0a                           asl     A
ca90: 0a                           asl     A
ca91: 0a                           asl     A
ca92: 0a                           asl     A
ca93: 0d f8 06     noshift         ora     temp              ;Get the rest of the bits
ca96: c8                           iny                       ;Put them in the ACIA
ca97: 80 17                        bra     cmdp2             ;increment puts em away where they go.

ca99: b9 fa bf     cmds            lda     scomd,y           ;Transmit a break
ca9c: 48                           pha                       ;Save current ACIA state
ca9d: 09 0c                        ora     #$0c              ;Do the break
ca9f: 99 fa bf                     sta     scomd,y
caa2: a9 e9                        lda     #233              ;For 233 ms
caa4: a2 53        mswait          ldx     #83               ;Wait 1 ms
caa6: 48           msloop          pha                       ;((12*82)+11)+2+3=1000us
caa7: 68                           pla
caa8: ca                           dex
caa9: d0 fb                        bne     msloop
caab: 3a                           dec     A
caac: d0 f6                        bne     mswait
caae: 68                           pla
caaf: fa                           plx
cab0: 99 fa bf     cmdp2           sta     scomd,y
cab3: 80 c1                        bra     cdone2

cab5: 99 f9 bf     cmdr            sta     sstat,y           ;Reset the ACIA
cab8: ad 7b 06                     lda     VFACTV            ;Check if video firmware active
cabb: 0a                           asl     A                 ;Save it in C
cabc: 20 23 ce                     jsr     SETHOOKS          ;assume video firmware active
cabf: 90 03                        bcc     cmdq              ;branch if good guesser...
cac1: 20 4d ce                     jsr     ZZQUIT            ;Reset the hooks
cac4: 18           cmdq            clc                       ;Quit terminal mode
cac5: b0                           .dd1    $b0               ;BCS to skip next byte
cac6: 38           cmdt            sec                       ;Into terminal mode
cac7: fa                           plx                       ;Recover X
cac8: 20 cd ca                     jsr     setterm
cacb: 80 a9                        bra     cdone2

cacd: bd b8 03     setterm         lda     sermode,x         ;Get terminal mode status
cad0: 89 40                        bit     #$40              ;Z=1 if not in terminal mode
cad2: 90 12                        bcc     stclr             ;Branch if clearing terminal mode
cad4: d0 20                        bne     stwasok           ;Was already set
cad6: e4 39                        cpx     KSWH              ;Are we in the input hooks
cad8: d0 47                        bne     strts             ;Leaves C=1 if =
cada: 09 40                        ora     #$40              ;Set term mode bit
cadc: ac 79 06                     ldy     oldcur            ;Save what was in oldcur
cadf: 8c 7a 06                     sty     oldcur2
cae2: a0 df                        ldy     #termcur          ;Get new cursor value
cae4: 80 07                        bra     stset

cae6: f0 0e        stclr           beq     stwasok           ;Branch if already clear
cae8: 29 bf                        and     #$bf              ;Clear the bit
caea: ac 7a 06                     ldy     oldcur2           ;Restore the cursor
caed: 9d b8 03     stset           sta     sermode,x
caf0: 8c 79 06                     sty     oldcur            ;Save cursor to be restored after command
caf3: 8c fb 07                     sty     CURSOR
caf6: bc 85 c8     stwasok         ldy     devno,x
caf9: 58                           cli                       ;want to leave with interrupts active
cafa: 08                           php
cafb: 78                           sei                       ;but off while we twittle bits
cafc: b9 fa bf                     lda     scomd,y
caff: 09 02                        ora     #2                ;disable receiver interrupts if
cb01: 90 02                        bcc     cmdt2             ; not in terminal mode
cb03: 29 fd                        and     #$fd              ;enable when in terminal mode
cb05: 99 fa bf     cmdt2           sta     scomd,y
cb08: a9 00                        lda     #0
cb0a: 6a                           ror     A                 ;set kbd interrupts according to t-mode
cb0b: 8d fa 05                     sta     typhed
cb0e: 10 07                        bpl     cmdt3             ;branch if leaving terminal mode
cb10: 9c 7f 05                     stz     twser             ; and set buf...
cb13: 9c 7f 06                     stz     trser
cb16: 8a                           txa                       ;use x to enable serial buffering
cb17: 8d ff 04     cmdt3           sta     aciabuf
cb1a: 28                           plp                       ;restore carry, enable interrupts.
cb1b: 8e ff 05     flush           stx     twkey             ;Flush the type ahead buffer
cb1e: 8e ff 06                     stx     ttrkey
cb21: 60           strts           rts

cb22: 00 00                        .junk   2

cb24: e8           zznm2           inx
cb25: 4c fb c7                     jmp     zznml

cb28: 9e 0b 40 50+ comtbl          .bulk   $9e,$0b,$40,$50,$16,$0b,$01,$00

                   NOTE: file SCROLLING
                   ; 
                   ; SCROLLIT scrolls the screen either up or down, depending
                   ; on the value of X.  It scrolls within windows when even
                   ; or odd edges for both 40 and 80 columns.  It can scroll
                   ; windows down to 1 characters wide.
                   ; 
cb30: da           SCROLLDN        phx                       ;save X
cb31: a2 00                        ldx     #$00              ;direction = down
cb33: 80 03                        bra     SCROLLIT          ;do scroll

cb35: da           SCROLLUP        phx                       ;save X
cb36: a2 01                        ldx     #$01              ;direction = up
cb38: a4 21        SCROLLIT        ldy     WNDWDTH           ;get width of screen window
cb3a: 2c 1f c0                     bit     RD80VID           ;in 40 or 80 columns?
cb3d: 10 18                        bpl     GETST             ;=>40, determine starting line
cb3f: 8d 01 c0                     sta     SET80COL          ;make sure this is enabled
cb42: 98                           tya                       ;get WNDWDTH for test
cb43: 4a                           lsr     A                 ;divide by 2 for 80 column index
cb44: a8                           tay                       ;and save
cb45: a5 20                        lda     WNDLFT            ;test oddity of right edge
cb47: 4a                           lsr     A                 ;by rotating low bit into carry
cb48: b8                           clv                       ;V=0 if left edge even
cb49: 90 03                        bcc     CHKRT             ;=>check right edge
cb4b: 2c c1 cb                     bit     SEV1              ;V=1 if left edge odd
cb4e: 2a           CHKRT           rol     A                 ;restore WNDLFT
cb4f: 45 21                        eor     WNDWDTH           ;get oddity of right edge
cb51: 4a                           lsr     A                 ;C=1 if right edge even
cb52: 70 03                        bvs     GETST             ;if odd left, don't DEY
cb54: b0 01                        bcs     GETST             ;if even right, don't DEY
cb56: 88                           dey                       ;if right edge odd, need one less
cb57: 8c f8 05     GETST           sty     TEMPY             ;save window width
cb5a: ad 1f c0                     lda     RD80VID           ;N=1 if 80 columns
cb5d: 08                           php                       ;save N,Z,V
cb5e: a5 22                        lda     WNDTOP            ;assume scroll from top
cb60: e0 00                        cpx     #0                ;up or down?
cb62: d0 03                        bne     SETDBAS           ;=>up
cb64: a5 23                        lda     WNDBTM            ;down, start scrolling at bottom
cb66: 3a                           dec     A                 ;really need one less
                   ; 
cb67: 8d 78 05     SETDBAS         sta     TEMPA             ;save current line
cb6a: 20 24 fc                     jsr     VTABZ             ;calculate base with window width
                   ; 
cb6d: a5 28        SCRLIN          lda     BASL              ;current line is destination
cb6f: 85 2a                        sta     BAS2L
cb71: a5 29                        lda     BASH
cb73: 85 2b                        sta     BAS2H
                   ; 
cb75: ad 78 05                     lda     TEMPA             ;get current line
cb78: e0 00                        cpx     #0                ;going up?
cb7a: d0 07                        bne     SETUP2            ;=>up, inc current line
cb7c: c5 22                        cmp     WNDTOP            ;down. Reached top yet?
cb7e: f0 39                        beq     SCRL3             ;yes! clear top line, exit
cb80: 3a                           dec     A                 ;no, go up a line
cb81: 80 05                        bra     SETSRC            ;set source for scroll

cb83: 1a           SETUP2          inc     A                 ;up, inc current line
cb84: c5 23                        cmp     WNDBTM            ;at bottom yet?
cb86: b0 31                        bcs     SCRL3             ;yes! clear bottom line, exit
                   ; 
cb88: 8d 78 05     SETSRC          sta     TEMPA             ;save new current line
cb8b: 20 24 fc                     jsr     VTABZ             ;get base for new current line
cb8e: ac f8 05                     ldy     TEMPY             ;get width for scroll
cb91: 28                           plp                       ;get status for scroll
cb92: 08                           php                       ;N=1 if 80 columns
cb93: 10 1f                        bpl     SKPRT             ;=>only do 40 columns
cb95: ad 55 c0                     lda     TXTPAGE2          ;scroll aux page first (even bytes)
cb98: 98                           tya                       ;test Y
cb99: f0 07                        beq     SCRLFT            ;if Y=0, only scroll one byte
cb9b: b1 28        SCRLEVEN        lda     (BASL),y
cb9d: 91 2a                        sta     (BAS2L),y
cb9f: 88                           dey
cba0: d0 f9                        bne     SCRLEVEN          ;do all but last even byte
cba2: 70 04        SCRLFT          bvs     SKPLFT            ;odd left edge, skip this byte
cba4: b1 28                        lda     (BASL),y
cba6: 91 2a                        sta     (BAS2L),y
cba8: ad 54 c0     SKPLFT          lda     TXTPAGE1          ;now do main page (odd bytes)
cbab: ac f8 05                     ldy     TEMPY             ;restore width
cbae: b0 04                        bcs     SKPRT             ;even right edge, skip this byte
cbb0: b1 28        SCRLODD         lda     (BASL),y
cbb2: 91 2a                        sta     (BAS2L),y
cbb4: 88           SKPRT           dey
cbb5: 10 f9                        bpl     SCRLODD
cbb7: 80 b4                        bra     SCRLIN            ;scroll next line

cbb9: 20 a0 fc     SCRL3           jsr     CLRLIN            ;clear current line
cbbc: 20 22 fc                     jsr     VTAB              ;restore original cursor line
cbbf: 28                           plp                       ;pull status off stack
cbc0: fa                           plx                       ;restore X
cbc1: 60           SEV1            rts                       ;done!!!

                   ; 
                   ; DOCLR is called by CLREOL.  It decides whether
                   ; to do a (quick) 40 or 80 column clear to end of line.
                   ; 
cbc2: 2c 1f c0     DOCLR           bit     RD80VID           ;40 or 80 column clear?
cbc5: 30 13                        bmi     CLR80             ;=>clear 80 columns
cbc7: 91 28        CLR40           sta     (BASL),y
cbc9: c8                           iny
cbca: c4 21                        cpy     WNDWDTH
cbcc: 90 f9                        bcc     CLR40
cbce: 60                           rts

cbcf: da           CLRHALF         phx                       ;clear right half of screen
cbd0: a2 d8                        ldx     #$d8              ;for SCRN48
cbd2: a0 14                        ldy     #20
cbd4: a5 32                        lda     INVFLG
cbd6: 29 a0                        and     #$a0
cbd8: 80 17                        bra     CLR2              ;=>jump into middle

cbda: da           CLR80           phx                       ;preserve X
cbdb: 48                           pha                       ;and blank
cbdc: 98                           tya                       ;get count for CH
cbdd: 48                           pha                       ;save for left edge check
cbde: 38                           sec                       ;count=WNDWDTH-Y-1
cbdf: e5 21                        sbc     WNDWDTH
cbe1: aa                           tax                       ;save CH counter
cbe2: 98                           tya                       ;div CH by 2 for half pages
cbe3: 4a                           lsr     A
cbe4: a8                           tay
cbe5: 68                           pla                       ;restore original CH
cbe6: 45 20                        eor     WNDLFT            ;get starting page
cbe8: 6a                           ror     A
cbe9: b0 03                        bcs     CLR0
cbeb: 10 01                        bpl     CLR0
cbed: c8                           iny                       ;iff WNDLFT odd, starting byte odd
cbee: 68           CLR0            pla                       ;get blankity blank
cbef: b0 0b                        bcs     CLR1              ;starting page is 1 (default)
cbf1: 2c 55 c0     CLR2            bit     TXTPAGE2          ;else do page 2
cbf4: 91 28                        sta     (BASL),y
cbf6: 2c 54 c0                     bit     TXTPAGE1          ;now do page 1
cbf9: e8                           inx
cbfa: f0 06                        beq     CLR3              ;all done
cbfc: 91 28        CLR1            sta     (BASL),y
cbfe: c8                           iny                       ;forward 2 columns
cbff: e8                           inx                       ;next CH
cc00: d0 ef                        bne     CLR2              ;not done yet
cc02: fa           CLR3            plx                       ;restore X
cc03: 60                           rts                       ;and exit

cc04: 9c fa 05     CLRPORT         stz     typhed            ;disable typeahead
cc07: 9c f9 05                     stz     extint2           ;and external interrupts
cc0a: 60                           rts

                   ; 
                   ; PASINVERT is used by Pascal to display the cursor. Pascal
                   ; normally leaves the cursor on the screen at all times. It
                   ; is fleetingly removed while a character is displayed, then
                   ; promptly redisplayed.  CTL-F and CTL-E, respecitvely,
                   ; disable and enable display of the cursor when printed using
                   ; the Pascal 1.12 entry point (PWRITE).  Screen I/O is
                   ; significantly faster when the cursor is disabled.  This
                   ; feature is supported by Pascal 1.2 and later.
                   ; 
cc0b: ad fb 04     PASINVERT       lda     VMODE             ;Called by pascal to
cc0e: 29 10                        and     #M_CURSOR         ;display cursor
cc10: d0 0a                        bne     INVX              ;=>cursor off, don't invert
cc12: 20 1d cc     INVERT          jsr     PICKY             ;load Y and get char
cc15: 48                           pha
cc16: 49 80                        eor     #$80              ;FLIP INVERSE/NORMAL
cc18: 20 b3 c3                     jsr     STORY             ;stuff onto screen
cc1b: 68                           pla                       ;for RDCHAR
cc1c: 60           INVX            rts

                   ; 
                   ; PICK lifts a character from the screen in either
                   ; 40 or 80 columns from the current cursor position.
                   ; If the alternate character set is switched in,
                   ; character codes $0-$1F are returned as $40-5F (which
                   ; is what must have been originally printed to the location).
                   ; 
cc1d: 5a           PICKY           phy                       ;save Y
cc1e: 20 9d cc                     jsr     GETCUR            ;get newest cursor into Y
cc21: ad 1f c0                     lda     RD80VID           ;80 columns?
cc24: 10 17                        bpl     PICK1             ;=>no
cc26: 8d 01 c0                     sta     SET80COL          ;force 80STORE if 80 columns
cc29: 98                           tya
cc2a: 45 20                        eor     WNDLFT            ;C=1 if char in main RAM
cc2c: 6a                           ror     A                 ;get low bit into carry
cc2d: b0 04                        bcs     PICK2             ;=>store in main memory
cc2f: ad 55 c0                     lda     TXTPAGE2          ;else switch in page 2
cc32: c8                           iny                       ;for odd left, aux bytes
cc33: 98           PICK2           tya                       ;divide pos'n by 2
cc34: 4a                           lsr     A
cc35: a8                           tay                       ;and use as offset into line
cc36: b1 28                        lda     (BASL),y          ;pick character
cc38: 8d 54 c0                     sta     TXTPAGE1          ;80 columns, switch in
cc3b: 80 02                        bra     PICK3             ;skip 40 column pick

cc3d: b1 28        PICK1           lda     (BASL),y          ;pick 40 column char
cc3f: 2c 1e c0     PICK3           bit     ALTCHARSET        ;only allow if alt set
cc42: 10 06                        bpl     PICK4
cc44: c9 20                        cmp     #$20
cc46: b0 02                        bcs     PICK4
cc48: 09 40                        ora     #$40
cc4a: 7a           PICK4           ply                       ;restore real Y
cc4b: 60                           rts

                   ; 
                   ; SHOWCUR displays either a checkerboard cursor, a solid
                   ; rectangle, or the current cursor character, depending
                   ; on the value of the CURSOR location.  0=inverse cursor,
                   ; $FF=checkerboard cursor, anything else is displayed
                   ; after being anded with inverse mask.
                   ; 
cc4c: ac fb 07     SHOWCUR         ldy     CURSOR            ;what's my type?
cc4f: d0 02                        bne     NOTINV            ;=>not inverse
cc51: 80 bf                        bra     INVERT            ;else invert the char (exit)

                   ; 
                   ; Exit with char in accumulator
                   ; 
cc53: 20 1d cc     NOTINV          jsr     PICKY             ;get char on screen
cc56: 48                           pha                       ;preserve it
cc57: 8d 7b 07                     sta     NXTCUR            ;save for update
cc5a: 98                           tya                       ;test for checkerboard
cc5b: c8                           iny
cc5c: f0 0d                        beq     NOTINV2           ;=>checkerboard, display it
cc5e: 7a                           ply                       ;test char
cc5f: 5a                           phy
cc60: 30 09                        bmi     NOTINV2           ;don't need inverse
cc62: ad 1e c0                     lda     ALTCHARSET        ;mask = $7F if alternate
cc65: 09 7f                        ora     #$7f              ; cahracter set,
cc67: 4a                           lsr     A                 ;$3F if normal char set
cc68: 2d fb 07     NOTINV1         and     CURSOR            ;form char to display
cc6b: 20 b3 c3     NOTINV2         jsr     STORY             ;and display it
cc6e: 68                           pla                       ;restore real char
cc6f: 60                           rts

                   ; 
                   ; The UPDATE routine increments the random seed.
                   ; If a certain value is reached and we are in Apple II
                   ; mode, the blinking check cursor is updated.  If a
                   ; key has been pressed, the old char is replaced on the
                   ; screen, and we return with BMI.
                   ; 
                   ; NOTE: this routine used by COMM firmware!!
                   ; 
cc70: 48           UPDATE          pha                       ;save char
cc71: e6 4e                        inc     RNDL              ;update seed
cc73: d0 1c                        bne     UD2               ;check for key
cc75: a5 4f                        lda     RNDH
cc77: e6 4f                        inc     RNDH
cc79: 45 4f                        eor     RNDH
cc7b: 29 10                        and     #$10              ;need to update cursor?
cc7d: f0 12                        beq     UD2               ;=>no, check for key
cc7f: ad fb 07                     lda     CURSOR            ;what cursor are we using?
cc82: f0 0d                        beq     UD2               ;=>//e cursor, leave alone
cc84: 20 1d cc                     jsr     PICKY             ;get the character into A
cc87: ac 7b 07                     ldy     NXTCUR            ;get next character
cc8a: 8d 7b 07                     sta     NXTCUR            ;save next next character
cc8d: 98                           tya
cc8e: 20 b3 c3                     jsr     STORY             ;and print it
cc91: 68           UD2             pla                       ;get real char
cc92: 20 ad c9                     jsr     XBITKBD           ;was a key pressed?
cc95: 10 28                        bpl     GETCURX           ;=>no key pressed
cc97: 20 b3 c3     CLRKBD          jsr     STORY             ;restore old key
cc9a: 4c 8f c9                     jmp     XRDKBD            ;look for keystroke and exit

                   ; 
                   ; ON CURSORS.  Whenever the horizontal cursor position is
                   ; needed, a call to GETCUR is done. This is the equivalent
                   ; of a LDY CH.  This returns the current cursor for II and
                   ; //e mode, which may have been poked as either CH or OURCH.
                   ; 
                   ; It also forces CH and OLDCH to 0 if 80 column mode active.
                   ; This prevents LDY CH, STA (BASL),Y from trashing non screen
                   ; memory. It works just like the //e.
                   ; 
                   ; All routines that update the cursor's horizontal position
                   ; are here.  This ensures that the newest value of the cursor
                   ; is always used, and that 80 column CH is always 0.
                   ; 
                   ; GETCUR only affects the Y register
                   ; 
cc9d: a4 24        GETCUR          ldy     CH                ;if CH=OLDCH, then
cc9f: cc 7b 04                     cpy     OLDCH             ;OURCH is valid
cca2: d0 03                        bne     GETCUR1           ;=>else CH must have been changed
cca4: ac 7b 05                     ldy     OURCH             ;use OURCH
cca7: c4 21        GETCUR1         cpy     WNDWDTH           ;is the value too big
cca9: 90 02                        bcc     GETCUR2           ;=>no, fits just fine
ccab: a0 00                        ldy     #0                ;else force CH to 0
                   ; 
                   ; GETCUR2 is commonly used to set the current cursor
                   ; position when Y can be used.
                   ; 
ccad: 8c 7b 05     GETCUR2         sty     OURCH             ;update real cursor
ccb0: 2c 1f c0                     bit     RD80VID           ;80 columns?
ccb3: 10 02                        bpl     GETCUR3           ;=>no, set all cursors
ccb5: a0 00                        ldy     #$00              ;yes, peg CH to 0
ccb7: 84 24        GETCUR3         sty     CH
ccb9: 8c 7b 04                     sty     OLDCH
ccbc: ac 7b 05                     ldy     OURCH             ;get cursor
ccbf: 60           GETCURX         rts                       ;and fly...

                   NOTE: file ESCAPE
                   ; 
                   ; START AN ESCAPE SEQUENCE:
                   ;  WE HANDLE THE FOLLOWING ONES:
                   ;    @ - HOME & CLEAR
                   ;    A - Cursor right
                   ;    B - Cursor left
                   ;    C - Cursor down
                   ;    D - Cursor up
                   ;    E - CLR TO EOL
                   ;    F - CLR TO EOS
                   ;    I - Up Arrow - CURSOR UP (stay escape)
                   ;    J - Lft Arrow - CURSOR LEFT (stay escape)
                   ;    K - Rt Arrow - CURSOR RIGHT (stay escape)
                   ;    M - Dn Arrow - CURSOR DOWN (stay escape)
                   ;    4 - GOTO 40 COLUMN MODE
                   ;    8 - GOTO 80 COLUMN MODE
                   ; CTL-D- Disable the printing of control chars
                   ; CTL-E- Enable the printing of control chars
                   ; CTL-Q- QUIT (PR#0/IN#0)
                   ; 
ccc0: b9 0c cd     ESC3            lda     ESCCHAR,y         ;GET CHAR TO "PRINT"
ccc3: 5a                           phy                       ;save index
ccc4: 20 58 cd                     jsr     CTLCHAR           ;execute character
ccc7: 7a                           ply                       ;restore index
ccc8: c0 08                        cpy     #8                ;[YHI] If Y<YHI, stay escape
ccca: b0 21                        bcs     ESCRDKEY          ;=>exit escape mode
                   ; 
                   ; This is the entry point called by RDKEY iff escapes
                   ; are enabled and an escape is encountered.  The next
                   ; keypress is read and processed.  If it is a key that
                   ; terminates escape mode, a new key is read by ESCRDKEY.
                   ; If escape mode should not be terminated, NEWESC is
                   ; called again.
                   ; 
cccc: 20 1d cc     NEWESC          jsr     PICKY             ;get current character
cccf: 48                           pha                       ;and save it
ccd0: 29 80                        and     #$80              ;save invert bit
ccd2: 49 ab                        eor     #$ab              ;make it inverted "+"
ccd4: 20 b3 c3                     jsr     STORY             ;and pop it on the screen
ccd7: 20 ad c9     ESC0            jsr     XBITKBD           ;check for keystroke
ccda: 10 fb                        bpl     ESC0
ccdc: 68                           pla                       ;get old char
ccdd: 20 97 cc                     jsr     CLRKBD            ;restore char, get key
cce0: 20 9b c3                     jsr     UPSHIFT           ;upshift esc char
cce3: a0 13        ESC1            ldy     #19               ;[ESCNUM] COUNT/INDEX
cce5: d9 f8 cc     ESC2            cmp     ESCTAB,y          ;IS IT A VALID ESCAPE?
cce8: f0 d6                        beq     ESC3              ;=>yes
ccea: 88                           dey
cceb: 10 f8                        bpl     ESC2              ;TRY 'EM ALL...
                   ; 
                   ; End of escape sequence, read next character.
                   ; This is initially called by RDCHAR which is usually called
                   ; by GETLN to read characters with escapes enabled.
                   ; 
cced: a9 08        ESCRDKEY        lda     #M_CTL            ;enable escape sequences
ccef: 1c fb 04                     trb     VMODE
ccf2: 20 0c fd                     jsr     RDKEY             ;read char with escapes
ccf5: 4c 44 fd                     jmp     NOESCAPE          ;got the key, disable escapes

                   ; 
                   ; When in escape mode, the characters in ESCTAB (high)
                   ; bits set), are mapped into the characters in ESCHAR.
                   ; These characters are then executed by a call to CTLCHAR.
                   ; 
                   ; CTLCHAR looks up a character in the table starting at
                   ; CTLTAB.  It uses the current index as an index into the
                   ; table of routine addresses, CTLADR.  If the character is 
                   ; not in the table, a call to VIDOUT1 is done in case the 
                   ; character is BS, LF, CR, or BEL.
                   ; 
                   ; NOTE: CTLON and CTLOFF are not accessible except through
                   ; and escape sequence
                   ; 
ccf8: ca           ESCTAB          .dd1    “J”               ;left (stay esc)
ccf9: 88                           .dd1    $88               ;left arrow (stay esc)
ccfa: cd                           .dd1    “M”               ;down (stay esc)
ccfb: 8b                           .dd1    $8b               ;up arrow (stay esc)
ccfc: 95                           .dd1    $95               ;right arrow (stay esc)
ccfd: 8a                           .dd1    $8a               ;down arrow (stay esc)
ccfe: c9                           .dd1    “I”               ;up (stay esc)
ccff: cb                           .dd1    “K”               ;right (stay esc)
                   ; [YH1 EQU *-ESCTAB]
cd00: c2                           .dd1    “B”               ;left
cd01: c3                           .dd1    “C”               ;down
cd02: c4                           .dd1    “D”               ;up
cd03: c1                           .dd1    “A”               ;right
cd04: c0                           .dd1    “@”               ;formfeed
cd05: c5                           .dd1    “E”               ;clear EOL
cd06: c6                           .dd1    “F”               ;clear EOS
cd07: b4                           .dd1    “4”               ;40 column mode
cd08: b8                           .dd1    “8”               ;80 column mode
cd09: 91                           .dd1    $91               ;CTL-Q = QUIT
cd0a: 84                           .dd1    $84               ;CTL-D ;ctl char disable
cd0b: 85                           .dd1    $85               ;CTL-E ;ctl char enable
                   ; list of escape chars
                   ; [ESCNUM EQU *-ESCTAB-1]
cd0c: 88           ESCCHAR         .dd1    $88               ;J: BS (stay esc)
cd0d: 88                           .dd1    $88               ;<-:BS (stay esc)
cd0e: 8a                           .dd1    $8a               ;M: LF (stay esc)
cd0f: 9f                           .dd1    $9f               ;UP:US (stay esc)
cd10: 9c                           .dd1    $9c               ;->:FS (stay esc)
cd11: 8a                           .dd1    $8a               ;DN: LF (stay esc)
cd12: 9f                           .dd1    $9f               ;I: LF (stay esc)
cd13: 9c                           .dd1    $9c               ;K: RT (stay esc)
cd14: 88                           .dd1    $88               ;ESC-B = BS
                   ; list of control characters
cd15: 8a           CTLTAB          .dd1    $8a               ;ESC-C = DN
cd16: 9f                           .dd1    $9f               ;ESC-D = UP
cd17: 9c                           .dd1    $9c               ;ESC-A = RT
cd18: 8c                           .dd1    $8c               ;@: Formfeed
cd19: 9d                           .dd1    $9d               ;E: CLREOL
cd1a: 8b                           .dd1    $8b               ;F: CLREOP
cd1b: 91                           .dd1    $91               ;SET40
cd1c: 92                           .dd1    $92               ;SET80
cd1d: 95                           .dd1    $95               ;QUIT
cd1e: 04                           .dd1    $04               ;Disable controls (escape only)
cd1f: 05                           .dd1    $05               ;Enable controls (escape only)
                   ; escape chars end here
cd20: 85                           .dd1    $85               ;X.CUR.ON
cd21: 86                           .dd1    $86               ;X.CUR.OFF
cd22: 8e                           .dd1    $8e               ;Normal
cd23: 8f                           .dd1    $8f               ;Inverse
cd24: 96                           .dd1    $96               ;Scroll down
cd25: 97                           .dd1    $97               ;Scroll up
cd26: 98                           .dd1    $98               ;mouse chars off
cd27: 99                           .dd1    $99               ;home cursor
cd28: 9a                           .dd1    $9a               ;clear line
cd29: 9b                           .dd1    $9b               ;mouse chars on
                   ; [CTLNUM EQU *-CTLTAB-1]
cd2a: 66 fc        CTLADR          .dd2    LF                ;move cursor down
cd2c: 1a fc                        .dd2    UP                ;move cursor up
cd2e: a0 fb                        .dd2    NEWADV            ;forward a space
cd30: 58 fc                        .dd2    HOME              ;home cursor, clear screen
cd32: 9c fc                        .dd2    CLREOL            ;clear to end of line
cd34: 42 fc                        .dd2    CLREOP            ;clear to end of page
cd36: c0 cd                        .dd2    SET40             ;set 40 column mode
cd38: be cd                        .dd2    SET80             ;set 80 column mode
cd3a: 45 ce                        .dd2    QUIT              ;Quit video firmware
cd3c: 91 cd                        .dd2    CTLOFF            ;disable //e control chars
cd3e: 95 cd                        .dd2    CTLON             ;enable //e control chars
cd40: 89 cd                        .dd2    X_CUR_ON          ;turn on cursor (pascal)
cd42: 8d cd                        .dd2    X_CUR_OFF         ;turn off cursor (pascal)
cd44: b0 cd                        .dd2    X_SO              ;normal video
cd46: b7 cd                        .dd2    X_SI              ;inverse video
cd48: 30 cb                        .dd2    SCROLLDN          ;scroll down a line
cd4a: 35 cb                        .dd2    SCROLLUP          ;scroll up a line
cd4c: 9f cd                        .dd2    MOUSOFF           ;disable mouse characters
cd4e: a5 cd                        .dd2    HOMECUR           ;move cursor home
cd50: a0 fc                        .dd2    CLRLIN            ;clear current line
cd52: 99 cd                        .dd2    MOUSON            ;enable mouse characters

                   ; 
                   ; CTLCHAR executes the control character in the
                   ; accumulator.  If it is called by Pascal, the character
                   ; is always executed.  If it is called by the video
                   ; firmware, the character is executed if M.CTL is set
                   ; and M.CTL2 is clear.
                   ; 
                   ; Note: This routine is only called if the video firmware
                   ; is active. The Monitor ROM calls VIDOUT1 if the video
                   ; firmware is inactive.
                   ; 
cd54: 2c c1 cb     CTLCHAR0        bit     SEV1              ;set V (use M.CTL)
cd57: 50                           .dd1    $50               ;BVC opcode (never taken)
cd58: b8           CTLCHAR         clv                       ;Always do the control character
cd59: da                           phx                       ;save X
cd5a: 8d f8 04                     sta     TEMP1             ;temp save of A
cd5d: 20 04 fc                     jsr     VIDOUT1           ;try to execute CR, LF, BS, or BEL
cd60: cd f8 04                     cmp     TEMP1             ;if acc has changed
cd63: d0 0a                        bne     CTLDONE           ;then function done
cd65: a2 14                        ldx     #20               ;[CTLNUM] number of CTL chars
cd67: dd 15 cd     FNDCTL          cmp     CTLTAB,x          ;is it in table
cd6a: f0 05                        beq     CTLGO             ;=>yes, should we execute?
cd6c: ca                           dex                       ;else check next
cd6d: 10 f8                        bpl     FNDCTL            ;=>try next one
cd6f: fa           CTLDONE         plx                       ;restore X
cd70: 60                           rts                       ;and return

cd71: 48           CTLGO           pha                       ;save A
cd72: 50 0c                        bvc     CTLGO1            ;V clear, always do (pascal,escape)
cd74: ad fb 04                     lda     VMODE             ;controls are enabled iff
cd77: 29 28                        and     #$28              ;[#M.CTL+M.CTL2] M.CTL = 1 and
cd79: 49 08                        eor     #M_CTL            ; M.CTL2 = 0
cd7b: f0 03                        beq     CTLGO1            ;=>they're enabled!!
cd7d: 68           CGO             pla                       ;restore A
cd7e: fa                           plx                       ;restore X
cd7f: 60                           rts                       ;and return

cd80: 8a           CTLGO1          txa                       ;double X as index
cd81: 0a                           asl     A                 ;into address table
cd82: aa                           tax
cd83: 68                           pla                       ;restore A
cd84: 20 a4 fc                     jsr     CLTD0             ;execute the char
cd87: fa                           plx                       ;restore X
cd88: 60                           rts                       ;and return

                   ; 
                   ; X.CUR.ON = Allow Pascal cursor display
                   ; X.CUR.OFF = Disable Pascal cursor display
                   ; Cursor is not displayed during call, so it will
                   ; be right when "redisplayed".
                   ; Note: Though these commands are executed from BASIC,
                   ; they have no effect on firmware operation.
                   ; 
cd89: a9 10        X_CUR_ON        lda     #M_CURSOR         ;clear cursor bit
cd8b: 80 0e                        bra     CLRIT

cd8d: a9 10        X_CUR_OFF       lda     #M_CURSOR         ;set cursor bit
cd8f: 80 10                        bra     SETIT

                   ; 
                   ; The control characters other than CR,LF,BEL,BS
                   ; are normally enabled when video firmware is active.
                   ; They can be disabled and enabled using the ESC-D
                   ; and ESC-E escape sequences.
                   ; 
cd91: a9 20        CTLOFF          lda     #M_CTL2           ;disable control characters
cd93: 80 0c                        bra     SETIT             ;by setting M.CTL2

cd95: a9 20        CTLON           lda     #M_CTL2           ;enable control characters
cd97: 80 02                        bra     CLRIT             ;by clearing M.CTL2

                   ; 
                   ; Enable mouse text by clearing M.MOUSE
                   ; 
cd99: a9 01        MOUSON          lda     #M_MOUSE
cd9b: 1c fb 04     CLRIT           trb     VMODE
cd9e: 60                           rts

                   ; 
                   ; Disable mouse text by setting M.MOUSE
                   ; 
cd9f: a9 01        MOUSOFF         lda     #M_MOUSE
cda1: 0c fb 04     SETIT           tsb     VMODE
cda4: 60                           rts

                   ; 
                   ; EXECUTE HOME:
                   ; 
cda5: 20 e9 fe     HOMECUR         jsr     CLRCH             ;move cursors to far left
cda8: a8                           tay                       ;(probably not needed)
cda9: a5 22                        lda     WNDTOP            ;and to top of window
cdab: 85 25                        sta     CV
cdad: 4c 88 fc                     jmp     NEWVTABZ          ;then set base address, OURCV

                   ; 
                   ; EXECUTE "NORMAL VIDEO"
                   ; 
cdb0: 20 84 fe     X_SO            jsr     SETNORM           ;set INVFLG to $FF
cdb3: a9 04                        lda     #M_VMODE          ;then clear inverse mode bit
cdb5: 80 e4                        bra     CLRIT

                   ; 
                   ; EXECUTE "INVERSE VIDEO"
                   ; 
cdb7: 20 80 fe     X_SI            jsr     SETINV            ;set INVFLG to $3F
cdba: a9 04                        lda     #M_VMODE          ;then set inverse mode bit
cdbc: 80 e3                        bra     SETIT

                   ; 
                   ; EXECUTE '40COL MODE' or '80COL MODE':
                   ; 
cdbe: 38           SET80           sec                       ;flag an 80 column window
cdbf: 90                           .dd1    $90               ;BCC opcode (never taken)
cdc0: 18           SET40           clc                       ;flag a 40 column window
cdc1: 2c fb 04                     bit     VMODE             ;but...it is pascal?
cdc4: 10 54                        bpl     SETX              ;=>yes, don't execute
cdc6: 08                           php                       ;save window size
cdc7: 20 1b ce                     jsr     HOOKITUP          ;COPYROM if needed, set I/O hooks
cdca: 28                           plp                       ;and get 40/80
cdcb: 80 08                        bra     WIN0              ;=>set window

                   ; 
                   ; CHK80 is called by PR#0 to convert to 40 if it was
                   ; 80. Otherwise the window is left ajar.
                   ; 
cdcd: 2c 1f c0     CHK80           bit     RD80VID           ;don't set 40 if
cdd0: 10 48                        bpl     SETX              ;already 40
                   ; 
cdd2: 18           WIN40           clc                       ;flag 40 column window
cdd3: b0                           .dd1    $b0               ;BCS opcode (never taken)
cdd4: 38           WIN80           sec                       ;flag 80 column window
cdd5: 64 22        WIN0            stz     WNDTOP            ;set window top now
cdd7: 2c 1a c0                     bit     RDTEXT            ;for text or mixed
cdda: 30 04                        bmi     WIN1              ;=>text
cddc: a9 14                        lda     #20
cdde: 85 22                        sta     WNDTOP            ;used by 80<->40 conversion
cde0: 2c 1f c0     WIN1            bit     RD80VID           ;80 columns now?
cde3: 08                           php                       ;save 80 or 40
cde4: b0 07                        bcs     WIN2              ;=>80: convert if 40
cde6: 10 0a                        bpl     WIN3              ;=>40: no convert
cde8: 20 53 ce                     jsr     SCRN84            ;80: convert to 40
cdeb: 80 05                        bra     WIN3              ;done converting

cded: 30 03        WIN2            bmi     WIN3              ;=>80: no convert
cdef: 20 80 ce                     jsr     SCRN48            ;40: convert to 80
cdf2: 20 9d cc     WIN3            jsr     GETCUR            ;determine absolute CH
cdf5: 98                           tya                       ;in case the window setting
cdf6: 18                           clc                       ;was different
cdf7: 65 20                        adc     WNDLFT
cdf9: 28                           plp                       ;pin to right edge if
cdfa: b0 06                        bcs     WIN4              ;80 to 40 leaves cursor
cdfc: c9 28                        cmp     #40               ;off the screen
cdfe: 90 02                        bcc     WIN4
ce00: a9 27                        lda     #39
ce02: 20 ec fe     WIN4            jsr     SETCUR            ;set new cursor
ce05: a5 25                        lda     CV                ;set new base address
ce07: 20 c1 fb                     jsr     BASCALC           ;for left = 0 (always)
                   ; 
ce0a: 64 20        WNDREST         stz     WNDLFT            ;Called by INIT and Pascal
ce0c: a9 18                        lda     #$18              ;and bottom
ce0e: 85 23                        sta     WNDBTM
ce10: a9 28                        lda     #$28              ;set left,width,bottom
ce12: 2c 1f c0                     bit     RD80VID           ;set width to 80 if 80 columns
ce15: 10 01                        bpl     WIN5
ce17: 0a                           asl     A
ce18: 85 21        WIN5            sta     WNDWDTH           ;set width
ce1a: 60           SETX            rts                       ;exit used by SET40/80

                   ; 
                   ; Turn on video firmware:
                   ; 
                   ; This routine is used by BASIC init, ESC-4, ESC-8
                   ; It copies the Monitor ROM to the language card
                   ; if necessary; it sets the input and output hooks to
                   ; $C30x; it sets all switches for video firmware operation
                   ; 
ce1b: 2c 7b 06     HOOKITUP        bit     VFACTV            ;don't touch hooks
ce1e: 10 11                        bpl     VIDMODE           ;if video firmware already active
ce20: 20 38 c3     HOOKUP          jsr     COPYROM           ;Copy ROM to LC?
ce23: a9 05        SETHOOKS        lda     #<C3KEYIN         ;set up $C300 hooks
ce25: 85 38                        sta     KSWL
ce27: a9 07                        lda     #<C3COUT1
ce29: 85 36                        sta     CSWL
ce2b: a9 c3                        lda     #>C3COUT1
ce2d: 85 39                        sta     KSWH
ce2f: 85 37                        sta     CSWH
                   ; 
                   ; Now set the video firmware active
                   ; 
ce31: 9c fb 07     VIDMODE         stz     CURSOR            ;set a solid inverse cursor
ce34: a9 08                        lda     #M_CTL            ;preserve M_CTL bit
ce36: 2d fb 04                     and     VMODE
ce39: 09 81                        ora     #$81              ;[#M.PASCAL+M.MOUSE] no pascal,mouse
                   ; 
                   ; Pascal calls here to set its mode
                   ; 
ce3b: 8d fb 04     PVMODE          sta     VMODE             ;set mode bits
ce3e: 9c 7b 06                     stz     VFACTV            ;say video firmware active
ce41: 8d 0f c0                     sta     SETALTCHAR        ;and set alternate char set
ce44: 60           QX              rts

ce45: 2c fb 04     QUIT            bit     VMODE             ;no quitting from pascal
ce48: 10 fa                        bpl     QX
ce4a: 20 d2 cd                     jsr     WIN40             ;first, do an escape 4
ce4d: 20 89 fe     ZZQUIT          jsr     SETKBD            ;do a IN#0 (used by COMM)
ce50: 4c 93 fe                     jmp     SETVID            ;and a PR#0

                   ; 
                   ; SCRN84 and SCRN48 convert screens between 40 & 80 cols.
                   ; WNDTOP must be set up to indicate the last line to
                   ; be done.  All registers are trashed
                   ; 
ce53: a2 17        SCRN84          ldx     #23               ;start at bottom of screen
ce55: 8d 01 c0                     sta     SET80COL          ;allow page 2 access
ce58: 8a           SCR1            txa                       ;calc base for line
ce59: 20 c1 fb                     jsr     BASCALC
ce5c: a0 27                        ldy     #39               ;start at right of screen
ce5e: 5a           SCR2            phy                       ;save 40 index
ce5f: 98                           tya                       ;div y 2 for 80 column index
ce60: 4a                           lsr     A
ce61: b0 03                        bcs     SCR3
ce63: 2c 55 c0                     bit     TXTPAGE2          ;even column, do page 2
ce66: a8           SCR3            tay                       ;get 80 index
ce67: b1 28                        lda     (BASL),y          ;get 80 char
ce69: 2c 54 c0                     bit     TXTPAGE1          ;restore page1
ce6c: 7a                           ply                       ;get 40 index
ce6d: 91 28                        sta     (BASL),y
ce6f: 88                           dey
ce70: 10 ec                        bpl     SCR2              ;do next 40 byte
ce72: ca                           dex                       ;do next line
ce73: 30 04                        bmi     SCR4              ;=>done with setup
ce75: e4 22                        cpx     WNDTOP            ;at top yet?
ce77: b0 df                        bcs     SCR1
ce79: 8d 00 c0     SCR4            sta     CLR80COL          ;clear 80STORE for 40 columns
ce7c: 8d 0c c0                     sta     CLR80VID          ;clear 80VID for 40 columns
ce7f: 60                           rts

ce80: a2 17        SCRN48          ldx     #23               ;start at bottom of screen
ce82: 8a           SCR5            txa                       ;set base for current line
ce83: 20 c1 fb                     jsr     BASCALC
ce86: a0 00                        ldy     #0                ;start at left of screen
ce88: 8d 01 c0                     sta     SET80COL          ;enable page2 store
ce8b: b1 28        SCR6            lda     (BASL),y          ;get 40 column char
ce8d: 5a           SCR8            phy                       ;save 40 column index
ce8e: 48                           pha                       ;save char
ce8f: 98                           tya                       ;div 2 for 80 column index
ce90: 4a                           lsr     A
ce91: b0 03                        bcs     SCR7              ;save on page1
ce93: 8d 55 c0                     sta     TXTPAGE2
ce96: a8           SCR7            tay                       ;get 80 column index
ce97: 68                           pla                       ;now save character
ce98: 91 28                        sta     (BASL),y
ce9a: 8d 54 c0                     sta     TXTPAGE1          ;flip page1
ce9d: 7a                           ply                       ;restore 40 column index
ce9e: c8                           iny                       ;move to the right
ce9f: c0 28                        cpy     #40               ;at right yet?
cea1: 90 e8                        bcc     SCR6              ;=>no, do next column
cea3: 20 cf cb                     jsr     CLRHALF           ;clear half of screen
cea6: ca                           dex                       ;else do next line of screen
cea7: 30 04                        bmi     SCR9              ;=>done with top line
cea9: e4 22                        cpx     WNDTOP            ;at top yet?
ceab: b0 d5                        bcs     SCR5
cead: 8d 0d c0     SCR9            sta     SET80VID          ;convert to 80 columns
ceb0: 60                           rts

                   NOTE: file PASCAL
ceb1: aa           PSTATUS         tax                       ;is request code=0?
ceb2: f0 08                        beq     PIORDY            ;=>yes, ready for output
ceb4: ca                           dex                       ;check for any input
ceb5: d0 07                        bne     PSTERR            ;=>bad request, return error
ceb7: 20 ad c9                     jsr     XBITKBD           ;test keyboard
ceba: 10 04                        bpl     PNOTRDY           ;=>no keystroked
cebc: 38           PIORDY          sec                       ;good return
cebd: 60                           rts

cebe: a2 03        PSTERR          ldx     #3                ;else flag error
cec0: 18           PNOTRDY         clc
cec1: 60                           rts

                   ; 
                   ; PASCAL OUTPUT:
                   ; 
cec2: 09 80        PWRITE          ora     #$80              ;turn on high bit
cec4: aa                           tax                       ;save character
cec5: 20 54 cf                     jsr     PSETUP2           ;SETUP ZP STUFF, don't set ROM
cec8: a9 08                        lda     #M_GOXY           ;ARE WE DOING GOTOXY?
ceca: 2c fb 04                     bit     VMODE
cecd: d0 2b                        bne     GETX              ;=>Doing X or Y?
cecf: 8a                           txa                       ;now check for control char
ced0: 89 60                        bit     #$60              ;is it control?
ced2: f0 45                        beq     PCTL              ;=>yes, do control
ced4: ac 7b 05                     ldy     OURCH             ;get horizontal position
ced7: 24 32                        bit     INVFLG            ;check for inverse
ced9: 30 02                        bmi     PWR1              ;normal, go store it
cedb: 29 7f                        and     #$7f
cedd: 20 c1 c3     PWR1            jsr     STORE             ;now store it (erasing cursor)
cee0: c8                           iny                       ;INC CH
cee1: 8c 7b 05                     sty     OURCH
cee4: c4 21                        cpy     WNDWDTH
cee6: 90 0c                        bcc     PWRET
cee8: 20 60 c3                     jsr     SETROM
ceeb: 20 e9 fe                     jsr     CLRCH             ;set cursor position to 0
ceee: 20 66 fc                     jsr     LF
cef1: 20 54 c3     PWRITERET       jsr     RESETLC
cef4: 20 0b cc     PWRET           jsr     PASINVERT         ;display new cursor
cef7: a2 00        PRET            ldx     #$00              ;return with no error
cef9: 60                           rts

                   ; 
                   ; HANDLE GOTOXY STUFF:
                   ; 
cefa: 20 0b cc     GETX            jsr     PASINVERT         ;turn off cursor
cefd: 8a                           txa                       ;get character
cefe: 38                           sec
ceff: e9 a0                        sbc     #160              ;MAKE BINARY
cf01: 2c fb 06                     bit     XCOORD            ;doing X?
cf04: 30 2a                        bmi     PSETX             ;=>yes, set it
                   ; 
                   ; Set Y and do the GOTOXY
                   ; 
cf06: 8d fb 05     GETY            sta     OURCV
cf09: 20 71 cf                     jsr     PASCALC           ;calc base addr
cf0c: ac fb 06                     ldy     XCOORD
cf0f: 20 ad cc                     jsr     GETCUR2           ;set proper cursors
cf12: a9 08                        lda     #M_GOXY           ;turn off gotoxy
cf14: 1c fb 04                     trb     VMODE
cf17: 80 db                        bra     PWRET             ;=>DONE (ALWAYS TAKEN)

cf19: 20 0b cc     PCTL            jsr     PASINVERT         ;turn off cursor
cf1c: 8a                           txa                       ;get char
cf1d: c9 9e                        cmp     #$9e              ;is it gotoXY?
cf1f: f0 08                        beq     STARTXY           ;=>yes, start it up
cf21: 20 60 c3                     jsr     SETROM            ;must switch in ROM for controls
cf24: 20 58 cd                     jsr     CTLCHAR           ;EXECUTE IT IF POSSIBLE
cf27: 80 c8                        bra     PWRITERET         ;=>display new cursor, exit

                   ; 
                   ; START THE GOTOXY SEQUENCE:
                   ; 
cf29: a9 08        STARTXY         lda     #M_GOXY
cf2b: 0c fb 04                     tsb     VMODE             ;turn on gotoxy
cf2e: a9 ff                        lda     #$ff              ;set XCOORD to -1
cf30: 8d fb 06     PSETX           sta     XCOORD            ;set X
cf33: 80 bf                        bra     PWRET             ;=>display cursor and exit

                   ; 
                   ; PASCAL INPUT:
                   ; 
cf35: 20 54 cf     PASREAD         jsr     PSETUP2           ;SETUP ZP STUFF
cf38: 20 8f c9     GKEY            jsr     XRDKBD            ;key pressed?
cf3b: 10 fb                        bpl     GKEY              ;=>not yet
cf3d: 29 7f                        and     #$7f              ;DROP HI BIT
cf3f: 80 b6                        bra     PRET              ;good exit

                   ; 
                   ; PASCAL INITIALIZATION:
                   ; 
cf41: a9 01        PINIT           lda     #M_MOUSE          ;Set mode to pascal
cf43: 20 3b ce                     jsr     PVMODE            ;without mouse characters
cf46: 20 51 cf                     jsr     PSETUP            ;setup zero page for pascal
cf49: 20 d4 cd                     jsr     WIN80             ;do 40->80 convert
cf4c: 20 58 fc                     jsr     HOME              ;home and clear screen
cf4f: 80 a0                        bra     PWRITERET         ;display cursor, set OURCH,OURCV...

cf51: 20 60 c3     PSETUP          jsr     SETROM            ;save LC state, set ROM read
cf54: 64 22        PSETUP2         stz     WNDTOP            ;set top to 0
cf56: 20 0a ce                     jsr     WNDREST           ;init either 40 or 80 window
cf59: a9 ff                        lda     #$ff              ;assume normal text
cf5b: 85 32                        sta     INVFLG
cf5d: a9 04                        lda     #M_VMODE          ;is it
cf5f: 2c fb 04                     bit     VMODE
cf62: f0 02                        beq     PS1               ;=>yes
cf64: 46 32                        lsr     INVFLG            ;no, make flag inverse
cf66: ac 7b 05     PS1             ldy     OURCH
cf69: 20 ad cc                     jsr     GETCUR2           ;set all cursors
cf6c: ad fb 05                     lda     OURCV
cf6f: 85 25                        sta     CV
                   ; 
                   ; Put BASCALC here so we don't have to switch
                   ; in the ROMs for each character output.
                   ; 
cf71: 0a           PASCALC         asl     A
cf72: a8                           tay                       ;calc base addr in BASL,H
cf73: 4a                           lsr     A                 ;for given line no.
cf74: 4a                           lsr     A
cf75: 29 03                        and     #$03              ; 0<=line no.<=$17
cf77: 09 04                        ora     #4                ; arg=000ABCDE, generate
cf79: 85 29                        sta     BASH              ; BASH=000001CD
cf7b: 98                           tya                       ;and
cf7c: 6a                           ror     A                 ; BASL=EABAB000
cf7d: 29 98                        and     #$98
cf7f: 85 28        PASCLC2         sta     BASL
cf81: 0a                           asl     A
cf82: 0a                           asl     A
cf83: 04 28                        tsb     BASL
cf85: 60                           rts

                   NOTE: file AUXSTUFF
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ; NAME    : MOVEAUX                                                            ;
                   ; FUNCTION: PERFORM CROSSBANK MEMORY MOVE                                      ;
                   ; INPUT   : A1=SOURCE ADDRESS                                                  ;
                   ;         : A2=SOURCE END                                                      ;
                   ;         : A4=DESTINATION START                                               ;
                   ;         : CARRY SET=MAIN-->CARD                                              ;
                   ;         :       CLR=CARD-->MAIN                                              ;
                   ; OUTPUT  : NONE                                                               ;
                   ; VOLATILE: NOTHING                                                            ;
                   ; CALLS   : NOTHING                                                            ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
cf86: 48           MOVEAUX         pha                       ;SAVE AC
cf87: ad 13 c0                     lda     RDRAMRD           ;SAVE STATE OF
cf8a: 48                           pha                       ; MEMORY FLAGS
cf8b: ad 14 c0                     lda     RDRAMWRT
cf8e: 48                           pha
                   ; 
                   ; SET FLAGS FOR CROSSBANK MOVE:
                   ; 
cf8f: 90 08                        bcc     MOVEC2M           ;=>CARD-->MAIN
cf91: 8d 02 c0                     sta     RDMAINRAM         ;SET FOR MAIN
cf94: 8d 05 c0                     sta     WRCARDRAM         ; TO CARD
cf97: b0 06                        bcs     MOVELOOP          ;=>(ALWAYS TAKEN)

cf99: 8d 04 c0     MOVEC2M         sta     WRMAINRAM         ;SET FOR CARD
cf9c: 8d 03 c0                     sta     RDCARDRAM         ; TO MAIN
                   ; 
cf9f: b2 3c        MOVELOOP        lda     (A1L)             ;get a byte
cfa1: 92 42                        sta     (A4L)             ;move it
cfa3: e6 42                        inc     A4L
cfa5: d0 02                        bne     NEXTA1
cfa7: e6 43                        inc     A4H
cfa9: a5 3c        NEXTA1          lda     A1L
cfab: c5 3e                        cmp     A2L
cfad: a5 3d                        lda     A1H
cfaf: e5 3f                        sbc     A2H
cfb1: e6 3c                        inc     A1L
cfb3: d0 02                        bne     GO1
cfb5: e6 3d                        inc     A1H
cfb7: 90 e6        GO1             bcc     MOVELOOP          ;->more to move
                   ; 
cfb9: 8d 04 c0                     sta     WRMAINRAM         ;CLEAR FLAG2
cfbc: 68                           pla                       ;GET ORIGINAL STATE
cfbd: 10 03                        bpl     GO3               ;=>IT WAS OFF
cfbf: 8d 05 c0                     sta     WRCARDRAM
cfc2: 8d 02 c0     GO3             sta     RDMAINRAM         ;CLEAR FLAG1
cfc5: 68                           pla                       ;GET ORIGINAL STATE
cfc6: 10 03                        bpl     MOVERET           ;=>IT WAS OFF
cfc8: 8d 03 c0                     sta     RDCARDRAM
cfcb: 68           MOVERET         pla                       ;Restore AC
cfcc: 60                           rts

                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
                   ; NAME    : XFER                                                               ;
                   ; FUNCTION: TRANSFER CONTROL CROSSBANK                                         ;
                   ; INPUT   : $03ED-TRANSFER ADDR                                                ;
                   ;         : CARRY SET=XFER TO CARD                                             ;
                   ;         :       CLR=XFER TO MAIN                                             ;
                   ;         : VFLAG CLR=USE STD ZP/STK                                           ;
                   ;         :       SET=USE ALT ZP/STK                                           ;
                   ; OUTPUT  : NONE                                                               ;
                   ; VOLATILE: $03ED/03EE IN DEST BANK                                            ;
                   ; CALLS   : NOTHING                                                            ;
                   ; NOTE    : ENTERED VIA JMP, NOT JSR                                           ;
                   ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
cfcd: 48           XFER            pha                       ;SAVE AC ON CURRENT STACK
                   ; 
                   ; COPY DESTINATION ADDRESS TO THE
                   ;  OTHER BANK SO THAT WE HAVE IT
                   ;  IN CASE WE DO A SWAP:
                   ; 
cfce: ad ed 03                     lda     $03ed             ;GET XFERADDR LO
cfd1: 48                           pha                       ;SAVE ON CURRENT STACK
cfd2: ad ee 03                     lda     $03ee             ;GET XFERADDR HI
cfd5: 48                           pha                       ;SAVE IT TOO
                   ; 
                   ; SWITCH TO APPROPRIATE BANK:
                   ; 
cfd6: 90 08                        bcc     XFERC2M           ;=>CARD-->MAIN
cfd8: 8d 03 c0                     sta     RDCARDRAM         ;SET FOR RUNNING
cfdb: 8d 05 c0                     sta     WRCARDRAM         ; IN CARD RAM
cfde: b0 06                        bcs     XFERZP            ;=>always taken

cfe0: 8d 02 c0     XFERC2M         sta     RDMAINRAM         ;SET FOR RUNNING
cfe3: 8d 04 c0                     sta     WRMAINRAM         ; IN MAIN RAM
                   ; SWITCH TO ALT ZP/STK
cfe6: 68           XFERZP          pla                       ;STUFF XFERADDR
cfe7: 8d ee 03                     sta     $03ee             ; HI AND
cfea: 68                           pla
cfeb: 8d ed 03                     sta     $03ed             ;  LO
cfee: 68                           pla                       ;RESTORE AC
cfef: 70 05                        bvs     XFERAZP           ;=>switch in alternate zp
cff1: 8d 08 c0                     sta     SETSTDZP          ;else force standard zp
cff4: 50 03                        bvc     JMPDEST           ;=>always perform transfer

cff6: 8d 09 c0     XFERAZP         sta     SETALTZP          ;switch in alternate zp
cff9: 6c ed 03     JMPDEST         jmp     ($03ed)           ;=>off we go

cffc: 00 00 00 67                  .align  $1000 (4 bytes)
                   NOTE: (Applesoft BASIC)
                   ; 
                   ; Applesoft BASIC starts here.
                   ; 
                   ; For brevity, the disassembly is not shown.  The address region is marked
                   ; isolated so that attempts to reference inside it aren't resolved.
                   ; 
                                   .addrs  $d000             ;[!in]
d000: 6f d8 65 d7+                 .junk   10240
                                   .adrend ↑ $d000

                   NOTE: file AUTOST1
                   ; 
                   ; F8 Monitor ROM
                   ; 
f800: 4a           PLOT            lsr     A                 ;Y-COORD/2
f801: 08                           php                       ;SAVE LSB IN CARRY
f802: 20 47 f8                     jsr     GBASCALC          ;CALC BASE FOR ADR IN GBASL,H
f805: 28                           plp                       ;RESTORE LSB FROM CARRY
f806: a9 0f                        lda     #$0f              ;MASK $0F IF EVEN
f808: 90 02                        bcc     RTMASK
f80a: 69 e0                        adc     #$e0              ;MASK $F0 IF ODD
f80c: 85 2e        RTMASK          sta     MASK
f80e: b1 26        PLOT1           lda     (GBASL),y         ;DATA
f810: 45 30                        eor     COLOR             ; XOR COLOR
f812: 25 2e                        and     MASK              ;  AND MASK
f814: 51 26                        eor     (GBASL),y         ;   XOR DATA
f816: 91 26                        sta     (GBASL),y         ;    TO DATA
f818: 60                           rts

f819: 20 00 f8     HLINE           jsr     PLOT              ;PLOT SQUARE
f81c: c4 2c        HLINE1          cpy     H2                ;DONE?
f81e: b0 11                        bcs     RTS1              ; YES, RETURN
f820: c8                           iny                       ; NO, INCR INDEX (X-COORD)
f821: 20 0e f8                     jsr     PLOT1             ;PLOT NEXT SQUARE
f824: 90 f6                        bcc     HLINE1            ;ALWAYS TAKEN
f826: 69 01        VLINEZ          adc     #$01              ;NEXT Y-COORD
f828: 48           VLINE           pha                       ; SAVE ON STACK
f829: 20 00 f8                     jsr     PLOT              ; PLOT SQUARE
f82c: 68                           pla
f82d: c5 2d                        cmp     V2                ;DONE?
f82f: 90 f5                        bcc     VLINEZ            ; NO, LOOP.
f831: 60           RTS1            rts

f832: a0 2f        CLRSCR          ldy     #$2f              ;MAX Y, FULL SCRN CLR
f834: d0 02                        bne     CLRSC2            ;ALWAYS TAKEN

f836: a0 27        CLRTOP          ldy     #$27              ;MAX Y, TOP SCRN CLR
f838: 84 2d        CLRSC2          sty     V2                ;STORE AS BOTTOM COORD FOR VLINE CALLS
f83a: a0 27                        ldy     #$27              ;RIGHTMOST X-COORD (COLUMN)
f83c: a9 00        CLRSC3          lda     #$00              ;TOP COORD FOR VLINE CALLS
f83e: 85 30                        sta     COLOR             ;CLEAR COLOR (BLACK)
f840: 20 28 f8                     jsr     VLINE             ;DRAW VLINE
f843: 88                           dey                       ;NEXT LEFTMOST X-COORD
f844: 10 f6                        bpl     CLRSC3            ;LOOP UNITL DONE.
f846: 60                           rts

f847: 48           GBASCALC        pha                       ;FOR INPUT  00DEFGH
f848: 4a                           lsr     A
f849: 29 03                        and     #$03
f84b: 09 04                        ora     #$04              ;GENERATE GBASH=000001FG
f84d: 85 27                        sta     GBASH
f84f: 68                           pla                       ;AND GBASL=HDEDE000
f850: 29 18                        and     #$18
f852: 90 02                        bcc     GBCALC
f854: 69 7f                        adc     #$7f
f856: 85 26        GBCALC          sta     GBASL
f858: 0a                           asl     A
f859: 0a                           asl     A
f85a: 05 26                        ora     GBASL
f85c: 85 26                        sta     GBASL
f85e: 60                           rts

f85f: a5 30        NXTCOL          lda     COLOR             ;INCREMENT COLOR BY 3
f861: 18                           clc
f862: 69 03                        adc     #$03
f864: 29 0f        SETCOL          and     #$0f              ;SETS COLOR=17*A MOD 16
f866: 85 30                        sta     COLOR
f868: 0a                           asl     A                 ;BOTH HALF BYTES OF COLOR EQUAL
f869: 0a                           asl     A
f86a: 0a                           asl     A
f86b: 0a                           asl     A
f86c: 05 30                        ora     COLOR
f86e: 85 30                        sta     COLOR
f870: 60                           rts

f871: 4a           SCRN            lsr     A                 ;READ SCREEN Y-COORD/2
f872: 08                           php                       ;SAVE LSB (CARRY)
f873: 20 47 f8                     jsr     GBASCALC          ;CALC BASE ADDRESS
f876: b1 26                        lda     (GBASL),y         ;GET BYTE
f878: 28                           plp                       ;RESTORE LSB FROM CARRY
f879: 90 04        SCRN2           bcc     RTMSKZ            ;IF EVEN, USE LO H
f87b: 4a                           lsr     A
f87c: 4a                           lsr     A
f87d: 4a                           lsr     A                 ;SHIFT HIGH HALF BYTE DOWN
f87e: 4a                           lsr     A
f87f: 29 0f        RTMSKZ          and     #$0f              ;MASK 4-BITS
f881: 60                           rts

f882: a6 3a        INSDS1          ldx     PCL               ;PRINT PCL,H
f884: a4 3b                        ldy     PCH
f886: 20 96 fd                     jsr     PRYX2
f889: 20 48 f9                     jsr     PRBLNK            ;FOLLOWED BY A BLANK
f88c: a1 3a        INSDS2          lda     (PCL,x)           ;GET OPCODE
f88e: a8                           tay
f88f: 4a                           lsr     A                 ;EVEN/ODD TEST
f890: 90 05                        bcc     IEVEN
f892: 6a                           ror     A                 ;BIT 1 TEST
f893: b0 0c                        bcs     ERR               ;XXXXXX11 INVALID OP
f895: 29 87                        and     #$87              ;MASK BITS
f897: 4a           IEVEN           lsr     A                 ;LSB INTO CARRY FOR L/R TEST
f898: aa                           tax
f899: bd 62 f9                     lda     FMT1,x            ;GET FORMAT INDEX BYTE
f89c: 20 79 f8                     jsr     SCRN2             ;R/L H-BYTE ON CARRY
f89f: d0 04                        bne     GETFMT
f8a1: a0 fc        ERR             ldy     #$fc              ;SUBSTITUTE $FC FOR INVALID OPS
f8a3: a9 00                        lda     #$00              ;SET PRINT FORMAT INDEX TO 0
f8a5: aa           GETFMT          tax
f8a6: bd a6 f9                     lda     FMT2,x            ;INDEX INTO PRINT FORMAT TABLE
f8a9: 85 2e                        sta     FORMAT            ;SAVE FOR ADR FIELD FORMATTING
f8ab: 29 03                        and     #$03              ;MASK FOR 2-BIT LENGTH
                   ; (0=1 BYTE, 1=2 BYTE, 2=3 BYTE)
f8ad: 85 2f                        sta     LENGTH
f8af: 20 35 fc                     jsr     NEWOPS            ;get index for new opcodes
f8b2: f0 18                        beq     GOTONE            ;found a new op (or no op)
f8b4: 29 8f                        and     #$8f              ;MASK FOR 1XXX1010 TEST
f8b6: aa                           tax                       ; SAVE IT
f8b7: 98                           tya                       ;OPCODE TO A AGAIN
f8b8: a0 03                        ldy     #$03
f8ba: e0 8a                        cpx     #$8a
f8bc: f0 0b                        beq     MNNDX3
f8be: 4a           MNNDX1          lsr     A
f8bf: 90 08                        bcc     MNNDX3            ;FORM INDEX INTO MNEMONIC TABLE
f8c1: 4a                           lsr     A
f8c2: 4a           MNNDX2          lsr     A                 ;  1) 1XXX1010 => 00101XXX
f8c3: 09 20                        ora     #$20              ;  2) XXXYYY01 => 00111XXX
f8c5: 88                           dey                       ;  3) XXXYYY10 => 00110XXX
f8c6: d0 fa                        bne     MNNDX2            ;  4) XXXYY100 => 00100XXX
f8c8: c8                           iny                       ;  5) XXXXX000 => 000XXXXX
f8c9: 88           MNNDX3          dey
f8ca: d0 f2                        bne     MNNDX1
f8cc: 60           GOTONE          rts

f8cd: ff ff ff                     .bulk   $ff,$ff,$ff

f8d0: 20 82 f8     INSTDSP         jsr     INSDS1            ;GEN FMT, LEN BYTES
f8d3: 48                           pha                       ;SAVE MNEMONIC TABLE INDEX
f8d4: b1 3a        PRNTOP          lda     (PCL),y
f8d6: 20 da fd                     jsr     PRBYTE
f8d9: a2 01                        ldx     #$01              ;PRINT 2 BLANKS
f8db: 20 4a f9     PRNTBL          jsr     PRBL2
f8de: c4 2f                        cpy     LENGTH            ;PRINT INST (1-3 BYTES)
f8e0: c8                           iny                       ;IN A 12 CHR FIELD
f8e1: 90 f1                        bcc     PRNTOP
f8e3: a2 03                        ldx     #$03              ;CHAR COUNT FOR MNEMONIC INDEX
f8e5: c0 04                        cpy     #$04
f8e7: 90 f2                        bcc     PRNTBL
f8e9: 68                           pla                       ;RECOVER MNEMONIC INDEX
f8ea: a8                           tay
f8eb: b9 c0 f9                     lda     MNEML,y
f8ee: 85 2c                        sta     LMNEM             ;FETCH 3-CHAR MNEMONIC
f8f0: b9 00 fa                     lda     MNEMR,y           ;  (PACKED INTO 2-BYTES)
f8f3: 85 2d                        sta     RMNEM
f8f5: a9 00        PRMN1           lda     #$00
f8f7: a0 05                        ldy     #$05
f8f9: 06 2d        PRMN2           asl     RMNEM             ;SHIFT 5 BITS OF CHARACTER INTO A
f8fb: 26 2c                        rol     LMNEM
f8fd: 2a                           rol     A                 ;  (CLEARS CARRY)
f8fe: 88                           dey
f8ff: d0 f8                        bne     PRMN2
f901: 69 bf                        adc     #$bf              ;ADD "?" OFFSET
f903: 20 ed fd                     jsr     COUT              ;OUTPUT A CHAR OF MNEM
f906: ca                           dex
f907: d0 ec                        bne     PRMN1
f909: 20 48 f9                     jsr     PRBLNK            ;OUTPUT 3 BLANKS
f90c: a4 2f                        ldy     LENGTH
f90e: a2 06                        ldx     #$06              ;CNT FOR 6 FORMAT BITS
f910: e0 03        PRADR1          cpx     #$03
f912: f0 1c                        beq     PRADR5            ;IF X=3 THEN ADDR.
f914: 06 2e        PRADR2          asl     FORMAT
f916: 90 0e                        bcc     PRADR3
f918: bd b9 f9                     lda     CHAR1-1,x
f91b: 20 ed fd                     jsr     COUT
f91e: bd b3 f9                     lda     CHAR2-1,x
f921: f0 03                        beq     PRADR3
f923: 20 ed fd                     jsr     COUT
f926: ca           PRADR3          dex
f927: d0 e7                        bne     PRADR1
f929: 60                           rts

f92a: 88           PRADR4          dey
f92b: 30 e7                        bmi     PRADR2
f92d: 20 da fd                     jsr     PRBYTE
f930: a5 2e        PRADR5          lda     MASK
f932: c9 e8                        cmp     #$e8              ;HANDLE REL ADR MODE
f934: b1 3a                        lda     (PCL),y           ;SPECIAL (PRINT TARGET,
f936: 90 f2                        bcc     PRADR4            ;  NOT OFFSET)
f938: 20 56 f9     RELADR          jsr     PCADJ3
f93b: aa                           tax                       ;PCL,PCH+OFFSET+1 TO A,Y
f93c: e8                           inx
f93d: d0 01                        bne     PRNTYX            ;+1 TO Y,X
f93f: c8                           iny
f940: 98           PRNTYX          tya
f941: 20 da fd     PRNTAX          jsr     PRBYTE            ;OUTPUT TARGET ADR
f944: 8a           PRNTX           txa                       ;  OF BRANCH AND RETURN
f945: 4c da fd                     jmp     PRBYTE

f948: a2 03        PRBLNK          ldx     #$03              ;BLANK COUNT
f94a: a9 a0        PRBL2           lda     #$a0              ;LOAD A SPACE
f94c: 20 ed fd     PRBL3           jsr     COUT              ;OUTPUT A BLANK
f94f: ca                           dex
f950: d0 f8                        bne     PRBL2             ;LOOP UNTIL COUNT=0
f952: 60                           rts

f953: 38           PCADJ           sec                       ;0=1 BYTE, 1=2 BYTE,
f954: a5 2f        PCADJ2          lda     LENGTH            ;  2=3 BYTE
f956: a4 3b        PCADJ3          ldy     PCH
f958: aa                           tax                       ;TEST DISPLACEMENT SIGN
f959: 10 01                        bpl     PCADJ4            ;  (FOR REL BRANCH)
f95b: 88                           dey                       ;EXTEND NEG BY DECR PCH
f95c: 65 3a        PCADJ4          adc     PCL
f95e: 90 01                        bcc     RTS2              ;PCL+LENGTH(OR DISPL)+1 TO A
f960: c8                           iny                       ;  CARRY INTO Y (PCH)
f961: 60           RTS2            rts

                   ; 
                   ; FMT1 BYTES:    XXXXXXY0 INSTRS
                   ; IF Y=0         THEN RIGHT HALF BYTE
                   ; IF Y=1         THEN LEFT HALF BYTE
                   ;                   (X=INDEX)
                   ; 
f962: 0f           FMT1            .dd1    $0f
f963: 22                           .dd1    $22
f964: ff                           .dd1    $ff
f965: 33                           .dd1    $33
f966: cb                           .dd1    $cb
f967: 62                           .dd1    $62
f968: ff                           .dd1    $ff
f969: 73                           .dd1    $73
f96a: 03                           .dd1    $03
f96b: 22                           .dd1    $22
f96c: ff                           .dd1    $ff
f96d: 33                           .dd1    $33
f96e: cb                           .dd1    $cb
f96f: 66                           .dd1    $66
f970: ff                           .dd1    $ff
f971: 77                           .dd1    $77
f972: 0f                           .dd1    $0f
f973: 20                           .dd1    $20
f974: ff                           .dd1    $ff
f975: 33                           .dd1    $33
f976: cb                           .dd1    $cb
f977: 60                           .dd1    $60
f978: ff                           .dd1    $ff
f979: 70                           .dd1    $70
f97a: 0f                           .dd1    $0f
f97b: 22                           .dd1    $22
f97c: ff                           .dd1    $ff
f97d: 39                           .dd1    $39
f97e: cb                           .dd1    $cb
f97f: 66                           .dd1    $66
f980: ff                           .dd1    $ff
f981: 7d                           .dd1    $7d
f982: 0b                           .dd1    $0b
f983: 22                           .dd1    $22
f984: ff                           .dd1    $ff
f985: 33                           .dd1    $33
f986: cb                           .dd1    $cb
f987: a6                           .dd1    $a6
f988: ff                           .dd1    $ff
f989: 73                           .dd1    $73
f98a: 11                           .dd1    $11
f98b: 22                           .dd1    $22
f98c: ff                           .dd1    $ff
f98d: 33                           .dd1    $33
f98e: cb                           .dd1    $cb
f98f: a6                           .dd1    $a6
f990: ff                           .dd1    $ff
f991: 87                           .dd1    $87
f992: 01                           .dd1    $01
f993: 22                           .dd1    $22
f994: ff                           .dd1    $ff
f995: 33                           .dd1    $33
f996: cb                           .dd1    $cb
f997: 60                           .dd1    $60
f998: ff                           .dd1    $ff
f999: 70                           .dd1    $70
f99a: 01                           .dd1    $01
f99b: 22                           .dd1    $22
f99c: ff                           .dd1    $ff
f99d: 33                           .dd1    $33
f99e: cb                           .dd1    $cb
f99f: 60                           .dd1    $60
f9a0: ff                           .dd1    $ff
f9a1: 70                           .dd1    $70
f9a2: 24                           .dd1    $24
f9a3: 31                           .dd1    $31
f9a4: 65                           .dd1    $65
f9a5: 78                           .dd1    $78
                   ; ZZXXXY01 INSTR'S
f9a6: 00           FMT2            .dd1    $00               ;ERR
f9a7: 21                           .dd1    $21               ;IMM
f9a8: 81                           .dd1    $81               ;Z-PAGE
f9a9: 82                           .dd1    $82               ;ABS
f9aa: 59                           .dd1    $59               ;(ZPAG,X)
f9ab: 4d                           .dd1    $4d               ;(ZPAG),Y
f9ac: 91                           .dd1    $91               ;ZPAG,X
f9ad: 92                           .dd1    $92               ;ABS,X
f9ae: 86                           .dd1    $86               ;ABS,Y
f9af: 4a                           .dd1    $4a               ;(ABS)
f9b0: 85                           .dd1    $85               ;ZPAG,Y
f9b1: 9d                           .dd1    $9d               ;RELATIVE
f9b2: 49                           .dd1    $49               ;(ZPAG)    (new)
f9b3: 5a                           .dd1    $5a               ;(ABS,X)   (new)
                   ; 
f9b4: d9           CHAR2           .dd1    $d9               ;'Y'
f9b5: 00                           .dd1    $00               ; (byte F of FMT2)
f9b6: d8                           .dd1    $d8               ;'Y'
f9b7: a4                           .dd1    $a4               ;'$'
f9b8: a4                           .dd1    $a4               ;'$'
f9b9: 00                           .dd1    $00
                   ; 
f9ba: ac           CHAR1           .dd1    $ac               ;'.'
f9bb: a9                           .dd1    $a9               ;')'
f9bc: ac                           .dd1    $ac               ;','
f9bd: a3                           .dd1    $a3               ;'#'
f9be: a8                           .dd1    $a8               ;'('
f9bf: a4                           .dd1    $a4               ;'$'
f9c0: 1c           MNEML           .dd1    $1c
f9c1: 8a                           .dd1    $8a
f9c2: 1c                           .dd1    $1c
f9c3: 23                           .dd1    $23
f9c4: 5d                           .dd1    $5d
f9c5: 8b                           .dd1    $8b
f9c6: 1b                           .dd1    $1b
f9c7: a1                           .dd1    $a1
f9c8: 9d                           .dd1    $9d
f9c9: 8a                           .dd1    $8a
f9ca: 1d                           .dd1    $1d
f9cb: 23                           .dd1    $23
f9cc: 9d                           .dd1    $9d
f9cd: 8b                           .dd1    $8b
f9ce: 1d                           .dd1    $1d
f9cf: a1                           .dd1    $a1
f9d0: 1c                           .dd1    $1c               ;BRA
f9d1: 29                           .dd1    $29
f9d2: 19                           .dd1    $19
f9d3: ae                           .dd1    $ae
f9d4: 69                           .dd1    $69
f9d5: a8                           .dd1    $a8
f9d6: 19                           .dd1    $19
f9d7: 23                           .dd1    $23
f9d8: 24                           .dd1    $24
f9d9: 53                           .dd1    $53
f9da: 1b                           .dd1    $1b
f9db: 23                           .dd1    $23
f9dc: 24                           .dd1    $24
f9dd: 53                           .dd1    $53
f9de: 19                           .dd1    $19
f9df: a1                           .dd1    $a1               ; (A) FORMAT ABOVE
f9e0: ad                           .dd1    $ad               ; TSB
f9e1: 1a                           .dd1    $1a
f9e2: 5b                           .dd1    $5b
f9e3: 5b                           .dd1    $5b
f9e4: a5                           .dd1    $a5
f9e5: 69                           .dd1    $69
f9e6: 24                           .dd1    $24
f9e7: 24                           .dd1    $24               ; (B) FORMAT
f9e8: ae                           .dd1    $ae
f9e9: ae                           .dd1    $ae
f9ea: a8                           .dd1    $a8
f9eb: ad                           .dd1    $ad
f9ec: 29                           .dd1    $29
f9ed: 8a                           .dd1    $8a
f9ee: 7c                           .dd1    $7c
f9ef: 8b                           .dd1    $8b               ; (C) FORMAT
f9f0: 15                           .dd1    $15
f9f1: 9c                           .dd1    $9c
f9f2: 6d                           .dd1    $6d
f9f3: 9c                           .dd1    $9c
f9f4: a5                           .dd1    $a5
f9f5: 69                           .dd1    $69
f9f6: 29                           .dd1    $29
f9f7: 53                           .dd1    $53               ; (D) FORMAT
f9f8: 84                           .dd1    $84
f9f9: 13                           .dd1    $13
f9fa: 34                           .dd1    $34
f9fb: 11                           .dd1    $11
f9fc: a5                           .dd1    $a5
f9fd: 69                           .dd1    $69
f9fe: 23                           .dd1    $23               ; (E) FORMAT
f9ff: a0                           .dd1    $a0
                   ; 
fa00: d8           MNEMR           .dd1    $d8
fa01: 62                           .dd1    $62
fa02: 5a                           .dd1    $5a
fa03: 48                           .dd1    $48
fa04: 26                           .dd1    $26
fa05: 62                           .dd1    $62
fa06: 94                           .dd1    $94
fa07: 88                           .dd1    $88
fa08: 54                           .dd1    $54
fa09: 44                           .dd1    $44
fa0a: c8                           .dd1    $c8
fa0b: 54                           .dd1    $54
fa0c: 68                           .dd1    $68
fa0d: 44                           .dd1    $44
fa0e: e8                           .dd1    $e8
fa0f: 94                           .dd1    $94
fa10: c4                           .dd1    $c4
fa11: b4                           .dd1    $b4
fa12: 08                           .dd1    $08
fa13: 84                           .dd1    $84
fa14: 74                           .dd1    $74
fa15: b4                           .dd1    $b4
fa16: 28                           .dd1    $28
fa17: 6e                           .dd1    $6e
fa18: 74                           .dd1    $74
fa19: f4                           .dd1    $f4
fa1a: cc                           .dd1    $cc
fa1b: 4a                           .dd1    $4a
fa1c: 72                           .dd1    $72
fa1d: f2                           .dd1    $f2
fa1e: a4                           .dd1    $a4
fa1f: 8a                           .dd1    $8a
fa20: 06                           .dd1    $06
fa21: aa                           .dd1    $aa
fa22: a2                           .dd1    $a2
fa23: a2                           .dd1    $a2
fa24: 74                           .dd1    $74
fa25: 74                           .dd1    $74
fa26: 74                           .dd1    $74
fa27: 72                           .dd1    $72
fa28: 44                           .dd1    $44
fa29: 68                           .dd1    $68
fa2a: b2                           .dd1    $b2
fa2b: 32                           .dd1    $32
fa2c: b2                           .dd1    $b2
fa2d: 72                           .dd1    $72
fa2e: 22                           .dd1    $22
fa2f: 72                           .dd1    $72
fa30: 1a                           .dd1    $1a
fa31: 1a                           .dd1    $1a
fa32: 26                           .dd1    $26
fa33: 26                           .dd1    $26
fa34: 72                           .dd1    $72
fa35: 72                           .dd1    $72
fa36: 88                           .dd1    $88
fa37: c8                           .dd1    $c8
fa38: c4                           .dd1    $c4
fa39: ca                           .dd1    $ca
fa3a: 26                           .dd1    $26
fa3b: 48                           .dd1    $48
fa3c: 44                           .dd1    $44
fa3d: 44                           .dd1    $44
fa3e: a2                           .dd1    $a2
fa3f: c8                           .dd1    $c8

fa40: 48           IRQ             pha                       ;save accumulator
fa41: 68                           pla                       ;rescued by stack trick later
fa42: 68                           pla
fa43: 4c 06 c8                     jmp     IRQ1              ;do rest of IRQ handler

fa46: ff                           .dd1    $ff               ;[appears as NOP $EA in listing]

                   ; 
                   ; NEWBRK is called by the interrupt handler which has
                   ; set the hardware to its default state and encoded
                   ; the state in the accumulator.  Software that wants
                   ; to do break processing using full system resources
                   ; can restore the machine state from this value.
                   ; 
fa47: 85 44        NEWBRK          sta     MACSTAT           ;save state of machine
fa49: 7a                           ply                       ;restore registers for save
fa4a: fa                           plx
fa4b: 68                           pla
                   ; 
fa4c: 28           BREAK           plp                       ;Note: same as old BREAK routine!!
fa4d: 20 4a ff                     jsr     SAVE              ;save reg's on BRK
fa50: 68                           pla                       ;including PC
fa51: 85 3a                        sta     PCL
fa53: 68                           pla
fa54: 85 3b                        sta     PCH
fa56: 6c f0 03                     jmp     (BRKV)            ;call BRK HANDLER

fa59: 20 82 f8     OLDBRK          jsr     INSDS1            ;PRINT USER PC
fa5c: 20 da fa                     jsr     RGDSP1            ;  AND REGS
fa5f: 4c 65 ff                     jmp     MON               ;GO TO MONITOR (NO PASS GO, NO $200!)

fa62: d8           RESET           cld                       ;DO THIS FIRST THIS TIME
fa63: 20 84 fe                     jsr     SETNORM
fa66: 20 2f fb                     jsr     INIT
fa69: 20 93 fe                     jsr     SETVID
fa6c: 20 89 fe                     jsr     SETKBD
fa6f: 20 1c c4                     jsr     initmouse         ;initialize the mouse
fa72: 20 04 cc                     jsr     CLRPORT           ;clear port setup bytes
fa75: 9c ff 04                     stz     aciabuf           ;and the commahead buffer
fa78: ad 5f c0                     lda     SETAN3            ; AN3 = TLL HI
fa7b: 20 bd fa                     jsr     RESET_X           ; initialize other devices
fa7e: 2c 10 c0                     bit     KBDSTRB           ; CLEAR KEYBOARD
fa81: d8           NEWMON          cld
fa82: 20 3a ff                     jsr     BELL              ; CAUSES DELAY IF KEY BOUNCES
fa85: ad f3 03                     lda     SOFTEV+1          ;IS RESET HI
fa88: 49 a5                        eor     #$a5              ;A FUNNY COMPLEMENT OF THE
fa8a: cd f4 03                     cmp     PWREDUP           ; PWR UP BYTE ???
fa8d: d0 17                        bne     PWRUP             ; NO SO PWRUP
fa8f: ad f2 03                     lda     SOFTEV            ; YES SEE IF COLD START
fa92: d0 3b                        bne     NOFIX             ; HAS BEEN DONE YET?
fa94: a9 e0                        lda     #$e0              ; DOES SEV POINT AT BASIC?
fa96: cd f3 03                     cmp     SOFTEV+1
fa99: d0 34                        bne     NOFIX             ; YES SO REENTER SYSTEM
fa9b: a0 03        FIXSEV          ldy     #3                ; NO SO POINT AT WARM START
fa9d: 8c f2 03                     sty     SOFTEV            ; FOR NEXT RESET
faa0: 4c 00 e0                     jmp     BASIC             ; AND DO THE COLD START

faa3: 20 3a ff     BEEPFIX         jsr     BELL              ;Beep on powerup
                   ; 
faa6: 20 ca fc     PWRUP           jsr     COLDSTART         ;Trash memory, init ports
faa9: a2 05                        ldx     #5                ; SET PAGE 3 VECTORS
faab: bd fc fa     SETPLP          lda     PWRCON-1,x        ; WITH CNTRL B ADRS
faae: 9d ef 03                     sta     BRKV-1,x          ; OF CURRENT BASIC
fab1: ca                           dex
fab2: d0 f7                        bne     SETPLP
fab4: a9 c6                        lda     #$c6              ; LOAD HI SLOT +1
fab6: 80 5a                        bra     PWRUP2            ;branch around mnemonics

                   ; 
                   ; Extension to MNEML (left mnemonics)
                   ; 
fab8: 8a                           .dd1    $8a               ;PHY
fab9: 8b                           .dd1    $8b               ;PLY
faba: a5                           .dd1    $a5               ;STZ
fabb: ac                           .dd1    $ac               ;TRB
fabc: 00                           .dd1    $00               ;???

                   ; 
                   ; This extension to the monitor reset routine ($FA62)
                   ; checks for apple keys.  If both are pressed, it goes
                   ; into an exerciser mode.  If the open apple key only is
                   ; pressed, memory is selectively trashed and a cold start
                   ; is done.
                   ; 
fabd: a9 ff        RESET_X         lda     #$ff
fabf: 8d fb 04                     sta     VMODE             ;initialize mode
fac2: 0e 62 c0                     asl     BUTN1
fac5: 2c 61 c0                     bit     BUTN0
fac8: 10 64                        bpl     RTS2D
faca: 90 d7                        bcc     BEEPFIX           ;open apple only, reboot
facc: 4c 7c c7                     jmp     BANGER            ;both apples, exercise 'er

facf: 6c f2 03     NOFIX           jmp     (SOFTEV)

fad2: c1 d8 d9 d0+ RTBL            .str    “AXYPS”

fad7: 20 8e fd     REGDSP          jsr     CROUT             ;DISPLAY USER REG CONTENTS
fada: a9 45        RGDSP1          lda     #$45              ;WITH LABELS
fadc: 85 40                        sta     A3L
fade: a9 00                        lda     #$00
fae0: 85 41                        sta     A3H
fae2: a2 fb                        ldx     #$fb
fae4: a9 a0        RDSP1           lda     #$a0
fae6: 20 ed fd                     jsr     COUT
fae9: bd d7 f9                     lda     RTBL-251,x
faec: 20 ed fd                     jsr     COUT
faef: a9 bd                        lda     #$bd
faf1: 20 ed fd                     jsr     COUT
faf4: b5 4a                        lda     ACC+5,x
faf6: 80 0a                        bra     RGDSP2            ;make room for mnemonics

faf8: 74                           .dd1    $74               ;PHY
faf9: 74                           .dd1    $74               ;PLY
fafa: 76                           .dd1    $76               ;STZ
fafb: c6                           .dd1    $c6               ;TRB
fafc: 00                           .dd1    $00               ;???

fafd: 59 fa        PWRCON          .dd2    OLDBRK
faff: 00 e0 45                     .bulk   $00,$e0,$45

fb02: 20 da fd     RGDSP2          jsr     PRBYTE
fb05: e8                           inx
fb06: 30 dc                        bmi     RDSP1
fb08: 60                           rts

fb09: c1 f0 f0 ec+                 .str    “Apple ][”
fb11: c4                           .dd1    $c4               ;optional filler

fb12: 86 00        PWRUP2          stx     LOC0              ; SETPG3 MUST RETURN X=0
fb14: 85 01                        sta     LOC1              ; SET PTR H
fb16: 20 60 fb                     jsr     APPLEII           ;Display our banner...
fb19: 6c 00 00                     jmp     (LOC0)            ;JUMP $C600

fb1c: ff                           .dd1    $ff               ;[BRK $00]
fb1d: ff                           .dd1    $ff               ;[BRK $00]

fb1e: 4c de c7     PREAD           jmp     MPADDLE           ;read mouse paddle

fb21: a0 00        PREAD4          ldy     #$00              ;INIT COUNT
fb23: ea                           nop                       ;COMPENSATE FOR 1ST COUNT
fb24: ea                           nop
fb25: bd 64 c0     PREAD2          lda     PADDL0,x          ;COUNT Y-REG EVERY 12 USEC.
fb28: 10 04                        bpl     RTS2D
fb2a: c8                           iny
fb2b: d0 f8                        bne     PREAD2            ;EXIT AT 255 MAX
fb2d: 88                           dey
fb2e: 60           RTS2D           rts

                   NOTE: file AUTOST2
fb2f: a9 00        INIT            lda     #$00              ;CLR STATUS FOR DEBUG SOFTWARE
fb31: 85 48                        sta     STATUS
fb33: ad 56 c0                     lda     LORES
fb36: ad 54 c0                     lda     TXTPAGE1          ;INIT VIDEO MODE
fb39: ad 51 c0     SETTXT          lda     TXTSET            ;SET FOR TEXT MODE
fb3c: a9 00                        lda     #$00              ;FULL SCREEN WINDOW
fb3e: f0 0b                        beq     SETWND

fb40: ad 50 c0     SETGR           lda     TXTCLR            ;SET FOR GRAPHICS MODE
fb43: ad 53 c0                     lda     MIXSET            ;LOWER 4 LINES AS TEXT WINDOW
fb46: 20 36 f8                     jsr     CLRTOP
fb49: a9 14                        lda     #$14
fb4b: 85 22        SETWND          sta     WNDTOP            ;SET WINDOW
fb4d: ea                           nop
fb4e: ea                           nop
fb4f: 20 0a ce                     jsr     WNDREST           ;40/80 column width
fb52: 80 05                        bra     VTASB23

fb54: 09 80        DOCTL           ora     #$80              ;controls need high bit
fb56: 4c 54 cd                     jmp     CTLCHAR0          ;execute control char

fb59: a9 17        VTASB23         lda     #$17              ;VTAB TO ROW 23
fb5b: 85 25        TABV            sta     CV                ;VTABS TO ROW IN A-REG
fb5d: 4c 22 fc                     jmp     VTAB              ;don't set OURCV!!

fb60: 20 58 fc     APPLEII         jsr     HOME              ;CLEAR THE SCRN
fb63: a0 09                        ldy     #$09
fb65: b9 02 fd     STITLE          lda     APPLE2C-1,y       ;GET A CHAR
fb68: 99 0d 04                     sta     LINE1+13,y        ;PUT IT AT TOP CENTER OF SCREEN
fb6b: 88                           dey
fb6c: d0 f7                        bne     STITLE
fb6e: 60                           rts

fb6f: ad f3 03     SETPWRC         lda     SOFTEV+1          ;ROUTINE TO CALCULATE THE 'FUNNY
fb72: 49 a5                        eor     #$a5              ;COMPLEMENT' FOR THE RESET VECTOR
fb74: 8d f4 03                     sta     PWREDUP
fb77: 60                           rts

                   ; CHECK FOR A PAUSE (CONTROL-S).
fb78: c9 8d        VIDWAIT         cmp     #$8d              ;ONLY WHEN I HAVE A CR
fb7a: d0 18                        bne     NOWAIT            ;NOT SO, DO REGULAR
fb7c: ac 00 c0                     ldy     KBD               ;IS KEY PRESSED?
fb7f: 10 13                        bpl     NOWAIT            ;NO.
fb81: c0 93                        cpy     #$93              ;YES -- IS IT CTRL-S?
fb83: d0 0f                        bne     NOWAIT            ;NOPE - IGNORE
fb85: 2c 10 c0                     bit     KBDSTRB           ;CLEAR STROBE
fb88: ac 00 c0     KBDWAIT         ldy     KBD               ;WAIT TILL NEXT KEY TO RESUME
fb8b: 10 fb                        bpl     KBDWAIT           ;WAIT FOR KEYPRESS
fb8d: c0 83                        cpy     #$83              ;IS IT CONTROL-C?
fb8f: f0 03                        beq     NOWAIT            ;YES, SO LEAVE IT
fb91: 2c 10 c0                     bit     KBDSTRB           ;CLR STROBE
fb94: 2c 7b 06     NOWAIT          bit     VFACTV            ;is video firmware active?
fb97: 30 64                        bmi     VIDOUT            ;=>no, do normal 40 column
fb99: 89 60                        bit     #$60              ;is it a control?
fb9b: f0 b7                        beq     DOCTL             ;=>yes, do it
fb9d: 20 b8 c3                     jsr     STORCH            ;print w/inverse mask
fba0: ee 7b 05     NEWADV          inc     OURCH             ;advance cursor
fba3: ad 7b 05                     lda     OURCH             ;and update others
fba6: 2c 1f c0                     bit     RD80VID           ;but only if not 80 columns
fba9: 30 05                        bmi     NEWADV1           ;=>80 columns, leav'em
fbab: 8d 7b 04                     sta     OLDCH
fbae: 85 24                        sta     CH
fbb0: 80 46        NEWADV1         bra     ADV2              ;check for CR

fbb2: ff                           .dd1    $ff               ;[NOP $ea]

fbb3: 06           F8VERSION       .dd1    GOODF8            ;//e, chels ID byte

fbb4: 10 06        DOCOUT1         bpl     DCX               ;->video firmware active, no mask
fbb6: c9 a0                        cmp     #$a0              ;is it control char?
fbb8: 90 02                        bcc     DCX               ;=>yes, no mask
fbba: 25 32                        and     INVFLG            ;else apply inverse mask
fbbc: 4c f6 fd     DCX             jmp     COUTZ             ;and print character

fbbf: ff                           .dd1    $ff               ;[BRK $00]

fbc0: 00                           .dd1    $00               ;chels ID byte

fbc1: 48           BASCALC         pha                       ;CALC BASE ADDR IN BASL,H
fbc2: 4a                           lsr     A                 ;FOR GIVEN LINE NO.
fbc3: 29 03                        and     #$03              ; 0<=LINE NO.<=$17
fbc5: 09 04                        ora     #$04              ;ARG=000ABCDE, GENERATE
fbc7: 85 29                        sta     BASH              ; BASH=000001CD
fbc9: 68                           pla                       ; AND
fbca: 29 18                        and     #$18              ; BASL=EABAB000
fbcc: 90 02                        bcc     BASCLC2
fbce: 69 7f                        adc     #$7f
fbd0: 85 28        BASCLC2         sta     BASL
fbd2: 0a                           asl     A
fbd3: 0a                           asl     A
fbd4: 05 28                        ora     BASL
fbd6: 85 28                        sta     BASL
fbd8: 60                           rts

fbd9: c9 87        CHKBELL         cmp     #$87              ;BELL CHAR? (CONTROL-G)
fbdb: d0 12                        bne     RTS2B             ; NO, RETURN.
fbdd: a9 40        BELL1           lda     #$40              ; YES...
fbdf: 20 a8 fc                     jsr     WAIT              ;DELAY .01 SECONDS
fbe2: a0 c0                        ldy     #$c0
fbe4: a9 0c        BELL2           lda     #$0c              ;TOGGLE SPEAKER AT 1 KHZ
fbe6: 20 a8 fc                     jsr     WAIT              ; FOR .1 SEC.
fbe9: ad 30 c0                     lda     SPKR
fbec: 88                           dey
fbed: d0 f5                        bne     BELL2
fbef: 60           RTS2B           rts

fbf0: a4 24        STORADV         ldy     CH                ;get 40 column position
fbf2: 91 28                        sta     (BASL),y          ;and store
fbf4: e6 24        ADVANCE         inc     CH                ;increment cursor
fbf6: a5 24                        lda     CH
fbf8: c5 21        ADV2            cmp     WNDWDTH           ;BEYOND WINDOW WIDTH?
fbfa: b0 66                        bcs     CR                ; YES, CR TO NEXT LINE.
fbfc: 60           RTS3            rts                       ; NO, RETURN.

fbfd: c9 a0        VIDOUT          cmp     #$a0              ;CONTROL CHAR?
fbff: b0 ef                        bcs     STORADV           ; NO, OUTPUT IT.
fc01: a8                           tay                       ;INVERSE VIDEO?
fc02: 10 ec                        bpl     STORADV           ; YES, OUTPUT IT.
fc04: c9 8d        VIDOUT1         cmp     #$8d              ;CR?
fc06: f0 6b                        beq     NEWCR             ;Yes, use new routine
fc08: c9 8a                        cmp     #$8a              ;LINE FEED?
fc0a: f0 5a                        beq     LF                ; IF SO, DO IT.
fc0c: c9 88                        cmp     #$88              ;BACK SPACE? (CONTROL-H)
fc0e: d0 c9                        bne     CHKBELL           ; NO, CHECK FOR BELL.
fc10: 20 e2 fe     BS              jsr     DECCH             ;decrement all cursor H indices
fc13: 10 e7                        bpl     RTS3              ;IF POSITIVE, OK; ELSE MOVE UP.
fc15: a5 21                        lda     WNDWDTH           ;get window width,
fc17: 20 eb fe                     jsr     WDTHCH            ;and set CH's to WNDWDTH-1
fc1a: a5 22        UP              lda     WNDTOP            ;CURSOR V INDEX
fc1c: c5 25                        cmp     CV
fc1e: b0 dc                        bcs     RTS3              ;top line, exit
fc20: c6 25                        dec     CV                ;not top, go up one
                   ; 
fc22: 80 62        VTAB            bra     NEWVTAB           ;go update OURCV

fc24: 20 c1 fb     VTABZ           jsr     BASCALC           ;calculate the base address
fc27: a5 20                        lda     WNDLFT            ;get the left window edge
fc29: 2c 1f c0                     bit     RD80VID           ;80 columns?
fc2c: 10 02                        bpl     TAB40             ;=>no, left edge ok
fc2e: 4a                           lsr     A                 ;divide width by 2
fc2f: 18                           clc                       ;prepare to add
fc30: 65 28        TAB40           adc     BASL              ;add width to base
fc32: 85 28                        sta     BASL
fc34: 60           RTS4            rts

                   ; 
                   ; NEWOPTS translates the opcode in the Y register
                   ; to a mnemonic table index and returns with Z=1.
                   ; If Y is not a new opcode, Z=0.
                   ; 
fc35: 98           NEWOPS          tya                       ;get the opcode
fc36: a2 16                        ldx     #22               ;[NUMOPS] check through new opcodes
fc38: dd fe fe     NEWOP1          cmp     OPTBL,x           ;does it match?
fc3b: f0 43                        beq     GETINDX           ;=>yes, get new index
fc3d: ca                           dex
fc3e: 10 f8                        bpl     NEWOP1            ;else check next one
fc40: 60                           rts                       ;not found, exit with BNE

fc41: ff                           .dd1    $ff               ;[BRK $00]

fc42: 80 19        CLREOP          bra     CLREOP1           ;ESC F IS CLR TO END OF PAGE

fc44: a5 25        CLREOP2         lda     CV
fc46: 48           CLEOP1          pha                       ;SAVE CURRENT LINE NO. ON STACK
fc47: 20 24 fc                     jsr     VTABZ             ;CALC BASE ADDRESS
fc4a: 20 9e fc                     jsr     CLEOLZ            ;CLEAR TO EOL. (SETS CARRY)
fc4d: a0 00                        ldy     #$00              ;CLEAR FROM H INDEX=0 FOR REST
fc4f: 68                           pla                       ;INCREMENT CURRENT LINE NO.
fc50: 1a                           inc     A
fc51: c5 23                        cmp     WNDBTM            ;DONE TO BOTTOM OF WINDOW?
fc53: 90 f1                        bcc     CLEOP1            ; NO, KEEP CLEARING LINES.
fc55: b0 cb                        bcs     VTAB              ; YES, TAB TO CURRENT LINE

fc57: ff                           .dd1    $ff               ;[BRK $00]

fc58: 20 a5 cd     HOME            jsr     HOMECUR           ;move cursor home
fc5b: 80 e7                        bra     CLREOP2           ;then clear to end of page

fc5d: 20 9d cc     CLREOP1         jsr     GETCUR            ;load Y with proper CH
fc60: 80 e2                        bra     CLREOP2           ;before clearing page

fc62: 80 0f        CR              bra     NEWCR             ;only LF if not Pascal

fc64: fa                           .dd1    $fa               ;[BRK $00]
fc65: fa                           .dd1    $fa               ;[BRK $00]

fc66: e6 25        LF              inc     CV                ;INCR CURSOR V. (DOWN 1 LINE)
fc68: a5 25                        lda     CV
fc6a: c5 23                        cmp     WNDBTM            ;OFF SCREEN?
fc6c: 90 1a                        bcc     NEWVTABZ          ;set base+WNDLFT
fc6e: c6 25                        dec     CV                ;DECR CURSOR V. (BACK TO BOTTOM)
                   ; 
fc70: 4c 35 cb     SCROLL          jmp     SCROLLUP          ;scroll the screen

fc73: 20 e9 fe     NEWCR           jsr     CLRCH             ;set CH's to 0
fc76: 2c fb 04                     bit     VMODE             ;is it Pascal?
fc79: 10 0a                        bpl     CRRTS             ;pascal, no LF
fc7b: 20 44 fd                     jsr     NOESCAPE          ;else clear escape mode
fc7e: 80 e6                        bra     LF                ;then do LF

fc80: bd 15 ff     GETINDX         lda     INDX,x            ;lookup index for mnemonic
fc83: a0 00                        ldy     #$00              ;exit with BEQ
fc85: 60           CRRTS           rts

fc86: a5 25        NEWVTAB         lda     CV                ;update //e CV
fc88: 8d fb 05     NEWVTABZ        sta     OURCV
fc8b: 80 97                        bra     VTABZ             ;and calc base+WNDLFT

fc8d: 20 9d cc     NEWCLREOL       jsr     GETCUR            ;get current cursor
fc90: a9 a0        NEWCLREOLZ      lda     #$a0              ;get a blank
fc92: 2c 7b 06                     bit     VFACTV            ;if video firmware active,
fc95: 30 02                        bmi     NEWC1             ;=>don't use inverse mask
fc97: 25 32                        and     INVFLG
fc99: 4c c2 cb     NEWC1           jmp     DOCLR             ;go do clear

fc9c: 80 ef        CLREOL          bra     NEWCLREOL         ;get cursor and clear

fc9e: 80 f0        CLEOLZ          bra     NEWCLREOLZ        ;clear from Y

fca0: a0 00        CLRLIN          ldy     #0                ;clear entire line
fca2: 80 ec                        bra     NEWCLREOLZ

fca4: 7c 2a cd     CLTD0           jmp     (CTLADR,x)        ;jump to proper routine

fca7: ff                           .dd1    $ff               ;[NOP $ea]

fca8: 38           WAIT            sec
fca9: 48           WAIT2           pha
fcaa: e9 01        WAIT3           sbc     #$01
fcac: d0 fc                        bne     WAIT3             ;1.0204 USEC
fcae: 68                           pla                       ;(13+2712*A+512*A*A)
fcaf: e9 01                        sbc     #$01
fcb1: d0 f6                        bne     WAIT2
fcb3: 60           RTS6            rts

fcb4: e6 42        NXTA4           inc     A4L               ;INCR 2-BYTE A4
fcb6: d0 02                        bne     NXTA1             ; AND A1
fcb8: e6 43                        inc     A4H
fcba: a5 3c        NXTA1           lda     A1L               ;INCR 2-BYTE A1.
fcbc: c5 3e                        cmp     A2L               ; AND COMPARE TO A2
fcbe: a5 3d                        lda     A1H               ; (CARRY SET IF >=)
fcc0: e5 3f                        sbc     A2H
fcc2: e6 3c                        inc     A1L
fcc4: d0 02                        bne     RTS4B
fcc6: e6 3d                        inc     A1H
fcc8: 60           RTS4B           rts

fcc9: 60           HEADR           rts                       ;don't do it

fcca: a0 b0        COLDSTART       ldy     #$b0              ;let it precess down
fccc: 64 3c                        stz     A1L
fcce: a2 bf                        ldx     #$bf              ;start from PFXX down
fcd0: 86 3d        BLAST           stx     A1H
fcd2: a9 a0                        lda     #$a0              ;store blanks
fcd4: 91 3c                        sta     (A1L),y
fcd6: 88                           dey
fcd7: 91 3c                        sta     (A1L),y
fcd9: ca                           dex                       ;back down to next page
fcda: e0 01                        cpx     #1                ;stay away from stack
fcdc: d0 f2                        bne     BLAST             ;fall into COMINIT
                   ; 
fcde: 8d 01 c0                     sta     SET80COL          ;init ALT screen holes
fce1: ad 55 c0                     lda     TXTPAGE2          ;for serial and comm ports
fce4: 38                           sec
fce5: a2 88                        ldx     #$88
fce7: bd 27 cb     COM1            lda     comtbl-1,x        ;XFER from rom
fcea: 90 0a                        bcc     COM2              ;branch if defaults ok
fcec: dd 77 04                     cmp     $0477,x           ;test for prior setup
fcef: 18                           clc                       ;branch if not valid
fcf0: d0 04                        bne     COM2              ;If $4F8 & $4FF = TBL values
fcf2: e0 82                        cpx     #$82
fcf4: 90 06                        bcc     COM3
fcf6: 9d 77 04     COM2            sta     $0477,x
fcf9: ca                           dex                       ;move all 8...
fcfa: d0 eb                        bne     COM1
fcfc: ad 54 c0     COM3            lda     TXTPAGE1          ;restore switches
fcff: 8d 00 c0                     sta     CLR80COL          ;to default states
fd02: 60                           rts

fd03: c1 f0 f0 ec+ APPLE2C         .str    “Apple //c”

fd0c: a4 24        RDKEY           ldy     CH                ;get char at current position
fd0e: b1 28                        lda     (BASL),y          ;for those who restore it
fd10: ea                           nop                       ;if a program controls input
fd11: ea                           nop                       ;hooks, no cursor may be displayed
fd12: ea                           nop
fd13: ea                           nop
fd14: ea                           nop
fd15: ea                           nop
fd16: ea                           nop
fd17: ea                           nop
fd18: 6c 38 00     KEYIN0          jmp     (KSWL)            ;GO TO USER KEY-IN

fd1b: 91 28        KEYIN           sta     (BASL),y          ;erase false images
fd1d: 20 4c cc                     jsr     SHOWCUR           ;display true cursor
fd20: 20 70 cc     DONXTCUR        jsr     UPDATE            ;look for key, blink II cursor
fd23: 10 fb                        bpl     DONXTCUR          ;loop until keypress
fd25: 48                           pha                       ;save character
fd26: a9 08                        lda     #M_CTL            ;were escapes enabled?
fd28: 2c fb 04                     bit     VMODE
fd2b: d0 1d                        bne     NOESC2            ;=>no, there is no escape
fd2d: 68                           pla                       ;yes, there may be a way out!!
fd2e: c9 9b                        cmp     #ESC              ;escape?
fd30: d0 06                        bne     LOOKPICK          ;=>no escape
fd32: 4c cc cc                     jmp     NEWESC            ;=>go do escape sequence

fd35: 4c ed cc     RDCHAR          jmp     ESCRDKEY          ;do RDKEY with escapes

fd38: 2c 7b 06     LOOKPICK        bit     VFACTV            ;only process f.arrow
fd3b: 30 07                        bmi     NOESCAPE          ;if video firmware is active
fd3d: c9 95                        cmp     #PICK             ;was it PICK? (->,CTL-U)
fd3f: d0 03                        bne     NOESCAPE          ;no, just return
fd41: 20 1d cc                     jsr     PICKY             ;yes, pick the character
                   ; 
                   ; NOESCAPE is used by GETCOUT too.
                   ; 
fd44: 48           NOESCAPE        pha                       ;save it
fd45: a9 08                        lda     #M_CTL            ;disable escape sequences
fd47: 0c fb 04                     tsb     VMODE             ;and enable controls
fd4a: 68           NOESC2          pla                       ;by setting M.CTL
fd4b: 60                           rts

fd4c: ea                           nop

fd4d: 20 a6 c3     NOTCR           jsr     GETCOUT           ;disable controls and print
fd50: c9 88                        cmp     #$88              ;CHECK FOR EDIT KEYS
fd52: f0 1d                        beq     BCKSPC            ;  - BACKSPACE
fd54: c9 98                        cmp     #$98
fd56: f0 0a                        beq     CANCEL            ;  - CONTROL-X
fd58: e0 f8                        cpx     #$f8
fd5a: 90 03                        bcc     NOTCR1            ;MARGIN?
fd5c: 20 3a ff                     jsr     BELL              ; YES, SOUND BELL
fd5f: e8           NOTCR1          inx                       ;ADVANCE INPUT INDEX
fd60: d0 13                        bne     NXTCHAR
fd62: a9 dc        CANCEL          lda     #$dc              ;BACKSLASH AFTER CANCELLED LINE
fd64: 20 a6 c3                     jsr     GETCOUT
fd67: 20 8e fd     GETLNZ          jsr     CROUT             ;OUTPUT 'CR'
fd6a: a5 33        GETLN           lda     PROMPT            ;OUTPUT PROMPT CHAR
fd6c: 20 ed fd                     jsr     COUT
fd6f: a2 01        GETLN1          ldx     #$01              ;INIT INPUT INDEX
fd71: 8a           BCKSPC          txa
fd72: f0 f3                        beq     GETLNZ            ;WILL BACKSPACE TO 0
fd74: ca                           dex
fd75: 20 ed cc     NXTCHAR         jsr     ESCRDKEY          ;do new RDCHAR (allow escapes)
fd78: c9 95                        cmp     #PICK             ;USE SCREEN CHAR
fd7a: d0 08                        bne     ADDINP            ; FOR CONTROL-U
fd7c: 20 1d cc                     jsr     PICKY             ;lift char from screen
fd7f: ea                           nop
fd80: ea                           nop
fd81: ea                           nop                       ;no upshifting needed
fd82: ea                           nop
fd83: ea                           nop
fd84: 9d 00 02     ADDINP          sta     IN,x              ;ADD TO INPUT BUFFER
fd87: c9 8d                        cmp     #$8d
fd89: d0 c2                        bne     NOTCR
fd8b: 20 9c fc     CROUT1          jsr     CLREOL            ;CLR TO EOL IF CR
fd8e: a9 8d        CROUT           lda     #$8d
fd90: d0 5b                        bne     COUT              ;(ALWAYS)

fd92: a4 3d        PRA1            ldy     A1H               ;PRINT CR,A1 IN HEX
fd94: a6 3c                        ldx     A1L
fd96: 20 8e fd     PRYX2           jsr     CROUT
fd99: 20 40 f9                     jsr     PRNTYX
fd9c: a0 00                        ldy     #$00
fd9e: a9 ad                        lda     #$ad              ;PRINT '-'
fda0: 4c ed fd                     jmp     COUT

fda3: a5 3c        XAM8            lda     A1L
fda5: 09 07                        ora     #$07              ;SET TO FINISH AT
fda7: 85 3e                        sta     A2L               ; MOD 8=7
fda9: a5 3d                        lda     A1H
fdab: 85 3f                        sta     A2H
fdad: a5 3c        MOD8CHK         lda     A1L
fdaf: 29 07                        and     #$07
fdb1: d0 03                        bne     DATAOUT
fdb3: 20 92 fd     XAM             jsr     PRA1
fdb6: a9 a0        DATAOUT         lda     #$a0
fdb8: 20 ed fd                     jsr     COUT              ;OUTPUT BLANK
fdbb: b1 3c                        lda     (A1L),y
fdbd: 20 da fd                     jsr     PRBYTE            ;OUTPUT BYTE IN HEX
fdc0: 20 ba fc                     jsr     NXTA1
fdc3: 90 e8                        bcc     MOD8CHK           ;NOT DONE YET. GO CHECK MOD 8
fdc5: 60           RTS4C           rts                       ;DONE.

fdc6: 4a           XAMPM           lsr     A                 ;DETERMINE IF MONITOR MODE IS
fdc7: 90 ea                        bcc     XAM               ; EXAMINE, ADD OR SUBTRACT
fdc9: 4a                           lsr     A
fdca: 4a                           lsr     A
fdcb: a5 3e                        lda     A2L
fdcd: 90 02                        bcc     ADD
fdcf: 49 ff                        eor     #$ff              ;FORM 2'S COMPLEMENT FOR SUBTRACT.
fdd1: 65 3c        ADD             adc     A1L
fdd3: 48                           pha
fdd4: a9 bd                        lda     #$bd              ;PRINT '=', THEN RESULT
fdd6: 20 ed fd                     jsr     COUT
fdd9: 68                           pla
                   ; 
fdda: 48           PRBYTE          pha                       ;PRINT BYTE AS 2 HEX DIGITS
fddb: 4a                           lsr     A                 ; (DESTROYS A-REG)
fddc: 4a                           lsr     A
fddd: 4a                           lsr     A
fdde: 4a                           lsr     A
fddf: 20 e5 fd                     jsr     PRHEXZ
fde2: 68                           pla
                   ; 
fde3: 29 0f        PRHEX           and     #$0f              ;PRINT HEX DIGIT IN A-REG
fde5: 09 b0        PRHEXZ          ora     #$b0              ;LSBITS ONLY.
fde7: c9 ba                        cmp     #$ba
fde9: 90 02                        bcc     COUT
fdeb: 69 06                        adc     #$06
                   ; 
fded: 6c 36 00     COUT            jmp     (CSWL)            ;VECTOR TO USER OUTPUT ROUTINE

fdf0: 2c 7b 06     COUT1           bit     VFACTV            ;video firmware active?
fdf3: 4c b4 fb                     jmp     DOCOUT1           ;mask II mode characters

fdf6: 84 35        COUTZ           sty     YSAV1             ;SAVE Y-REG
fdf8: 48                           pha                       ;SAVE A -REG
fdf9: 20 78 fb                     jsr     VIDWAIT           ;OUTPUT CHR AND CHECK FOR CTRL-S
fdfc: 68                           pla                       ;RESTORE A-REG
fdfd: a4 35                        ldy     YSAV1             ;AND Y-REG
fdff: 60                           rts                       ;RETURN TO SENDER...

fe00: c6 34        BL1             dec     YSAV
fe02: f0 9f                        beq     XAM8
                   ; 
fe04: ca           BLANK           dex                       ;BLANK TO MON
fe05: d0 16                        bne     SETMDZ            ;AFTER BLANK
fe07: c9 ba                        cmp     #$ba              ;DATA STORE MODE?
fe09: d0 bb                        bne     XAMPM             ; NO; XAM, ADD, OR SUBTRACT.
                   ; 
fe0b: 85 31                        sta     MODE              ;KEEP IN STORE MODE
fe0d: a5 3e                        lda     A2L
fe0f: 91 40                        sta     (A3L),y           ;STORE AS LOW BYTE AT (A3)
fe11: e6 40                        inc     A3L
fe13: d0 02                        bne     RTS5              ;INCR A3, RETURN.
fe15: e6 41                        inc     A3H
fe17: 60           RTS5            rts

fe18: a4 34        SETMODE         ldy     YSAV              ;SAVE CONVERTED ':', '+',
fe1a: b9 ff 01                     lda     IN-1,y            ; '-', '.' AS MODE
fe1d: 85 31        SETMDZ          sta     MODE
fe1f: 60                           rts

fe20: a2 01        LT              ldx     #$01
fe22: b5 3e        LT2             lda     A2L,x             ;COPY A2 (2 BYTES) TO
fe24: 95 42                        sta     A4L,x             ; A4 AND A5
fe26: 95 44                        sta     A5L,x
fe28: ca                           dex
fe29: 10 f7                        bpl     LT2
fe2b: 60                           rts

fe2c: b1 3c        MOVE            lda     (A1L),y           ;MOVE (A1) THRU (A2) TO (A4)
fe2e: 91 42                        sta     (A4L),y
fe30: 20 b4 fc                     jsr     NXTA4
fe33: 90 f7                        bcc     MOVE
fe35: 60                           rts

fe36: b1 3c        VERIFY          lda     (A1L),y           ;VERIFY (A1) THRU (A2)
fe38: d1 42                        cmp     (A4L),y           ; WITH (A4)
fe3a: f0 1c                        beq     VFYOK
fe3c: 20 92 fd                     jsr     PRA1
fe3f: b1 3c                        lda     (A1L),y
fe41: 20 da fd                     jsr     PRBYTE
fe44: a9 a0                        lda     #$a0
fe46: 20 ed fd                     jsr     COUT
fe49: a9 a8                        lda     #$a8
fe4b: 20 ed fd                     jsr     COUT
fe4e: b1 42                        lda     (A4L),y
fe50: 20 da fd                     jsr     PRBYTE
fe53: a9 a9                        lda     #$a9
fe55: 20 ed fd                     jsr     COUT
fe58: 20 b4 fc     VFYOK           jsr     NXTA4
fe5b: 90 d9                        bcc     VERIFY
fe5d: 60                           rts

fe5e: 20 75 fe     LIST            jsr     A1PC              ;MOVE A1 (2 BYTES) TO
fe61: a9 14                        lda     #$14              ; PC IF SPEC'D AND
fe63: 48           LIST2           pha                       ; DISASSEMBLE 20 INSTRUCTIONS.
fe64: 20 d0 f8                     jsr     INSTDSP
fe67: 20 53 f9                     jsr     PCADJ             ;ADJUST PC AFTER EACH INSTRUCTION
fe6a: 85 3a                        sta     PCL
fe6c: 84 3b                        sty     PCH
fe6e: 68                           pla
fe6f: 38                           sec
fe70: e9 01                        sbc     #$01              ;NEXT OF 20 INSTRUCTIONS
fe72: d0 ef                        bne     LIST2
fe74: 60                           rts

fe75: 8a           A1PC            txa                       ;IF USER SPECIFIED AN ADDRESS,
fe76: f0 07                        beq     A1PCRTS           ; COPY IT FROM A1 TO PC.
fe78: b5 3c        A1PCLP          lda     A1L,x             ;YEP, SO COPY IT.
fe7a: 95 3a                        sta     PCL,x
fe7c: ca                           dex
fe7d: 10 f9                        bpl     A1PCLP
fe7f: 60           A1PCRTS         rts

fe80: a0 3f        SETINV          ldy     #$3f              ;SET FOR INVERSE VID
fe82: d0 02                        bne     SETFLG            ; VIA COUT1

fe84: a0 ff        SETNORM         ldy     #$ff              ;SET FOR NORMAL VID
fe86: 84 32        SETFLG          sty     INVFLG
fe88: 60                           rts

fe89: a9 00        SETKBD          lda     #$00              ;DO 'IN#0'
fe8b: 85 3e        INPORT          sta     A2L               ;DO 'IN#AREG'
fe8d: a2 38        INPRT           ldx     #KSWL
fe8f: a0 1b                        ldy     #<KEYIN
fe91: d0 08                        bne     IPORT

fe93: a9 00        SETVID          lda     #$00              ;DO 'PR#0'
fe95: 85 3e        OUTPORT         sta     A2L               ;DO 'PR#AREG'
fe97: a2 36        OUTPRT          ldx     #CSWL
fe99: a0 f0                        ldy     #<COUT1
fe9b: a5 3e        IPORT           lda     A2L
fe9d: 29 0f                        and     #$0f
fe9f: d0 06                        bne     NOTPRT0           ;not slot 0
fea1: c0 1b                        cpy     #$1b              ;Continue if KEYIN
fea3: f0 39                        beq     IOPRT1
fea5: 80 1b                        bra     CPRT0             ;=>do PR#0

fea7: 09 c0        NOTPRT0         ora     #>IOADR
fea9: a0 00                        ldy     #$00
feab: 94 00        IOPRT2          sty     LOC0,x
fead: 95 01                        sta     LOC1,x
feaf: 60                           rts

feb0: 4c 00 e0     XBASIC          jmp     BASIC             ;TO BASIC, COLD START

feb3: 4c 03 e0     BASCONT         jmp     BASIC2            ;TO BASIC, WARM START

feb6: 20 75 fe     GO              jsr     A1PC              ;ADDR TO PC IF SPECIFIED
feb9: 20 3f ff                     jsr     RESTORE           ;RESTORE FAKE REGISTERS
febc: 6c 3a 00                     jmp     (PCL)             ; AND GO!

febf: 4c d7 fa     REGZ            jmp     REGDSP            ;GO DISPLAY REGISTERS

fec2: 3a           CPRT0           dec     A                 ;Need $FF
fec3: 8d fb 07                     sta     CURSOR            ;set checkerboard cursor
fec6: a9 f7                        lda     #$f7              ;[#$FF-M.CTL] reset mode
fec8: 80 04                        bra     DOPR0

feca: 4c f8 03     USR             jmp     USRADR            ;JUMP TO CONTROL-Y VECTOR IN RAM

fecd: 60           WRITE           rts                       ;Tape write not needed

fece: 8d 7b 06     DOPR0           sta     VFACTV            ;say video firmware inactive
fed1: 8d 0e c0                     sta     CLRALTCHAR        ;switch in normal char set
fed4: 0c fb 04                     tsb     VMODE             ;don't change M.CTL
fed7: da                           phx                       ;save X and Y
fed8: 5a                           phy                       ;for rest of PR#0
fed9: 20 cd cd                     jsr     CHK80             ;convert to 40 if needed
fedc: 7a                           ply
fedd: fa                           plx
fede: a9 fd        IOPRT1          lda     #>COUT1           ;set I/O page
fee0: 80 c9                        bra     IOPRT2            ;=>go set output hook

                   ; 
                   ; DECCH decrements the current cursor
                   ; CLRCH sets all cursors to 0
                   ; SETCUR sets cursors to value in Acc.
                   ; See explanatory note with GETCUR
                   ; 
fee2: 5a           DECCH           phy                       ;(from $FC10)
fee3: 20 9d cc                     jsr     GETCUR            ;get current CH
fee6: 88                           dey                       ;decrement it
fee7: 80 05                        bra     SETCUR1           ;go update cursors

fee9: a9 01        CLRCH           lda     #1                ;set all cursors to 0
feeb: 3a           WDTHCH          dec     A                 ;dec window width (from $FC17)
feec: 5a           SETCUR          phy                       ;save Y
feed: a8                           tay                       ;need value in Y
feee: 20 ad cc     SETCUR1         jsr     GETCUR2           ;save new CH
fef1: 7a                           ply                       ;restore Y
fef2: ad 7b 05                     lda     OURCH             ;and get new CH into acc
fef5: 60                           rts                       ;(Need LDA to set flags)

fef6: 20 00 fe     CRMON           jsr     BL1               ;HANDLE CR AS BLANK
fef9: 68                           pla                       ; THEN POP STACK
fefa: 68                           pla                       ; AND RETURN TO MON
fefb: d0 6c                        bne     MONZ              ;(ALWAYS)

fefd: 60           READ            rts                       ;Tape read not needed

                   ; 
                   ; OPTBL is a table containing the new opcodes that
                   ; wouldn't fit into the existing lookup table.
                   ; 
fefe: 12           OPTBL           .dd1    $12               ;ORA (ZPAG)
feff: 14                           .dd1    $14               ;TRB ZPAG
ff00: 1a                           .dd1    $1a               ;INC A
ff01: 1c                           .dd1    $1c               ;TRB ABS
ff02: 32                           .dd1    $32               ;AND (ZPAG)
ff03: 34                           .dd1    $34               ;BIT ZPAG,X
ff04: 3a                           .dd1    $3a               ;DEC A
ff05: 3c                           .dd1    $3c               ;BIT ABS,X
ff06: 52                           .dd1    $52               ;EOR (ZPAG)
ff07: 5a                           .dd1    $5a               ;PHY
ff08: 64                           .dd1    $64               ;STZ ZPAG
ff09: 72                           .dd1    $72               ;ADC (ZPAG)
ff0a: 74                           .dd1    $74               ;STZ ZPAG,X
ff0b: 7a                           .dd1    $7a               ;PLY
ff0c: 7c                           .dd1    $7c               ;JMP (ABS,X)
ff0d: 89                           .dd1    $89               ;BIT IMM
ff0e: 92                           .dd1    $92               ;STZ (ZPAG)
ff0f: 9c                           .dd1    $9c               ;STZ ABS
ff10: 9e                           .dd1    $9e               ;STZ ABS,X
ff11: b2                           .dd1    $b2               ;LDA (ZPAG)
ff12: d2                           .dd1    $d2               ;CMP (ZPAG)
ff13: f2                           .dd1    $f2               ;SBC (ZPAG)
ff14: fc                           .dd1    $fc               ;??? (the unknown opcode)
                   ; [NUMOPS EQU *-OPTBL-1] number of bytes to check
ff15: 38           INDX            .dd1    $38
ff16: fb                           .dd1    $fb
ff17: 37                           .dd1    $37
ff18: fb                           .dd1    $fb
ff19: 39                           .dd1    $39
ff1a: 21                           .dd1    $21
ff1b: 36                           .dd1    $36
ff1c: 21                           .dd1    $21
ff1d: 3a                           .dd1    $3a
ff1e: f8                           .dd1    $f8
ff1f: fa                           .dd1    $fa
ff20: 3b                           .dd1    $3b
ff21: fa                           .dd1    $fa
ff22: f9                           .dd1    $f9
ff23: 22                           .dd1    $22
ff24: 21                           .dd1    $21
ff25: 3c                           .dd1    $3c
ff26: fa                           .dd1    $fa
ff27: fa                           .dd1    $fa
ff28: 3d                           .dd1    $3d
ff29: 3e                           .dd1    $3e
ff2a: 3f                           .dd1    $3f
ff2b: fc                           .dd1    $fc               ;???
ff2c: 00                           .dd1    $00

ff2d: a9 c5        PRERR           lda     #$c5              ;PRINT 'ERR', THEN FALL INTO
ff2f: 20 ed fd                     jsr     COUT              ; FWEEPER.
ff32: a9 d2                        lda     #$d2
ff34: 20 ed fd                     jsr     COUT
ff37: 20 ed fd                     jsr     COUT
                   ; 
ff3a: a9 87        BELL            lda     #$87              ;MAKE A JOYFUL NOISE, THEN RETURN.
ff3c: 4c ed fd                     jmp     COUT

ff3f: a5 48        RESTORE         lda     STATUS            ;RESTORE 6502 REGISTER CONTENTS
ff41: 48                           pha                       ; USED BY DEBUG SOFTWARE
ff42: a5 45                        lda     A5H
ff44: a6 46        RESTR1          ldx     XREG
ff46: a4 47                        ldy     YREG
ff48: 28                           plp
ff49: 60                           rts

ff4a: 85 45        SAVE            sta     A5H               ;SAVE 6502 REGISTER CONTENTS
ff4c: 86 46        SAV1            stx     XREG              ; FOR DEBUG SOFTWARE
ff4e: 84 47                        sty     YREG
ff50: 08                           php
ff51: 68                           pla
ff52: 85 48                        sta     STATUS
ff54: ba                           tsx
ff55: 86 49                        stx     SPNT
ff57: d8                           cld
ff58: 60           IORTS           rts

ff59: 20 84 fe     OLDRST          jsr     SETNORM           ;SET SCREEN MODE
ff5c: 20 2f fb                     jsr     INIT              ; AND INIT KBD/SCREEN
ff5f: 20 93 fe                     jsr     SETVID            ; AS I/O DEVS.
ff62: 20 89 fe                     jsr     SETKBD
                   ; 
ff65: d8           MON             cld                       ;MUST SET HEX MODE!
ff66: 20 3a ff                     jsr     BELL              ;FWEEPER.
ff69: a9 aa        MONZ            lda     #$aa              ;'*' PROMPT FOR MONITOR
ff6b: 85 33                        sta     PROMPT
ff6d: 20 67 fd                     jsr     GETLNZ            ;READ A LINE OF INPUT
ff70: 20 c7 ff                     jsr     ZMODE             ;CLEAR MONITOR MODE, SCAN IDX
ff73: 20 a7 ff     NXTITM          jsr     GETNUM            ;GET ITEM, NON-HEX
ff76: 84 34                        sty     YSAV              ; CHAR IN A-REG.
ff78: a0 13                        ldy     #$13              ;[#SUBTBL-CHRTBL] X-REG=0 IF NO HEX INPUT
ff7a: 88           CHRSRCH         dey
ff7b: 30 e8                        bmi     MON               ;COMMAND NOT FOUND, BEEP & TRY AGAIN.
ff7d: d9 cd ff                     cmp     CHRTBL,y          ;FIND COMMAND CHAR IN TABLE
ff80: d0 f8                        bne     CHRSRCH           ;NOT THIS TIME
ff82: 20 be ff                     jsr     TOSUB             ;GOT IT! CALL CORRESPONDING SUBROUTINE
ff85: a4 34                        ldy     YSAV              ;PROCESS NEXT ENTRY ON HIS LINE
ff87: 4c 73 ff                     jmp     NXTITM

ff8a: a2 03        DIG             ldx     #$03
ff8c: 0a                           asl     A
ff8d: 0a                           asl     A                 ;GOT HEX DIGIT,
ff8e: 0a                           asl     A                 ; SHIFT INTO A2
ff8f: 0a                           asl     A
ff90: 0a           NXTBIT          asl     A
ff91: 26 3e                        rol     A2L
ff93: 26 3f                        rol     A2H
ff95: ca                           dex                       ;LEAVE X=$FF IF DIG
ff96: 10 f8                        bpl     NXTBIT
ff98: a5 31        NXTBAS          lda     MODE
ff9a: d0 06                        bne     NXTBS2            ;IF MODE IS ZERO,
ff9c: b5 3f                        lda     A2H,x             ; THEN COPY A2 TO A1 AND A3
ff9e: 95 3d                        sta     A1H,x
ffa0: 95 41                        sta     A3H,x
ffa2: e8           NXTBS2          inx
ffa3: f0 f3                        beq     NXTBAS
ffa5: d0 06                        bne     NXTCHR

ffa7: a2 00        GETNUM          ldx     #$00              ;CLEAR A2
ffa9: 86 3e                        stx     A2L
ffab: 86 3f                        stx     A2H
ffad: b9 00 02     NXTCHR          lda     IN,y              ;GET CHAR
ffb0: c8                           iny
ffb1: 20 99 c3                     jsr     UPSHIFT0          ;upshift if necessary (set high bit)
ffb4: 49 b0                        eor     #$b0
ffb6: c9 0a                        cmp     #$0a
ffb8: 90 d0                        bcc     DIG               ;it's a digit
ffba: 80 37                        bra     GETHEX            ;check for other digits

ffbc: ff                           .dd1    $ff               ;[BRK $00]
ffbd: 41                           .dd1    $41               ;[BRK $00]

ffbe: a9 fe        TOSUB           lda     #>GO              ;DISPATCH TO SUBROUTINE, BY
ffc0: 48                           pha                       ; PUSHING THE HI-ORDER SUBR ADDR,
ffc1: b9 e0 ff                     lda     SUBTBL,y          ; THEN THE LO-RDER SUBR ADDR
ffc4: 48                           pha                       ; ONTO THE STACK,
ffc5: a5 31                        lda     MODE              ; (CLEARING THE MODE, SAVE THE OLD
ffc7: a0 00        ZMODE           ldy     #$00              ; MODE IN A-REG).
ffc9: 84 31                        sty     MODE
ffcb: 60                           rts                       ;AND 'RTS' TO THE SUBROUTINE!

ffcc: ea                           .dd1    $ea               ;[NOP $EA]
                   ; 
ffcd: bc           CHRTBL          .dd1    $bc               ;^C  (BASIC WARM START)
ffce: b2                           .dd1    $b2               ;^Y  (USER VECTOR)
ffcf: be                           .dd1    $be               ;^E  (OPEN AND DISPLAY REGISTERS)
ffd0: ef                           .dd1    $ef               ;V   (MEMORY VERIFY)
ffd1: c4                           .dd1    $c4               ;^K  (IN#SLOT)
ffd2: a9                           .dd1    $a9               ;^P  (PR#SLOT)
ffd3: bb                           .dd1    $bb               ;^B  (BASIC COLD START)
ffd4: a6                           .dd1    $a6               ;'-' (SUBTRACTION)
ffd5: a4                           .dd1    $a4               ;'+' (ADDITION)
ffd6: 06                           .dd1    $06               ;M   (MEMORY MOVE)
ffd7: 95                           .dd1    $95               ;'<' (DELIMITER FOR MOVE, VFY)
ffd8: 07                           .dd1    $07               ;N   (SET NORMAL VIDEO)
ffd9: 02                           .dd1    $02               ;I   (SET INVERSE VIDEO)
ffda: 05                           .dd1    $05               ;L   (DISASSEMBLE 20 INSTRS)
ffdb: 00                           .dd1    $00               ;G   (EXECUTE PROGRAM)
ffdc: 93                           .dd1    $93               ;':' (MEMORY FILL)
ffdd: a7                           .dd1    $a7               ;'.' (ADDRESS DELIMITER)
ffde: c6                           .dd1    $c6               ;'CR' (END OF INPUT)
ffdf: 99                           .dd1    $99               ;BLANK
                   ; 
                   ; Table of low order monitor routine
                   ; dispatch addresses.
                   ; 
ffe0: b2           SUBTBL          .dd1    <BASCONT-1
ffe1: c9                           .dd1    <USR-1
ffe2: be                           .dd1    <REGZ-1
ffe3: 35                           .dd1    <VERIFY-1
ffe4: 8c                           .dd1    <INPRT-1
ffe5: 96                           .dd1    <OUTPRT-1
ffe6: af                           .dd1    <XBASIC-1
ffe7: 17                           .dd1    <SETMODE-1
ffe8: 17                           .dd1    <SETMODE-1
ffe9: 2b                           .dd1    <MOVE-1
ffea: 1f                           .dd1    <LT-1
ffeb: 83                           .dd1    <SETNORM-1
ffec: 7f                           .dd1    <SETINV-1
ffed: 5d                           .dd1    <LIST-1
ffee: b5                           .dd1    <GO-1
ffef: 17                           .dd1    <SETMODE-1
fff0: 17                           .dd1    <SETMODE-1
fff1: f5                           .dd1    <CRMON-1
fff2: 03                           .dd1    <BLANK-1

fff3: 69 88        GETHEX          adc     #$88
fff5: c9 fa                        cmp     #$fa
fff7: b0 91                        bcs     DIG
fff9: 60                           rts

fffa: fb 03                        .dd2    NMI               ;NON-MASKABLE INTERRUPT VECTOR
fffc: 62 fa                        .dd2    RESET             ;RESET VECTOR
fffe: 03 c8        IRQVECT         .dd2    NEWIRQ            ;INTERRUPT REQUEST VECTOR
                                   .adrend ↑ $c100

Symbol Table

No exported symbols found.