back to project page

PAINT#066800 Disassembly

                   ********************************************************************************
                   * Micro-Painter, by Bob Bishop                                                 *
                   * Copyright 1980 Datasoft, Inc. All Rights Reserved.                           *
                   *                                                                              *
                   * Disassembly of "PAINT" routines.                                             *
                   ********************************************************************************
                   * Disassembly by Andy McFadden, using 6502bench SourceGen v1.4.                *
                   * Last updated 2019/10/25.                                                     *
                   ********************************************************************************
                   color_black   .eq     0      {const}
                   color_purple  .eq     1      {const}
                   color_green   .eq     2      {const}
                   color_blue    .eq     3      {const}
                   color_orange  .eq     4      {const}
                   color_white   .eq     5      {const}
                   work_buffer   .eq     $7000  {addr/4096} ;work data area, from $7000-7fff
                   TXTCLR        .eq     $c050           ;RW display graphics
                   MIXCLR        .eq     $c052           ;RW display full screen
                   TXTPAGE1      .eq     $c054           ;RW display page 1
                   LORES         .eq     $c056           ;RW display lo-res graphics

                                 .org    $6800
                   ********************************************************************************
                   * FILL - flood fill with dither pattern.                                       *
                   *                                                                              *
                   * Uses a circular buffer at $7000-7fff to hold X/Y coordinates.  The color of  *
                   * the pixel at the initial X/Y is used as the to-fill color.                   *
                   *                                                                              *
                   * Start by adding the initial X/Y to the work buffer.  We then loop, removing  *
                   * the first coordinate from the buffer and testing the color at that location. *
                   * If it matches, we draw the pixel, and then add the four adjacent pixels to   *
                   * the list.  Repeat until the list is empty.                                   *
                   *                                                                              *
                   * Warning: filling with the same color, e.g. filling a white area with white,  *
                   * will likely hang.                                                            *
                   *                                                                              *
                   * On entry:                                                                    *
                   *   $01 - X-coord                                                              *
                   *   $02 - Y-coord                                                              *
                   *   $04 - even color (0-5)                                                     *
                   *   $05 - odd color (0-5)                                                      *
                   *                                                                              *
                   * Preserves X/Y registers.                                                     *
                   ********************************************************************************
                   xc            .var    $01    {addr/1}
                   yc            .var    $02    {addr/1}
                   back          .var    $03    {addr/1}
                   evenc         .var    $04    {addr/1}
                   oddc          .var    $05    {addr/1}
                   match_color   .var    $10    {addr/1}
                   add_coord_lo  .var    $12    {addr/1}
                   plot_coord_lo .var    $13    {addr/1}
                   add_coord_ptr .var    $14    {addr/2} ;new coords are added at this point
                   plot_coord_ptr .var   $16    {addr/2} ;coords are read from this pointer and plotted
                   tmp           .var    $18    {addr/1}

6800: 8a           FILL          txa
6801: 48                         pha
6802: 98                         tya
6803: 48                         pha
6804: a9 80                      lda     #$80
6806: 85 03                      sta     back
6808: 20 03 69                   jsr     PLT             ;get current color at X,Y
680b: a5 03                      lda     back
680d: 85 10                      sta     match_color     ;this is the color we're replacing
680f: a9 00                      lda     #<work_buffer
6811: 85 14                      sta     add_coord_ptr
6813: 85 16                      sta     plot_coord_ptr
6815: a9 70                      lda     #>work_buffer
6817: 85 15                      sta     add_coord_ptr+1
6819: 85 17                      sta     plot_coord_ptr+1
681b: a5 01                      lda     xc              ;put first point into work buffer
681d: 8d 00 70                   sta     work_buffer
6820: a5 02                      lda     yc
6822: 8d 01 70                   sta     work_buffer+1
6825: a0 02                      ldy     #$02            ;point next output past the X,Y we just added
6827: 84 12                      sty     add_coord_lo
6829: a0 00                      ldy     #$00
682b: 84 13                      sty     plot_coord_lo
                   ; Get the next candidate coordinate.
682d: b1 16        FillLoop      lda     (plot_coord_ptr),y
682f: 85 01                      sta     xc
6831: c8                         iny
6832: b1 16                      lda     (plot_coord_ptr),y
6834: 85 02                      sta     yc
6836: c8                         iny
6837: d0 0c                      bne     L6845           ;still on same page, branch
6839: e6 17                      inc     plot_coord_ptr+1 ;move to next page
683b: a5 17                      lda     plot_coord_ptr+1
683d: c9 80                      cmp     #$80            ;did we reach the end of the buffer?
683f: d0 04                      bne     L6845           ;no, keep going
6841: a9 70                      lda     #>work_buffer   ;yes, reset it
6843: 85 17                      sta     plot_coord_ptr+1
6845: 84 13        L6845         sty     plot_coord_lo
6847: a9 80                      lda     #$80
6849: 85 03                      sta     back
684b: 20 03 69                   jsr     PLT             ;get screen pixel color
684e: a5 03                      lda     back
6850: c5 10                      cmp     match_color     ;matching color?
6852: d0 1f                      bne     L6873           ;no, don't plot
                   ; The current pixel matches the color we want to replace.  Plot a pixel and add
                   ; the four adjacent pixels to the work list.
6854: 20 00 69                   jsr     DITHER          ;plot pixel with dither colors
6857: e6 01                      inc     xc
6859: 20 84 68                   jsr     AddCoord        ;X+1,Y
685c: c6 01                      dec     xc
685e: e6 02                      inc     yc
6860: 20 84 68                   jsr     AddCoord        ;X,Y+1
6863: c6 01                      dec     xc
6865: c6 02                      dec     yc
6867: 20 84 68                   jsr     AddCoord        ;X-1,Y
686a: e6 01                      inc     xc
686c: c6 02                      dec     yc
686e: 20 84 68                   jsr     AddCoord        ;X-1,Y-1
6871: e6 02                      inc     yc
6873: a4 13        L6873         ldy     plot_coord_lo   ;have we reached the end?
6875: c4 12                      cpy     add_coord_lo
6877: d0 b4                      bne     FillLoop        ;low part differs, continue
6879: a5 17                      lda     plot_coord_ptr+1
687b: c5 15                      cmp     add_coord_ptr+1
687d: d0 ae                      bne     FillLoop        ;high part differs, continue
687f: 68                         pla                     ;done!
6880: a8                         tay
6881: 68                         pla
6882: aa                         tax
6883: 60                         rts

6884: a5 02        AddCoord      lda     yc              ;check Y-coord
6886: c9 ff                      cmp     #255            ;off top of screen?
6888: f0 40                      beq     L68CA           ;yes, ignore
688a: c9 c0                      cmp     #192            ;off bottom of screen?
688c: f0 3c                      beq     L68CA           ;yes, ignore
688e: a5 01                      lda     xc              ;check X-coord
6890: c9 ff                      cmp     #$ff            ;off left of screen?
6892: f0 36                      beq     L68CA           ;yes, ignore
6894: c9 8c                      cmp     #140            ;off right of screen?
6896: f0 32                      beq     L68CA           ;yes, ignore
                   ; Looks good, add X,Y to list.
                   ; Note add_coord_ptr is always $xx00; the low byte is in add_coord_lo.
6898: a4 12                      ldy     add_coord_lo
689a: 91 14                      sta     (add_coord_ptr),y
689c: c8                         iny
689d: a5 02                      lda     yc
689f: 91 14                      sta     (add_coord_ptr),y
68a1: c8                         iny
68a2: 84 12                      sty     add_coord_lo
68a4: a5 15                      lda     add_coord_ptr+1
68a6: 85 18                      sta     tmp
68a8: c0 00                      cpy     #$00            ;did we advance to next page?
68aa: d0 0c                      bne     L68B8           ;no, continue
68ac: e6 15                      inc     add_coord_ptr+1 ;yes, advance
68ae: a5 15                      lda     add_coord_ptr+1
68b0: c9 80                      cmp     #(>work_buffer)+16 ;did we reach end of work area?
68b2: d0 04                      bne     L68B8           ;no, still good
68b4: a9 70                      lda     #>work_buffer   ;yes, wrap around
68b6: 85 15                      sta     add_coord_ptr+1
68b8: c4 13        L68B8         cpy     plot_coord_lo   ;did we run into the "write" ptr?
68ba: d0 0e                      bne     L68CA           ;no
68bc: a5 17                      lda     plot_coord_ptr+1 ;check the high byte
68be: c5 15                      cmp     add_coord_ptr+1
68c0: d0 08                      bne     L68CA           ;still no
68c2: c6 12                      dec     add_coord_lo    ;whoops; back up, discarding what we just added
68c4: c6 12                      dec     add_coord_lo
68c6: a5 18                      lda     tmp             ;restore previous high byte
68c8: 85 15                      sta     add_coord_ptr+1
68ca: 60           L68CA         rts

68cb: 01 ff ff 01+               .align  $0100 (53 bytes)

6900: 4c 06 69     DITHER        jmp     DITHER1

6903: 4c 26 69     PLT           jmp     PLT1            ;external entry point

                   ********************************************************************************
                   * DITHER - plot a point with dithered colors.                                  *
                   *                                                                              *
                   * On entry:                                                                    *
                   *                                                                              *
                   *   $00 - hi-res page (zero for page 1, nonzero for page 2)                    *
                   *   $01 - X coordinate [0,139]                                                 *
                   *   $02 - Y coordinate [0,191]                                                 *
                   *   $04 - even color value                                                     *
                   *   $05 - odd color value                                                      *
                   *                                                                              *
                   * Preserves X/Y registers.                                                     *
                   ********************************************************************************
                   • Clear variables
                   pageflg       .var    $00    {addr/1}
                   xc            .var    $01    {addr/1}
                   yc            .var    $02    {addr/1}
                   back          .var    $03    {addr/1}
                   evenc         .var    $04    {addr/1}
                   oddc          .var    $05    {addr/1}
                   hptr          .var    $07    {addr/2}

6906: 8a           DITHER1       txa
6907: 48                         pha
6908: a5 02                      lda     yc              ;start with the Y-coord
690a: a6 04                      ldx     evenc           ;check the even color
690c: f0 0c                      beq     L691A           ;black, use checkerboard
690e: e0 05                      cpx     #color_white    ;white?
6910: f0 08                      beq     L691A           ;yes, use checkerboard pattern
6912: a6 05                      ldx     oddc            ;check the odd color
6914: f0 04                      beq     L691A           ;black, use checkerboard
6916: e0 05                      cpx     #color_white    ;white?
6918: d0 02                      bne     L691C           ;yes, use checkerboard
691a: 45 01        L691A         eor     xc              ;factor in the X coord to get checkerboard
691c: 29 01        L691C         and     #$01            ;only low bit matters
691e: aa                         tax                     ;X=0 or 1
691f: b5 04                      lda     evenc,x         ;load evenc or oddc
6921: 85 03                      sta     back            ;set as color to draw
6923: 4c 28 69                   jmp     Plt2

                   ********************************************************************************
                   * PLT - plot a point and return the current color.                             *
                   *                                                                              *
                   * On entry:                                                                    *
                   *                                                                              *
                   *   $00 = hi-res page (zero for page 1, nonzero for page 2)                    *
                   *   $01 = X-coord [0,139]                                                      *
                   *   $02 = Y-coord [0,191]                                                      *
                   *   $03 = $80=no plot, 0-5=color to draw                                       *
                   *                                                                              *
                   * On exit:                                                                     *
                   *   $03 = screen color (0-5) (will be the new color if we're in draw mode)     *
                   *                                                                              *
                   * Preserves X/Y registers.                                                     *
                   ********************************************************************************
                   screen_bit    .var    $06    {addr/1}
                   cflag         .var    $09    {addr/2}

6926: 8a           PLT1          txa
6927: 48                         pha
6928: 98           Plt2          tya
6929: 48                         pha
692a: 20 c5 69                   jsr     SetRowBase      ;set $07-08 as hi-res pointer
692d: a6 03                      ldx     back            ;get color
692f: 30 0a                      bmi     L693B           ;not drawing, branch
6931: bd d8 69                   lda     color_flag_0,x  ;get color flags for the two bits
6934: 85 09                      sta     cflag
6936: bd de 69                   lda     color_flag_1,x
6939: 85 0a                      sta     cflag+1
693b: a6 01        L693B         ldx     xc
693d: bc 00 6f                   ldy     div7_tab,x      ;get byte offset
6940: bd 00 6e                   lda     bit_tab,x       ;get bit offset (low bit of pair)
6943: 85 06                      sta     screen_bit
                   ; We want to read/write two hi-res bits, so we loop through here twice.
6945: a2 00                      ldx     #$00            ;first bit
6947: a5 06        BitLoop       lda     screen_bit
6949: 24 03                      bit     back            ;are we writing?
694b: 10 16                      bpl     PlotWrite       ;yes, branch
                   ; Just reading the screen.
694d: 31 07                      and     (hptr),y        ;test screen bit
694f: f0 36                      beq     BitLoopBottom   ;not set
6951: 8a                         txa                     ;0 or 1
6952: 38                         sec                     ;will add +1 or +2
6953: 65 03                      adc     back            ;so this sets bit 0 or bit 1
6955: 85 03                      sta     back
6957: b1 07                      lda     (hptr),y        ;check hi bit
6959: 10 2c                      bpl     BitLoopBottom   ;not set, branch
695b: a5 03                      lda     back            ;set bit 2 if the hi-res pixel's high bit was set
695d: 09 04                      ora     #$04
695f: 85 03                      sta     back
6961: d0 24                      bne     BitLoopBottom

                   ; Draw the pixel.
6963: 49 ff        PlotWrite     eor     #$ff            ;reverse screen bit to form mask
6965: 31 07                      and     (hptr),y        ;AND with screen data
6967: 91 07                      sta     (hptr),y        ;store, clearing previous value at that bit
6969: b5 09                      lda     cflag,x         ;get color flag 0 or 1
696b: f0 1a                      beq     BitLoopBottom   ;zero, don't need to set pixel or high bit
696d: a5 06                      lda     screen_bit      ;nonzero, set the appropriate bit in the pixel
696f: 11 07                      ora     (hptr),y
6971: 91 07                      sta     (hptr),y
6973: a5 09                      lda     cflag           ;is it black or white?
6975: c5 0a                      cmp     cflag+1         ;(want black/white to match hi bit of adjacent color)
6977: f0 0e                      beq     BitLoopBottom   ;yes, leave high bit alone
6979: b1 07                      lda     (hptr),y        ;not black or white, so we need to set high bit
697b: 29 7f                      and     #$7f            ;clear whatever's there now
697d: 91 07                      sta     (hptr),y
697f: b5 09                      lda     cflag,x         ;get high bit from color flag
6981: 29 80                      and     #$80
6983: 11 07                      ora     (hptr),y
6985: 91 07                      sta     (hptr),y        ;set that on the screen
6987: e8           BitLoopBottom inx
6988: e0 02                      cpx     #$02            ;have we done it twice?
698a: f0 0b                      beq     BitLoopDone     ;yes, bail
698c: 06 06                      asl     screen_bit      ;no, shift screen bit to next position
698e: 10 b7                      bpl     BitLoop         ;didn't shift into high bit, loop
6990: c8                         iny                     ;shifted into high bit, move on to next byte
6991: a9 01                      lda     #$01            ;and reset bit to low bit
6993: 85 06                      sta     screen_bit
6995: d0 b0                      bne     BitLoop         ;(always)

6997: a5 03        BitLoopDone   lda     back            ;were we writing?
6999: 10 08                      bpl     L69A3           ;yes, bail
699b: 29 07                      and     #$07            ;no, do a color lookup
699d: aa                         tax
699e: bd e4 69                   lda     bits_to_color,x ;convert 00000HBA to 0-5
69a1: 85 03                      sta     back
69a3: 68           L69A3         pla
69a4: a8                         tay
69a5: 68                         pla
69a6: aa                         tax
69a7: 60                         rts

69a8: 08 29 07 aa+               .junk   29

                   ; 
                   ; Sets $07-08 as the hi-res base pointer for the row in "yc".
                   ; 
69c5: a4 02        SetRowBase    ldy     yc
69c7: b9 00 6c                   lda     ytable_lo,y
69ca: 85 07                      sta     hptr
69cc: a5 00                      lda     pageflg         ;0 for page 1, nonzero for page 2
69ce: f0 02                      beq     L69D2
69d0: a9 60                      lda     #$60            ;configure for page 2
69d2: 59 00 6d     L69D2         eor     ytable_hi,y
69d5: 85 08                      sta     hptr+1
69d7: 60                         rts

                   ; These bytes have three possible values.  They're used by PLT to figure out
                   ; which bits to set on the hi-res screen for a given color (0-5).
                   ; 
                   ;  $00 = don't set this bit
                   ;  $7f = set this bit, clear high bit of byte
                   ;  $ff = set this bit, set high bit of byte
                   ; 
                   ; Each hi-res color (in our 140x192 screen) requires two bits per pixel.  One
                   ; bit comes from each table.
69d8: 00 7f 00 ff+ color_flag_0  .bulk   007f00ff00ff
69de: 00 00 7f 00+ color_flag_1  .bulk   00007f00ffff
                   ; 
                   ; Converts a bit pattern to a color, 0-5.
                   ; 
                   ; Index is a 3-bit value 00000HBA, where A is set if the first bit of the hi-res
                   ; pixel was set, B is set if the second bit of the hi-res pixel was set, and H
                   ; is set if the high bit of at least one of the bytes with a pixel was set. 
                   ; (Remember that we're treating the screen as being 140 pixels across, so it's
                   ; two bits per pixel.)
69e4: 00           bits_to_color .dd1    color_black
69e5: 01                         .dd1    color_purple
69e6: 02                         .dd1    color_green
69e7: 05                         .dd1    color_white
69e8: 00                         .dd1    color_black
69e9: 03                         .dd1    color_blue
69ea: 04                         .dd1    color_orange
69eb: 05                         .dd1    color_white
69ec: 00 ff 01 01+               .align  $0100 (20 bytes)

6a00: 4c 30 6a     SCOPE         jmp     SCOPE1          ;entry point from Applesoft

                   ********************************************************************************
                   * INIT - initialize "micro" / "scope" mode                                     *
                   *                                                                              *
                   * Clears the lo-res screen and enables lo-res graphics mode.                   *
                   *                                                                              *
                   * Preserves X/Y registers.                                                     *
                   ********************************************************************************
                   • Clear variables
                   ptr           .var    $0e    {addr/2}

6a03: 8a           INIT          txa
6a04: 48                         pha
6a05: 98                         tya
6a06: 48                         pha
                   ; Clear lo-res screen to black.
6a07: a2 17                      ldx     #23             ;X = row
6a09: bd 86 6b     ClearLoLoop   lda     lr_ytable_lo,x
6a0c: 85 0e                      sta     ptr
6a0e: bd 9e 6b                   lda     lr_ytable_hi,x
6a11: 85 0f                      sta     ptr+1
6a13: a9 00                      lda     #$00
6a15: a0 27                      ldy     #39             ;Y = column
6a17: 91 0e        L6A17         sta     (ptr),y
6a19: 88                         dey
6a1a: 10 fb                      bpl     L6A17
6a1c: ca                         dex
6a1d: 10 ea                      bpl     ClearLoLoop
                   ; Configure soft-switches for lo-res.
6a1f: 8d 50 c0                   sta     TXTCLR
6a22: 8d 52 c0                   sta     MIXCLR
6a25: 8d 54 c0                   sta     TXTPAGE1
6a28: 8d 56 c0                   sta     LORES
6a2b: 68                         pla
6a2c: a8                         tay
6a2d: 68                         pla
6a2e: aa                         tax
6a2f: 60                         rts

                   ********************************************************************************
                   * SCOPE - display part of the hi-res screen magnified on the lo-res screen.    *
                   *                                                                              *
                   * On entry:                                                                    *
                   *  $00 = X position [0,139]                                                    *
                   *  $01 = Y position [0,191]                                                    *
                   *                                                                              *
                   * Preserves X/Y registers.                                                     *
                   ********************************************************************************
                   • Clear variables
                   xc            .var    $00    {addr/1}
                   yc            .var    $01    {addr/1}
                   col_ctr       .var    $02    {addr/1}
                   row_ctr       .var    $03    {addr/1}
                   saved_byte_off .var   $04    {addr/1}
                   work_ptr_lo   .var    $05    {addr/1}
                   first_bit     .var    $06    {addr/1}
                   hr_byte       .var    $07    {addr/1}
                   hi_in_lo      .var    $08    {addr/1}
                   start_x       .var    $09    {addr/1}
                   hptr          .var    $0c    {addr/2}
                   work_ptr      .var    $0e    {addr/2}

6a30: 8a           SCOPE1        txa
6a31: 48                         pha
6a32: 98                         tya
6a33: 48                         pha
6a34: 38                         sec                     ;left edge is XC - 9
6a35: a5 00                      lda     xc
6a37: e9 09                      sbc     #9
6a39: 85 00                      sta     xc
6a3b: 85 09                      sta     start_x
6a3d: 38                         sec
6a3e: a5 01                      lda     yc              ;top edge is YC - 11
6a40: e9 0b                      sbc     #11
6a42: 85 01                      sta     yc
6a44: a9 00                      lda     #$00
6a46: 85 05                      sta     work_ptr_lo
6a48: 85 0e                      sta     work_ptr
6a4a: a9 70                      lda     #>work_buffer
6a4c: 85 0f                      sta     work_ptr+1      ;out_ptr = work buffer
                   ; 
                   ; Phase 1: convert hi-res pixels to values in the work buffer.
                   ; 
                   ; Each hi-res pixel in our window gets two adjacent values in the work buffer,
                   ; one per bit.  The value is from 0-3, and reflects the state of one bit on the
                   ; pixel plus the high bit of the byte.
                   ; 
                   ; Note: there's a 1-pixel black border on the left and right of the lo-res
                   ; display, presumably to allow the central 2x2 block to be centered on the
                   ; screen.  There's also a 2-pixel black border on the bottom of the screen.
                   ; 
6a4e: a9 17                      lda     #23
6a50: 85 03                      sta     row_ctr
6a52: a9 26        RowLoop       lda     #38
6a54: 85 02                      sta     col_ctr
6a56: a6 01                      ldx     yc              ;get the Y-coord
6a58: e0 c0                      cpx     #192            ;did we wrap off the top?
6a5a: b0 67                      bcs     OffEdge         ;yes, bail
6a5c: bd 00 6c                   lda     ytable_lo,x     ;get the hi-res row base
6a5f: 85 0c                      sta     hptr
6a61: bd 00 6d                   lda     ytable_hi,x
6a64: 85 0d                      sta     hptr+1
6a66: a6 00                      ldx     xc              ;get the X-coord
6a68: e0 8c                      cpx     #140            ;did we wrap around to the left when subtracting?
6a6a: 90 18                      bcc     ScanPixel       ;no, scan it
                   ; We're off the left edge, so just fill in black until we get on the screen.
6a6c: a4 05                      ldy     work_ptr_lo
6a6e: a9 00                      lda     #$00
6a70: 91 0e        OffLeftLoop   sta     (work_ptr),y
6a72: c8                         iny
6a73: 91 0e                      sta     (work_ptr),y
6a75: c8                         iny
6a76: d0 02                      bne     L6A7A
6a78: e6 0f                      inc     work_ptr+1
6a7a: c6 02        L6A7A         dec     col_ctr
6a7c: c6 02                      dec     col_ctr
6a7e: e8                         inx
6a7f: d0 ef                      bne     OffLeftLoop
6a81: 84 05                      sty     work_ptr_lo
6a83: 18                         clc
                   ; Get the color of a pixel.  X coordinate in X-reg, carry flag is clear.
6a84: bd 00 6e     ScanPixel     lda     bit_tab,x       ;get first hi-res pixel bit
6a87: 85 06                      sta     first_bit
6a89: bc 00 6f                   ldy     div7_tab,x      ;get byte offset
6a8c: a6 02                      ldx     col_ctr         ;lo-res column counter
6a8e: b1 0c        L6A8E         lda     (hptr),y        ;get hi-res byte
6a90: 85 07                      sta     hr_byte
6a92: 29 80                      and     #$80            ;clear everything but the hi bit
6a94: 2a                         rol     A               ;roll it into the low bit
6a95: 2a                         rol     A               ;(note carry was clear)
6a96: 85 08                      sta     hi_in_lo
6a98: c8                         iny
6a99: 84 04                      sty     saved_byte_off
6a9b: a4 05                      ldy     work_ptr_lo
6a9d: a5 07        L6A9D         lda     hr_byte         ;get pixel byte
6a9f: 25 06                      and     first_bit       ;mask off everything but interesting bit
6aa1: f0 02                      beq     L6AA5           ;bit not set, branch
6aa3: a9 02                      lda     #$02            ;bit set, use $02 regardless of bit position
6aa5: 05 08        L6AA5         ora     hi_in_lo        ;add high bit (so now value is 0-3)
6aa7: 91 0e                      sta     (work_ptr),y    ;save that off
6aa9: c8                         iny                     ;advance work ptr
6aaa: d0 02                      bne     L6AAE
6aac: e6 0f                      inc     work_ptr+1
6aae: ca           L6AAE         dex                     ;decrement column counter
6aaf: f0 21                      beq     L6AD2           ;bail when we reach column 0
6ab1: 06 06                      asl     first_bit       ;shift to the next bit in the pixel
6ab3: 10 e8                      bpl     L6A9D           ;still in same byte, repeat
6ab5: 84 05                      sty     work_ptr_lo
6ab7: a9 01                      lda     #$01            ;move to next byte, reset mask to bit 0
6ab9: 85 06                      sta     first_bit
6abb: a4 04                      ldy     saved_byte_off
6abd: c0 28                      cpy     #40             ;off right edge of hi-res screen?
6abf: 90 cd                      bcc     L6A8E           ;nope, keep going
6ac1: 86 02                      stx     col_ctr         ;yes, go into "off edge" code
                   ; We're off the edge, to the right or the bottom.  Fill out the row with black
                   ; pixels.
6ac3: a4 05        OffEdge       ldy     work_ptr_lo
6ac5: a9 00                      lda     #$00
6ac7: 91 0e        L6AC7         sta     (work_ptr),y
6ac9: c8                         iny
6aca: d0 02                      bne     L6ACE
6acc: e6 0f                      inc     work_ptr+1
6ace: c6 02        L6ACE         dec     col_ctr         ;decrement the column counter
6ad0: d0 f5                      bne     L6AC7           ;not end of row yet, branch
6ad2: 84 05        L6AD2         sty     work_ptr_lo
6ad4: a5 09                      lda     start_x         ;reset X-coord
6ad6: 85 00                      sta     xc
6ad8: e6 01                      inc     yc              ;advance to next row
6ada: c6 03                      dec     row_ctr         ;are we done?
6adc: f0 22                      beq     Scope2          ;yes, move to rendering
6ade: 4c 52 6a                   jmp     RowLoop         ;no, loop

6ae1: 00 c6 03 f0+               .align  $0100 (31 bytes)

                   ; Phase 2: render the contents of the work buffer on the lo-res screen.
                   ; 
                   ; The values in the work buffer are from 0-3.  0/2 indicates that the
                   ; corresponding hi-res bit was set, +1 if the high bit in the byte was set.
                   work_ptr      .var    $0c    {addr/2}
                   lr_ptr        .var    $0e    {addr/2}

6b00: a9 01        Scope2        lda     #$01            ;left edge; 1-pixel boundary at sides
6b02: 85 00                      sta     xc
6b04: a9 00                      lda     #$00            ;no border at top
6b06: 85 01                      sta     yc
6b08: 85 04                      sta     saved_byte_off
6b0a: 85 0c                      sta     work_ptr
6b0c: a9 70                      lda     #>work_buffer
6b0e: 85 0d                      sta     work_ptr+1
6b10: a6 01                      ldx     yc              ;get lo-res screen row base
6b12: bd 86 6b     L6B12         lda     lr_ytable_lo,x
6b15: 85 0e                      sta     lr_ptr
6b17: bd 9e 6b                   lda     lr_ytable_hi,x
6b1a: 85 0f                      sta     lr_ptr+1
6b1c: a4 04        DrawLoLoop    ldy     saved_byte_off
6b1e: b1 0c                      lda     (work_ptr),y    ;get the first value
6b20: c8                         iny
6b21: 0a                         asl     A               ;shift it over
6b22: 0a                         asl     A
6b23: 11 0c                      ora     (work_ptr),y    ;add in the second value
6b25: c8                         iny                     ;advance work ptr
6b26: d0 02                      bne     L6B2A
6b28: e6 0d                      inc     work_ptr+1
6b2a: 84 04        L6B2A         sty     saved_byte_off
6b2c: aa                         tax                     ;put color value (0-15) in X
6b2d: bd b6 6b                   lda     lr_color_map,x  ;convert it to a lo-res color
6b30: a4 00                      ldy     xc
6b32: 91 0e                      sta     (lr_ptr),y      ;plot 2x2 pixel (two bytes wide)
6b34: c8                         iny
6b35: 91 0e                      sta     (lr_ptr),y
6b37: c8                         iny
6b38: 84 00                      sty     xc
6b3a: c0 27                      cpy     #39             ;end of row?
6b3c: d0 de                      bne     DrawLoLoop      ;not yet, loop
6b3e: a9 01                      lda     #$01            ;reset X-coord
6b40: 85 00                      sta     xc
6b42: e6 01                      inc     yc              ;advance to next row
6b44: a6 01                      ldx     yc
6b46: e0 17                      cpx     #23             ;done? (leaves 1-pixel boundary at bottom)
6b48: d0 c8                      bne     L6B12           ;no, loop
                   ; Draw crosshairs.  It flickers a little because, on each loop, we draw the hi-
                   ; res colors and then slam the crosshairs down.
6b4a: a9 dd                      lda     #$dd            ;two pixels, color=13 (yellow)
6b4c: a2 04                      ldx     #$04
6b4e: 9d b5 05     L6B4E         sta     $05b5,x         ;hard-wired screen positions
6b51: 9d be 05                   sta     $05be,x
6b54: ca                         dex
6b55: 10 f7                      bpl     L6B4E
6b57: a2 01                      ldx     #$01
6b59: 9d 3b 04     L6B59         sta     $043b,x
6b5c: 9d bb 04                   sta     $04bb,x
6b5f: 9d bb 06                   sta     $06bb,x
6b62: 9d 3b 07                   sta     $073b,x
6b65: ca                         dex
6b66: 10 f1                      bpl     L6B59
                   ; Add "half-pixel" crosshair gap.  The hi-res pixel at the center is a 2x2 lo-
                   ; res block.  We create a gap of 1 lo-res block between it and the crosshair. 
                   ; For the vertical line, that means we're not writing a full byte, because each
                   ; text byte holds two lo-res blocks.
6b68: a2 01                      ldx     #$01
6b6a: bd 3b 05     L6B6A         lda     $053b,x         ;draw one pixel with color=13
6b6d: 29 f0                      and     #$f0            ; leave other pixel alone
6b6f: 09 0d                      ora     #$0d
6b71: 9d 3b 05                   sta     $053b,x
6b74: bd 3b 06                   lda     $063b,x
6b77: 29 0f                      and     #$0f
6b79: 09 d0                      ora     #$d0
6b7b: 9d 3b 06                   sta     $063b,x
6b7e: ca                         dex
6b7f: 10 e9                      bpl     L6B6A
6b81: 68                         pla
6b82: a8                         tay
6b83: 68                         pla
6b84: aa                         tax
6b85: 60                         rts

                   ; Low-res row address, low byte.
6b86: 00 80 00 80+ lr_ytable_lo  .bulk   008000800080008028a828a828a828a850d050d050d050d0
                   ; Low-res row address, high byte.
6b9e: 04 04 05 05+ lr_ytable_hi  .bulk   040405050606070704040505060607070404050506060707
                   ; 
                   ; Map hi-res pixel values to lo-res colors.
                   ; 
                   ; Index is AHBH, where A and B are the hi-res pixel values, and H is the high
                   ; bit of the hi-res byte.  For example, green is 0010, purple is 1010, orange is
                   ; 0111, blue is 1101.
                   ; 
                   ; Some pixels straddle two bytes and potentially have different values for the
                   ; high bit in each.  Each color thus has two entries.
                   ; 
6bb6: 00           lr_color_map  .dd1    $00             ;0000 lo-res color 0 = black
6bb7: 00                         .dd1    $00             ;0001
6bb8: cc                         .dd1    $cc             ;0010 12 = light green
6bb9: 99                         .dd1    $99             ;0011 9 = orange
6bba: 00                         .dd1    $00             ;0100
6bbb: 00                         .dd1    $00             ;0101
6bbc: cc                         .dd1    $cc             ;0110
6bbd: 99                         .dd1    $99             ;0111
6bbe: 33                         .dd1    $33             ;1000 3 = purple
6bbf: 33                         .dd1    $33             ;1001
6bc0: ff                         .dd1    $ff             ;1010 15 = white
6bc1: ff                         .dd1    $ff             ;1011
6bc2: 66                         .dd1    $66             ;1100 6 = medium blue
6bc3: 66                         .dd1    $66             ;1101
6bc4: ff                         .dd1    $ff             ;1110
6bc5: ff                         .dd1    $ff             ;1111
6bc6: 00 ff ff 00+               .align  $0100 (58 bytes)
                   ; Hi-res row base address, low byte.
6c00: 00 00 00 00+ ytable_lo     .bulk   0000000000000000808080808080808000000000000000008080808080808080
                                  +      0000000000000000808080808080808000000000000000008080808080808080
                                  +      2828282828282828a8a8a8a8a8a8a8a82828282828282828a8a8a8a8a8a8a8a8
                                  +      2828282828282828a8a8a8a8a8a8a8a82828282828282828a8a8a8a8a8a8a8a8
                                  +      5050505050505050d0d0d0d0d0d0d0d05050505050505050d0d0d0d0d0d0d0d0
                                  +      5050505050505050d0d0d0d0d0d0d0d05050505050505050d0d0d0d0d0d0d0d0

                   ********************************************************************************
                   * CLEAN -- set all non-white pixels to black.                                  *
                   *                                                                              *
                   * Preserves X/Y registers.                                                     *
                   ********************************************************************************
                   • Clear variables
                   xc            .var    $01    {addr/1}
                   yc            .var    $02    {addr/1}
                   back          .var    $03    {addr/1}

6cc0: 8a           CLEAN         txa
6cc1: 48                         pha
6cc2: 98                         tya
6cc3: 48                         pha
6cc4: a0 00                      ldy     #$00
6cc6: a2 00        L6CC6         ldx     #$00
6cc8: 86 01        L6CC8         stx     xc
6cca: 84 02                      sty     yc
6ccc: a9 80                      lda     #$80            ;read only
6cce: 85 03                      sta     back
6cd0: 20 03 69                   jsr     PLT             ;get current pixel color
6cd3: a5 03                      lda     back
6cd5: c9 05                      cmp     #color_white    ;is it a white pixel?
6cd7: f0 07                      beq     L6CE0           ;yes, leave it alone
6cd9: a9 00                      lda     #color_black    ;no, clear it
6cdb: 85 03                      sta     back
6cdd: 20 03 69                   jsr     PLT             ;draw black pixel
6ce0: e8           L6CE0         inx
6ce1: e0 8c                      cpx     #140            ;end of line?
6ce3: d0 e3                      bne     L6CC8           ;no, continue
6ce5: c8                         iny
6ce6: c0 c0                      cpy     #192            ;end of screen?
6ce8: d0 dc                      bne     L6CC6           ;no, continue
6cea: 68                         pla
6ceb: a8                         tay
6cec: 68                         pla
6ced: aa                         tax
6cee: 60                         rts

6cef: 20 40 01 02+               .align  $0100 (17 bytes)
                   ; Hi-res row base address, high byte.
6d00: 20 24 28 2c+ ytable_hi     .bulk   2024282c3034383c2024282c3034383c2125292d3135393d2125292d3135393d
                                  +      22262a2e32363a3e22262a2e32363a3e23272b2f33373b3f23272b2f33373b3f
                                  +      2024282c3034383c2024282c3034383c2125292d3135393d2125292d3135393d
                                  +      22262a2e32363a3e22262a2e32363a3e23272b2f33373b3f23272b2f33373b3f
                                  +      2024282c3034383c2024282c3034383c2125292d3135393d2125292d3135393d
                                  +      22262a2e32363a3e22262a2e32363a3e23272b2f33373b3f23272b2f33373b3f

                   ********************************************************************************
                   * NEG -- reverse colors on entire hi-res screen                                *
                   *                                                                              *
                   * Does a top-to-bottom operation to avoid the Venetian-blind look.             *
                   ********************************************************************************
                   • Clear variables
                   xc            .var    $01    {addr/1}
                   yc            .var    $02    {addr/1}
                   hptr          .var    $07    {addr/2}

6dc0: 8a           NEG           txa
6dc1: 48                         pha
6dc2: 98                         tya
6dc3: 48                         pha
6dc4: a2 00                      ldx     #$00            ;start at the top
6dc6: 86 02        L6DC6         stx     yc
6dc8: 20 c5 69                   jsr     SetRowBase      ;get address in hptr
6dcb: a0 27                      ldy     #39             ;for each byte in the row
6dcd: b1 07        L6DCD         lda     (hptr),y
6dcf: 49 ff                      eor     #$ff            ;reverse colors
6dd1: 91 07                      sta     (hptr),y
6dd3: 88                         dey
6dd4: 10 f7                      bpl     L6DCD
6dd6: e8                         inx                     ;next row
6dd7: e0 c0                      cpx     #192            ;done?
6dd9: d0 eb                      bne     L6DC6
6ddb: 68                         pla
6ddc: a8                         tay
6ddd: 68                         pla
6dde: aa                         tax
6ddf: 60                         rts

6de0: 60 02 d0 dc+               .align  $0100 (32 bytes)
                   ; Maps X coordinate [0,139] to bit.
6e00: 01 04 10 40+ bit_tab       .bulk   0104104002082001041040020820010410400208200104104002082001041040
                                  +      0208200104104002082001041040020820010410400208200104104002082001
                                  +      0410400208200104104002082001041040020820010410400208200104104002
                                  +      0820010410400208200104104002082001041040020820010410400208200104
                                  +      104002082001041040020820
6e8c: 00 00 00 00+               .align  $0100 (116 bytes)
                   ; Maps X coordinate [0,139] to byte [0,39].
6f00: 00 00 00 00+ div7_tab      .bulk   0000000001010102020202030303040404040505050606060607070708080808
                                  +      0909090a0a0a0a0b0b0b0c0c0c0c0d0d0d0e0e0e0e0f0f0f1010101011111112
                                  +      1212121313131414141415151516161616171717181818181919191a1a1a1a1b
                                  +      1b1b1c1c1c1c1d1d1d1e1e1e1e1f1f1f20202020212121222222222323232424
                                  +      242425252526262626272727
6f8c: 00 00 00 00+               .align  $0100 (116 bytes)

Symbol Table

CLEAN$6cc0
DITHER$6900
FILL$6800
INIT$6a03
NEG$6dc0
PLT$6903
SCOPE$6a00