]> git.sur5r.net Git - cc65/blob - libsrc/c128/tgi/c128-hi.s
Made the VIC-IIe TGI driver put its bitmap behind the ROMs.
[cc65] / libsrc / c128 / tgi / c128-hi.s
1 ;
2 ; Graphics driver for the 320x200x2 mode on the C128.
3 ;
4 ; Based on Stephen L. Judd's GRLIB code.
5 ;
6 ; 2018-03-13, Sven Klose
7 ; 2018-07-22, Scott Hutter
8 ; 2018-07-28, Greg King
9 ;
10
11         .include        "zeropage.inc"
12
13         .include        "tgi-kernel.inc"
14         .include        "tgi-error.inc"
15         .include        "c128.inc"
16
17         .macpack        generic
18         .macpack        module
19
20
21 ; ------------------------------------------------------------------------
22 ; Header. Includes jump table and constants.
23
24         module_header   _c128_hi_tgi
25
26 ; First part of the header is a structure that has a magic and defines the
27 ; capabilities of the driver
28
29         .byte   $74, $67, $69           ; "tgi"
30         .byte   TGI_API_VERSION         ; TGI API version number
31         .addr   $0000                   ; Library reference
32         .word   320                     ; X resolution
33         .word   200                     ; Y resolution
34         .byte   2                       ; Number of drawing colors
35         .byte   1                       ; Number of screens available
36         .byte   8                       ; System font X size
37         .byte   8                       ; System font Y size
38         .word   $00D4                   ; Aspect ratio (based on 4/3 display)
39         .byte   0                       ; TGI driver flags
40
41 ; Next comes the jump table. With the exception of IRQ, all entries must be
42 ; valid and may point to an RTS for test versions (function not implemented).
43
44         .addr   INSTALL
45         .addr   UNINSTALL
46         .addr   INIT
47         .addr   DONE
48         .addr   GETERROR
49         .addr   CONTROL
50         .addr   CLEAR
51         .addr   SETVIEWPAGE
52         .addr   SETDRAWPAGE
53         .addr   SETCOLOR
54         .addr   SETPALETTE
55         .addr   GETPALETTE
56         .addr   GETDEFPALETTE
57         .addr   SETPIXEL
58         .addr   GETPIXEL
59         .addr   LINE
60         .addr   BAR
61         .addr   TEXTSTYLE
62         .addr   OUTTEXT
63
64 ; ------------------------------------------------------------------------
65 ; Data.
66
67 ; Variables mapped to the zero page segment variables. Some of these are
68 ; used for passing parameters to the driver.
69
70 X1              := ptr1
71 Y1              := ptr2
72 X2              := ptr3
73 Y2              := ptr4
74 TEXT            := ptr3
75
76 TEMP            := tmp4
77 TEMP2           := sreg
78 POINT           := regsave
79
80 CHUNK           := X2           ; Used in the line routine
81 OLDCHUNK        := X2+1         ; Ditto
82
83 ; Absolute variables used in the code
84
85 .bss
86
87 ERROR:          .res    1       ; Error code
88 PALETTE:        .res    2       ; The current palette
89
90 BITMASK:        .res    1       ; $00 = clear, $FF = set pixels
91
92 ; Line routine stuff
93 DX:             .res    2
94 DY:             .res    2
95
96 ; BAR variables
97 X1SAVE:         .res    2
98 Y1SAVE:         .res    1
99 X2SAVE:         .res    2
100 Y2SAVE:         .res    1
101
102 ; Text output stuff
103 TEXTMAGX:       .res    1
104 TEXTMAGY:       .res    1
105 TEXTDIR:        .res    1
106
107 ; Constants and tables
108
109 .rodata
110
111 DEFPALETTE:     .byte   $00, $01        ; White on black
112 PALETTESIZE     = * - DEFPALETTE
113
114 BITTAB:         .byte   $80,$40,$20,$10,$08,$04,$02,$01
115 BITCHUNK:       .byte   $FF,$7F,$3F,$1F,$0F,$07,$03,$01
116
117 CHARROM         := $D000                ; Character ROM base address
118
119 VBASE           := $C000                ; Video memory base address
120 CBASE           := $E000                ; Color memory base address
121
122 .code
123
124 ; ------------------------------------------------------------------------
125 ; INSTALL routine. Is called after the driver is loaded into memory. May
126 ; initialize anything that has to be done just once. Is probably empty
127 ; most of the time.
128 ;
129 ; Must set an error code: NO
130 ;
131
132 INSTALL:
133 ;       rts                     ; fall through
134
135
136 ; ------------------------------------------------------------------------
137 ; UNINSTALL routine. Is called before the driver is removed from memory. May
138 ; clean up anything done by INSTALL but is probably empty most of the time.
139 ;
140 ; Must set an error code: NO
141 ;
142
143 UNINSTALL:
144         rts
145
146
147 ; ------------------------------------------------------------------------
148 ; INIT: Changes an already installed device from text mode to graphics
149 ; mode.
150 ; Note that INIT/DONE may be called multiple times while the driver
151 ; is loaded, while INSTALL is only called once, so any code that is needed
152 ; to initializes variables and so on must go here. Setting palette and
153 ; clearing the screen is not needed because this is called by the graphics
154 ; kernel later.
155 ; The graphics kernel will never call INIT when a graphics mode is already
156 ; active, so there is no need to protect against that.
157 ;
158 ; Must set an error code: YES
159 ;
160
161 INIT:
162
163 ; Initialize variables.
164
165         ldx     #$FF            ; Foreground color
166         stx     BITMASK
167
168 ; Switch into graphics mode.
169
170 ; Select a video bank:
171 ; bank 0 = $03 ($0000-$3FFF) (default)
172 ; bank 1 = $02 ($4000-$7FFF)
173 ; bank 2 = $01 ($8000-$BFFF)
174 ; bank 3 = $00 ($C000-$FFFF) (TGI)
175
176         lda     CIA2_PRA
177         and     #<~$03          ; Bank 3
178         sta     CIA2_PRA
179
180         lda     #$80            ; color-map at $E000, bitmap at $C000
181         sta     VM2
182
183 ; Make the VIC-IIe read RAM instead of the font ROM.
184
185         lda     #%00000100
186         sta     CHARDIS
187
188 ; Switch to bitmap mode.
189
190         lda     #%00100000
191         sta     GRAPHM
192
193         lda     #TGI_ERR_OK
194         sta     ERROR
195         rts
196
197 ; ------------------------------------------------------------------------
198 ; DONE: Will be called to switch the graphics device back into text mode.
199 ; The graphics kernel will never call DONE when no graphics mode is active,
200 ; so there is no need to protect against that.
201 ;
202 ; Must set an error code: NO
203 ;
204
205 DONE:
206
207 ; Select the text video bank.
208
209         lda     CIA2_PRA
210         ora     #$03            ; Bank 0
211         sta     CIA2_PRA
212
213 ; Make the VIC-IIe read the font ROM instead of RAM.
214
215         lda     #%00000000
216         sta     CHARDIS
217
218         ;lda    #%00000000      ; Switch back to text mode
219         sta     GRAPHM
220
221 ; Restore a value that's needed by BASIC's GRAPHIC 1 statement.
222
223         lda     #$78            ; color-map at $1C00, bitmap at $2000
224         sta     VM2
225         rts
226
227 ; ------------------------------------------------------------------------
228 ; GETERROR: Return the error code in A and clear it.
229
230 GETERROR:
231         ldx     #TGI_ERR_OK
232         lda     ERROR
233         stx     ERROR
234         rts
235
236 ; ------------------------------------------------------------------------
237 ; CONTROL: Platform/driver specific entry point.
238 ;
239 ; Must set an error code: YES
240 ;
241
242 CONTROL:
243         lda     #TGI_ERR_INV_FUNC
244         sta     ERROR
245         rts
246
247 ; ------------------------------------------------------------------------
248 ; CLEAR: Clears the screen.
249 ;
250 ; Must set an error code: NO
251 ;
252
253 CLEAR:
254         ldy     #$00
255         tya
256         ldx     #MMU_CFG_RAM0
257         sei
258         stx     MMU_CR
259 @L1:    sta     VBASE+$0000,y
260         sta     VBASE+$0100,y
261         sta     VBASE+$0200,y
262         sta     VBASE+$0300,y
263         sta     VBASE+$0400,y
264         sta     VBASE+$0500,y
265         sta     VBASE+$0600,y
266         sta     VBASE+$0700,y
267         sta     VBASE+$0800,y
268         sta     VBASE+$0900,y
269         sta     VBASE+$0A00,y
270         sta     VBASE+$0B00,y
271         sta     VBASE+$0C00,y
272         sta     VBASE+$0D00,y
273         sta     VBASE+$0E00,y
274         sta     VBASE+$0F00,y
275         sta     VBASE+$1000,y
276         sta     VBASE+$1100,y
277         sta     VBASE+$1200,y
278         sta     VBASE+$1300,y
279         sta     VBASE+$1400,y
280         sta     VBASE+$1500,y
281         sta     VBASE+$1600,y
282         sta     VBASE+$1700,y
283         sta     VBASE+$1800,y
284         sta     VBASE+$1900,y
285         sta     VBASE+$1A00,y
286         sta     VBASE+$1B00,y
287         sta     VBASE+$1C00,y
288         sta     VBASE+$1D00,y
289         sta     VBASE+$1E00,y
290         sta     VBASE+$1F00,y
291         iny
292         bne     @L1
293         ldx     #MMU_CFG_CC65
294         stx     MMU_CR
295         cli
296         rts
297
298 ; ------------------------------------------------------------------------
299 ; SETVIEWPAGE: Set the visible page. Called with the new page in A (0..n).
300 ; The page number is already checked to be valid by the graphics kernel.
301 ;
302 ; Must set an error code: NO (will only be called if page ok)
303 ;
304
305 SETVIEWPAGE:
306 ;       rts                     ; fall through
307
308 ; ------------------------------------------------------------------------
309 ; SETDRAWPAGE: Set the drawable page. Called with the new page in A (0..n).
310 ; The page number is already checked to be valid by the graphics kernel.
311 ;
312 ; Must set an error code: NO (will only be called if page ok)
313 ;
314
315 SETDRAWPAGE:
316         rts
317
318 ; ------------------------------------------------------------------------
319 ; SETCOLOR: Set the drawing color (in A). The new color is already checked
320 ; to be in a valid range (0..maxcolor-1).
321 ;
322 ; Must set an error code: NO (will only be called if color ok)
323 ;
324
325 SETCOLOR:
326         tax
327         beq     @L1
328         lda     #$FF
329 @L1:    sta     BITMASK
330         rts
331
332 ; ------------------------------------------------------------------------
333 ; SETPALETTE: Set the palette (not available with all drivers/hardware).
334 ; A pointer to the palette is passed in ptr1. Must set an error if palettes
335 ; are not supported
336 ;
337 ; Must set an error code: YES
338 ;
339
340 SETPALETTE:
341         ldy     #PALETTESIZE - 1
342 @L1:    lda     (ptr1),y        ; Copy the palette
343         and     #$0F            ; Make a valid color
344         sta     PALETTE,y
345         dey
346         bpl     @L1
347
348 ; Get the color entries from the palette
349
350         lda     PALETTE+1       ; Foreground color
351         asl     a
352         asl     a
353         asl     a
354         asl     a
355         ora     PALETTE         ; Background color
356
357 ; Initialize the color map with the new color settings (it is below the
358 ; Kernal ROM).
359
360         ldy     #$00
361         ldx     #MMU_CFG_RAM0
362         sei
363         stx     MMU_CR
364 @L2:    sta     CBASE+$0000,y
365         sta     CBASE+$0100,y
366         sta     CBASE+$0200,y
367         sta     CBASE+$02e8,y
368         iny
369         bne     @L2
370         ldx     #MMU_CFG_CC65
371         stx     MMU_CR
372         cli
373
374 ; Done, reset the error code
375
376         lda     #TGI_ERR_OK
377         sta     ERROR
378         rts
379
380 ; ------------------------------------------------------------------------
381 ; GETPALETTE: Return the current palette in A/X. Even drivers that cannot
382 ; set the palette should return the default palette here, so there's no
383 ; way for this function to fail.
384 ;
385 ; Must set an error code: NO
386 ;
387
388 GETPALETTE:
389         lda     #<PALETTE
390         ldx     #>PALETTE
391         rts
392
393 ; ------------------------------------------------------------------------
394 ; GETDEFPALETTE: Return the default palette for the driver in A/X. All
395 ; drivers should return something reasonable here, even drivers that don't
396 ; support palettes, otherwise the caller has no way to determine the colors
397 ; of the (not changeable) palette.
398 ;
399 ; Must set an error code: NO (all drivers must have a default palette)
400 ;
401
402 GETDEFPALETTE:
403         lda     #<DEFPALETTE
404         ldx     #>DEFPALETTE
405         rts
406
407 ; ------------------------------------------------------------------------
408 ; SETPIXEL: Draw one pixel at X1/Y1 = ptr1/ptr2 with the current drawing
409 ; color. The coordinates passed to this function are never outside the
410 ; visible screen area, so there is no need for clipping inside this function.
411 ;
412 ; Must set an error code: NO
413 ;
414
415 SETPIXEL:
416         jsr     CALC            ; Calculate coordinates
417
418         lda     #MMU_CFG_RAM0   ; Work behind ROMs
419         sei
420         sta     MMU_CR
421
422         lda     (POINT),Y
423         eor     BITMASK
424         and     BITTAB,X
425         eor     (POINT),Y
426         sta     (POINT),Y
427
428         ldx     #MMU_CFG_CC65
429         stx     MMU_CR
430         cli
431
432         rts
433
434 ; ------------------------------------------------------------------------
435 ; GETPIXEL: Read the color value of a pixel and return it in A/X. The
436 ; coordinates passed to this function are never outside the visible screen
437 ; area, so there is no need for clipping inside this function.
438
439
440 GETPIXEL:
441         jsr     CALC            ; Calculate coordinates
442
443         lda     #MMU_CFG_RAM0   ; Work behind ROMs
444         sei
445         sta     MMU_CR
446
447         lda     (POINT),Y
448         and     BITTAB,X
449         beq     @L1
450         lda     #$01            ; Foreground color
451
452 @L1:    ldy     #MMU_CFG_CC65
453         sty     MMU_CR
454         cli
455         ldx     #$00            ; Clear high byte
456         rts
457
458 ; ------------------------------------------------------------------------
459 ; LINE: Draw a line from X1/Y1 to X2/Y2, where X1/Y1 = ptr1/ptr2 and
460 ; X2/Y2 = ptr3/ptr4 using the current drawing color.
461 ;
462 ; X1,X2 etc. are set up above (x2=LINNUM in particular)
463 ; Format is LINE x2,y2,x1,y1
464 ;
465 ; Must set an error code: NO
466 ;
467
468 LINE:
469
470 @CHECK: lda     X2           ;Make sure x1<x2
471         sec
472         sbc     X1
473         tax
474         lda     X2+1
475         sbc     X1+1
476         bpl     @CONT
477         lda     Y2           ;If not, swap P1 and P2
478         ldy     Y1
479         sta     Y1
480         sty     Y2
481         lda     Y2+1
482         ldy     Y1+1
483         sta     Y1+1
484         sty     Y2+1
485         lda     X1
486         ldy     X2
487         sty     X1
488         sta     X2
489         lda     X2+1
490         ldy     X1+1
491         sta     X1+1
492         sty     X2+1
493         bcc     @CHECK
494
495 @CONT:  sta     DX+1
496         stx     DX
497
498         ldx     #$C8         ;INY
499         lda     Y2           ;Calculate dy
500         sec
501         sbc     Y1
502         tay
503         lda     Y2+1
504         sbc     Y1+1
505         bpl     @DYPOS       ;Is y2>=y1?
506         lda     Y1           ;Otherwise dy=y1-y2
507         sec
508         sbc     Y2
509         tay
510         ldx     #$88         ;DEY
511
512 @DYPOS: sty     DY              ; 8-bit DY -- FIX ME?
513         stx     YINCDEC
514         stx     XINCDEC
515
516         jsr     CALC            ; Set up .X, .Y, and POINT
517         lda     BITCHUNK,X
518         sta     OLDCHUNK
519         sta     CHUNK
520
521         lda     #MMU_CFG_RAM0   ; Work behind ROMs
522         sei
523         sta     MMU_CR
524
525         ldx     DY
526         cpx     DX           ;Who's bigger: dy or dx?
527         bcc     STEPINX      ;If dx, then...
528         lda     DX+1
529         bne     STEPINX
530
531 ;
532 ; Big steps in Y
533 ;
534 ;   To simplify my life, just use PLOT to plot points.
535 ;
536 ;   No more!
537 ;   Added special plotting routine -- cool!
538 ;
539 ;   X is now counter, Y is y-coordinate
540 ;
541 ; On entry, X=DY=number of loop iterations, and Y=
542 ;   Y1 AND #$07
543 STEPINY:
544         lda     #00
545         sta     OLDCHUNK     ;So plotting routine will work right
546         lda     CHUNK
547         lsr                  ;Strip the bit
548         eor     CHUNK
549         sta     CHUNK
550         txa
551         beq     YCONT2       ;If dy=0, it's just a point
552 @CONT:  lsr                  ;Init counter to dy/2
553 ;
554 ; Main loop
555 ;
556 YLOOP:  sta     TEMP
557
558         lda     (POINT),y
559         eor     BITMASK
560         and     CHUNK
561         eor     (POINT),y
562         sta     (POINT),y
563 YINCDEC:
564         iny                  ;Advance Y coordinate
565         cpy     #8
566         bcc     @CONT        ;No prob if Y=0..7
567         jsr     FIXY
568 @CONT:  lda     TEMP         ;Restore A
569         sec
570         sbc     DX
571         bcc     YFIXX
572 YCONT:  dex                  ;X is counter
573         bne     YLOOP
574 YCONT2: lda     (POINT),y    ;Plot endpoint
575         eor     BITMASK
576         and     CHUNK
577         eor     (POINT),y
578         sta     (POINT),y
579         ldx     #MMU_CFG_CC65
580         stx     MMU_CR
581         cli
582         rts
583
584 YFIXX:                    ;x=x+1
585         adc     DY
586         lsr     CHUNK
587         bne     YCONT        ;If we pass a column boundary...
588         ror     CHUNK        ;then reset CHUNK to $80
589         sta     TEMP2
590         lda     POINT        ;And add 8 to POINT
591         adc     #8
592         sta     POINT
593         bcc     @CONT
594         inc     POINT+1
595 @CONT:  lda     TEMP2
596         dex
597         bne     YLOOP
598         beq     YCONT2
599
600 ;
601 ; Big steps in X direction
602 ;
603 ; On entry, X=DY=number of loop iterations, and Y=
604 ;   Y1 AND #$07
605
606 .bss
607 COUNTHI:
608         .byte   $00       ;Temporary counter
609                           ;only used once
610 .code
611 STEPINX:
612         ldx     DX
613         lda     DX+1
614         sta     COUNTHI
615         cmp     #$80
616         ror                  ;Need bit for initialization
617         sta     Y1           ;High byte of counter
618         txa
619         bne     @CONT        ;Could be $100
620         dec     COUNTHI
621 @CONT:  ror
622 ;
623 ; Main loop
624 ;
625 XLOOP:  lsr     CHUNK
626         beq     XFIXC        ;If we pass a column boundary...
627 XCONT1: sbc     DY
628         bcc     XFIXY        ;Time to step in Y?
629 XCONT2: dex
630         bne     XLOOP
631         dec     COUNTHI      ;High bits set?
632         bpl     XLOOP
633
634         lsr     CHUNK        ;Advance to last point
635         jsr     LINEPLOT     ;Plot the last chunk
636         ldx     #MMU_CFG_CC65
637         stx     MMU_CR
638         cli
639         rts
640 ;
641 ; CHUNK has passed a column, so plot and increment pointer
642 ; and fix up CHUNK, OLDCHUNK.
643 ;
644 XFIXC:  sta     TEMP
645         jsr     LINEPLOT
646         lda     #$FF
647         sta     CHUNK
648         sta     OLDCHUNK
649         lda     POINT
650         clc
651         adc     #8
652         sta     POINT
653         lda     TEMP
654         bcc     XCONT1
655         inc     POINT+1
656         jmp     XCONT1
657 ;
658 ; Check to make sure there isn't a high bit, plot chunk,
659 ; and update Y-coordinate.
660 ;
661 XFIXY:  dec     Y1           ;Maybe high bit set
662         bpl     XCONT2
663         adc     DX
664         sta     TEMP
665         lda     DX+1
666         adc     #$FF         ;Hi byte
667         sta     Y1
668
669         jsr     LINEPLOT     ;Plot chunk
670         lda     CHUNK
671         sta     OLDCHUNK
672
673         lda     TEMP
674 XINCDEC:
675         iny                  ;Y-coord
676         cpy     #8           ;0..7 is ok
677         bcc     XCONT2
678         sta     TEMP
679         jsr     FIXY
680         lda     TEMP
681         jmp     XCONT2
682
683 ;
684 ; Subroutine to plot chunks/points (to save a little
685 ; room, gray hair, etc.)
686 ;
687 LINEPLOT:                       ; Plot the line chunk
688         lda     (POINT),Y
689         eor     BITMASK
690         ora     CHUNK
691         and     OLDCHUNK
692         eor     CHUNK
693         eor     (POINT),Y
694         sta     (POINT),Y
695         rts
696
697 ;
698 ; Subroutine to fix up pointer when Y decreases through
699 ; zero or increases through 7.
700 ;
701 FIXY:   cpy     #255         ;Y=255 or Y=8
702         beq     @DECPTR
703
704 @INCPTR:                     ;Add 320 to pointer
705         ldy     #0           ;Y increased through 7
706         lda     POINT
707         adc     #<320
708         sta     POINT
709         lda     POINT+1
710         adc     #>320
711         sta     POINT+1
712         rts
713
714 @DECPTR:                     ;Okay, subtract 320 then
715         ldy     #7           ;Y decreased through 0
716         lda     POINT
717         sec
718         sbc     #<320
719         sta     POINT
720         lda     POINT+1
721         sbc     #>320
722         sta     POINT+1
723         rts
724
725 ; ------------------------------------------------------------------------
726 ; BAR: Draw a filled rectangle with the corners X1/Y1, X2/Y2, where
727 ; X1/Y1 = ptr1/ptr2 and X2/Y2 = ptr3/ptr4 using the current drawing color.
728 ; Contrary to most other functions, the graphics kernel will sort and clip
729 ; the coordinates before calling the driver, so on entry the following
730 ; conditions are valid:
731 ;       X1 <= X2
732 ;       Y1 <= Y2
733 ;       (X1 >= 0) && (X1 < XRES)
734 ;       (X2 >= 0) && (X2 < XRES)
735 ;       (Y1 >= 0) && (Y1 < YRES)
736 ;       (Y2 >= 0) && (Y2 < YRES)
737 ;
738 ; Must set an error code: NO
739 ;
740
741 ; Note: This function needs optimization. It's just a cheap translation of
742 ; the original C wrapper and could be written much smaller (besides that,
743 ; calling LINE is not a good idea either).
744
745 BAR:
746         lda     X2
747         sta     X2SAVE
748         lda     X2+1
749         sta     X2SAVE+1
750
751         lda     Y2
752         sta     Y2SAVE
753
754         lda     X1
755         sta     X1SAVE
756         lda     X1+1
757         sta     X1SAVE+1
758
759         lda     Y1
760         sta     Y1SAVE
761
762 @L1:    sta     Y2
763         lda     #>200
764         sta     Y1+1
765         sta     Y2+1
766
767         jsr     LINE
768
769         lda     Y1SAVE
770         cmp     Y2SAVE
771         beq     @L4
772
773         inc     Y1SAVE
774
775         lda     X1SAVE
776         sta     X1
777         lda     X1SAVE+1
778         sta     X1+1
779
780         lda     X2SAVE
781         sta     X2
782         lda     X2SAVE+1
783         sta     X2+1
784
785         lda     Y1SAVE
786         sta     Y1
787         jmp     @L1
788
789 @L4:    rts
790
791
792 ; ------------------------------------------------------------------------
793 ; TEXTSTYLE: Set the style used when calling OUTTEXT. Text scaling in X and Y
794 ; direction is passend in X/Y, the text direction is passed in A.
795 ;
796 ; Must set an error code: NO
797 ;
798
799 TEXTSTYLE:
800         stx     TEXTMAGX
801         sty     TEXTMAGY
802         sta     TEXTDIR
803         rts
804
805
806 ; ------------------------------------------------------------------------
807 ; OUTTEXT: Output text at X/Y = ptr1/ptr2 using the current color and the
808 ; current text style. The text to output is given as a zero terminated
809 ; string with address in ptr3.
810 ;
811 ; Must set an error code: NO
812 ;
813
814 OUTTEXT:
815
816 ; Calculate a pointer to the representation of the character in the
817 ; character ROM
818
819         ldx     #((>(CHARROM + $0800)) >> 3)
820         ldy     #0
821         lda     (TEXT),y
822         bmi     @L1
823         ldx     #((>(CHARROM + $0000)) >> 3)
824 @L1:    stx     ptr4+1
825         asl     a
826         rol     ptr4+1
827         asl     a
828         rol     ptr4+1
829         asl     a
830         rol     ptr4+1
831         sta     ptr4
832
833
834
835
836
837         rts
838
839 ; ------------------------------------------------------------------------
840 ; Calculate all variables to plot the pixel at X1/Y1.
841
842 CALC:   lda     Y1
843         sta     TEMP2
844         and     #7
845         tay
846         lda     Y1+1
847         lsr                     ; Neg is possible
848         ror     TEMP2
849         lsr
850         ror     TEMP2
851         lsr
852         ror     TEMP2
853
854         lda     #00
855         sta     POINT
856         lda     TEMP2
857         cmp     #$80
858         ror
859         ror     POINT
860         cmp     #$80
861         ror
862         ror     POINT           ; row*64
863         adc     TEMP2           ; +row*256
864         clc
865         adc     #>VBASE         ; +bitmap base
866         sta     POINT+1
867
868         lda     X1
869         tax
870         and     #$F8
871         clc
872         adc     POINT           ; +(X AND #$F8)
873         sta     POINT
874         lda     X1+1
875         adc     POINT+1
876         sta     POINT+1
877         txa
878         and     #7
879         tax
880         rts