]> git.sur5r.net Git - cc65/blob - libsrc/apple2/apple2-40-48-16.s
Testcode for strtol and atoi.
[cc65] / libsrc / apple2 / apple2-40-48-16.s
1 ;
2 ; Graphics driver for the 40x48x16 mode on the Apple II
3 ;
4 ; Stefan Haubenthal <polluks@sdf.lonestar.org>
5 ; Oliver Schmidt <ol.sc@web.de>
6 ; Based on Maciej Witkowiak's line and circle routine
7 ;
8
9         .include        "zeropage.inc"
10
11         .include        "tgi-kernel.inc"
12         .include        "tgi-mode.inc"
13         .include        "tgi-error.inc"
14         .include        "apple2.inc"
15
16         .macpack        generic
17
18 ; ------------------------------------------------------------------------
19
20 ; Zero page stuff
21
22 H2      :=      $2C
23
24 ; ROM entry points
25
26 TEXT    :=      $F399
27 PLOT    :=      $F800
28 HLINE   :=      $F819
29 CLRSCR  :=      $F832
30 SETCOL  :=      $F864
31 SCRN    :=      $F871
32 SETGR   :=      $FB40
33 HOME    :=      $FC58
34
35 ; ------------------------------------------------------------------------
36
37 ; Variables mapped to the zero page segment variables. Some of these are
38 ; used for passing parameters to the driver.
39
40 X1      :=      ptr1
41 Y1      :=      ptr2
42 X2      :=      ptr3
43 Y2      :=      ptr4
44 RADIUS  :=      tmp1
45
46 ADDR    :=      tmp1
47 TEMP    :=      tmp3
48 TEMP2   :=      tmp4
49 TEMP3   :=      sreg
50 TEMP4   :=      sreg+1
51
52 ; Line routine stuff (must be on zpage)
53
54 PB      :=      ptr3            ; (2)   LINE
55 UB      :=      ptr4            ; (2)   LINE
56 ERR     :=      regsave         ; (2)   LINE
57 NX      :=      regsave+2       ; (2)   LINE
58
59 ; Circle routine stuff (must be on zpage)
60
61 XX      :=      ptr3            ; (2)   CIRCLE
62 YY      :=      ptr4            ; (2)   CIRCLE
63 MaxO    :=      sreg            ; (overwritten by TEMP3+TEMP4, but restored from OG/OU anyway)
64 XS      :=      regsave         ; (2)   CIRCLE
65 YS      :=      regsave+2       ; (2)   CIRCLE
66
67 ; ------------------------------------------------------------------------
68
69         .segment        "JUMPTABLE"
70
71 ; Header. Includes jump table and constants.
72
73 ; First part of the header is a structure that has a magic and defines the
74 ; capabilities of the driver
75
76         .byte   $74, $67, $69   ; "tgi"
77         .byte   TGI_API_VERSION ; TGI API version number
78 xres:   .word   40              ; X resolution
79 yres:   .word   48              ; Y resolution
80         .byte   16              ; Number of drawing colors
81         .byte   1               ; Number of screens available
82         .byte   8               ; System font X size
83         .byte   8               ; System font Y size
84         .res    4, $00          ; Reserved for future extensions
85
86 ; Next comes the jump table. Currently all entries must be valid and may point
87 ; to an RTS for test versions (function not implemented).
88
89         .addr   INSTALL
90         .addr   UNINSTALL
91         .addr   INIT
92         .addr   DONE
93         .addr   GETERROR
94         .addr   CONTROL
95         .addr   CLEAR
96         .addr   SETVIEWPAGE
97         .addr   SETDRAWPAGE
98         .addr   SETCOLOR
99         .addr   SETPALETTE
100         .addr   GETPALETTE
101         .addr   GETDEFPALETTE
102         .addr   SETPIXEL
103         .addr   GETPIXEL
104         .addr   LINE
105         .addr   BAR
106         .addr   CIRCLE
107         .addr   TEXTSTYLE
108         .addr   OUTTEXT
109         .addr   0               ; IRQ entry is unused
110
111 ; ------------------------------------------------------------------------
112
113         .bss
114
115 ; Absolute variables used in the code
116
117 ERROR:  .res    1               ; Error code
118
119 ; Line routine stuff (combined with circle routine stuff to save space)
120
121 OGora:
122 COUNT:  .res    2
123 OUkos:
124 NY:     .res    2
125 Y3:
126 DX:     .res    1
127 DY:     .res    1
128 AX:     .res    1
129 AY:     .res    1
130
131 ; ------------------------------------------------------------------------
132
133         .rodata
134
135 ; Constants and tables
136
137 DEFPALETTE: .byte $00, $01, $02, $03, $04, $05, $06, $07
138             .byte $08, $09, $0A, $0B, $0C, $0D, $0E, $0F
139
140 ; ------------------------------------------------------------------------
141
142         .code
143
144 ; INIT: Changes an already installed device from text mode to graphics mode.
145 ; Note that INIT/DONE may be called multiple times while the driver
146 ; is loaded, while INSTALL is only called once, so any code that is needed
147 ; to initializes variables and so on must go here. Setting palette and
148 ; clearing the screen is not needed because this is called by the graphics
149 ; kernel later.
150 ; The graphics kernel will never call INIT when a graphics mode is already
151 ; active, so there is no need to protect against that.
152 ; Must set an error code: YES
153 INIT:
154         ; Switch into graphics mode
155         bit     $C082           ; Switch in ROM
156         jsr     SETGR
157         bit     MIXCLR
158         bit     $C080           ; Switch in LC bank 2 for R/O
159
160         ; Done, reset the error code
161         lda     #TGI_ERR_OK
162         sta     ERROR
163
164         ; Fall through
165
166 ; INSTALL routine. Is called after the driver is loaded into memory. May
167 ; initialize anything that has to be done just once. Is probably empty
168 ; most of the time.
169 ; Must set an error code: NO
170 INSTALL:
171         ; Fall through
172
173 ; UNINSTALL routine. Is called before the driver is removed from memory. May
174 ; clean up anything done by INSTALL but is probably empty most of the time.
175 ; Must set an error code: NO
176 UNINSTALL:
177         ; Fall through
178
179 ; SETVIEWPAGE: Set the visible page. Called with the new page in A (0..n).
180 ; The page number is already checked to be valid by the graphics kernel.
181 ; Must set an error code: NO (will only be called if page ok)
182 SETVIEWPAGE:
183         ; Fall through
184
185 ; SETDRAWPAGE: Set the drawable page. Called with the new page in A (0..n).
186 ; The page number is already checked to be valid by the graphics kernel.
187 ; Must set an error code: NO (will only be called if page ok)
188 SETDRAWPAGE:
189         ; Fall through
190
191 ; TEXTSTYLE: Set the style used when calling OUTTEXT. Text scaling in X and Y
192 ; direction is passend in X/Y, the text direction is passed in A.
193 ; Must set an error code: NO
194 TEXTSTYLE:
195         ; Fall through
196
197 ; OUTTEXT: Output text at X/Y = ptr1/ptr2 using the current color and the
198 ; current text style. The text to output is given as a zero terminated
199 ; string with address in ptr3.
200 ; Must set an error code: NO
201 OUTTEXT:
202         rts
203
204 ; DONE: Will be called to switch the graphics device back into text mode.
205 ; The graphics kernel will never call DONE when no graphics mode is active,
206 ; so there is no need to protect against that.
207 ; Must set an error code: NO
208 DONE:
209         bit     $C082           ; Switch in ROM
210         jsr     TEXT
211         jsr     HOME
212         bit     $C080           ; Switch in LC bank 2 for R/O
213         rts
214
215 ; GETERROR: Return the error code in A and clear it.
216 GETERROR:
217         lda     ERROR
218         ldx     #TGI_ERR_OK
219         stx     ERROR
220         rts
221
222 ; CLEAR: Clears the screen.
223 ; Must set an error code: NO
224 CLEAR:
225         bit     $C082           ; Switch in ROM
226         jsr     CLRSCR
227         bit     $C080           ; Switch in LC bank 2 for R/O
228         rts
229
230 ; SETCOLOR: Set the drawing color (in A). The new color is already checked
231 ; to be in a valid range (0..maxcolor-1).
232 ; Must set an error code: NO (will only be called if color ok)
233 SETCOLOR:
234         bit     $C082           ; Switch in ROM
235         jsr     SETCOL
236         bit     $C080           ; Switch in LC bank 2 for R/O
237         rts
238
239 ; CONTROL: Platform/driver specific entry point.
240 ; Must set an error code: YES
241 CONTROL:
242         ; Fall through
243
244 ; SETPALETTE: Set the palette (not available with all drivers/hardware).
245 ; A pointer to the palette is passed in ptr1. Must set an error if palettes
246 ; are not supported
247 ; Must set an error code: YES
248 SETPALETTE:
249         lda     #TGI_ERR_INV_FUNC
250         sta     ERROR
251         rts
252
253 ; GETPALETTE: Return the current palette in A/X. Even drivers that cannot
254 ; set the palette should return the default palette here, so there's no
255 ; way for this function to fail.
256 ; Must set an error code: NO
257 GETPALETTE:
258         ; Fall through
259
260 ; GETDEFPALETTE: Return the default palette for the driver in A/X. All
261 ; drivers should return something reasonable here, even drivers that don't
262 ; support palettes, otherwise the caller has no way to determine the colors
263 ; of the (not changeable) palette.
264 ; Must set an error code: NO (all drivers must have a default palette)
265 GETDEFPALETTE:
266         lda     #<DEFPALETTE
267         ldx     #>DEFPALETTE
268         rts
269
270 ; SETPIXEL: Draw one pixel at X1/Y1 = ptr1/ptr2 with the current drawing
271 ; color. The coordinates passed to this function are never outside the
272 ; visible screen area, so there is no need for clipping inside this function.
273 ; Must set an error code: NO
274 SETPIXEL:
275         bit     $C082           ; Switch in ROM
276         ldy     X1
277         lda     Y1
278         jsr     PLOT
279         bit     $C080           ; Switch in LC bank 2 for R/O
280         rts
281
282 SETPIXELCLIP:
283         lda     Y1+1
284         bmi     :+              ; y < 0
285         lda     X1+1
286         bmi     :+              ; x < 0
287         lda     X1
288         ldx     X1+1
289         sta     ADDR
290         stx     ADDR+1
291         ldx     #ADDR
292         lda     xres
293         ldy     xres+1
294         jsr     icmp            ; ( x < xres ) ...
295         bcs     :+
296         lda     Y1
297         ldx     Y1+1
298         sta     ADDR
299         stx     ADDR+1
300         ldx     #ADDR
301         lda     yres
302         ldy     yres+1
303         jsr     icmp            ; ... && ( y < yres )
304         bcc     SETPIXEL
305 :       rts
306
307 ; GETPIXEL: Read the color value of a pixel and return it in A/X. The
308 ; coordinates passed to this function are never outside the visible screen
309 ; area, so there is no need for clipping inside this function.
310 GETPIXEL:
311         bit     $C082           ; Switch in ROM
312         ldy     X1
313         lda     Y1
314         jsr     SCRN
315         ldx     #$00
316         bit     $C080           ; Switch in LC bank 2 for R/O
317         rts
318
319 ; LINE: Draw a line from X1/Y1 to X2/Y2, where X1/Y1 = ptr1/ptr2 and
320 ; X2/Y2 = ptr3/ptr4 using the current drawing color.
321 ; Must set an error code: NO
322 LINE:
323         ; nx = abs (x2 - x1)
324         lda     X2
325         sub     X1
326         sta     NX
327         lda     X2+1
328         sbc     X1+1
329         tay
330         lda     NX
331         jsr     abs
332         sta     NX
333         sty     NX+1
334
335         ; ny = abs (y2 - y1)
336         lda     Y2
337         sub     Y1
338         sta     NY
339         lda     Y2+1
340         sbc     Y1+1
341         tay
342         lda     NY
343         jsr     abs
344         sta     NY
345         sty     NY+1
346
347         ; if (x2 >= x1)
348         ldx     #X2
349         lda     X1
350         ldy     X1+1
351         jsr     icmp
352         bcc     :+
353
354         ;    dx = 1
355         lda     #$01
356         bne     :++
357
358         ; else
359         ;    dx = -1
360 :       lda     #$FF
361 :       sta     DX
362
363         ; if (y2 >= y1)
364         ldx     #Y2
365         lda     Y1
366         ldy     Y1+1
367         jsr     icmp
368         bcc     :+
369
370         ;    dy = 1
371         lda     #$01
372         bne     :++
373
374         ; else
375         ;    dy = -1
376 :       lda     #$FF
377 :       sta     DY
378
379         ; err = ax = ay = 0
380         lda     #$00
381         sta     ERR
382         sta     ERR+1
383         sta     AX
384         sta     AY
385
386         ; if (nx < ny) {
387         ldx     #NX
388         lda     NY
389         ldy     NY+1
390         jsr     icmp
391         bcs     :+
392
393         ;    nx <-> ny
394         lda     NX
395         ldx     NY
396         sta     NY
397         stx     NX
398         lda     NX+1
399         ldx     NY+1
400         sta     NY+1
401         stx     NX+1
402
403         ;    ax = dx
404         lda     DX
405         sta     AX
406
407         ;    ay = dy
408         lda     DY
409         sta     AY
410
411         ;    dx = dy = 0 }
412         lda     #$00
413         sta     DX
414         sta     DY
415
416         ; ny = - ny
417 :       lda     NY
418         ldy     NY+1
419         jsr     neg
420         sta     NY
421         sty     NY+1
422
423         ; for (count = nx; count > 0; --count) {
424         lda     NX
425         ldx     NX+1
426         sta     COUNT
427         stx     COUNT+1
428 for:    lda     COUNT           ; count > 0
429         ora     COUNT+1
430         bne     :+
431         rts
432
433         ;    setpixel (X1, Y1)
434 :       jsr     SETPIXELCLIP
435
436         ;    pb = err + ny
437         lda     ERR
438         add     NY
439         sta     PB
440         lda     ERR+1
441         adc     NY+1
442         sta     PB+1
443         tax
444
445         ;    ub = pb + nx
446         lda     PB
447         add     NX
448         sta     UB
449         txa
450         adc     NX+1
451         sta     UB+1
452
453         ;    x1 = x1 + dx
454         ldx     #$00
455         lda     DX
456         bpl     :+
457         dex
458 :       add     X1
459         sta     X1
460         txa
461         adc     X1+1
462         sta     X1+1
463
464         ;    y1 = y1 + ay
465         ldx     #$00
466         lda     AY
467         bpl     :+
468         dex
469 :       add     Y1
470         sta     Y1
471         txa
472         adc     Y1+1
473         sta     Y1+1
474
475         ;    if (abs (pb) < abs (ub)) {
476         lda     PB
477         ldy     PB+1
478         jsr     abs
479         sta     TEMP3
480         sty     TEMP4
481         lda     UB
482         ldy     UB+1
483         jsr     abs
484         ldx     #TEMP3
485         jsr     icmp
486         bpl     :+
487
488         ;       err = pb }
489         lda     PB
490         ldx     PB+1
491         jmp     next
492
493         ;    else { x1 = x1 + ax
494 :       ldx     #$00
495         lda     AX
496         bpl     :+
497         dex
498 :       add     X1
499         sta     X1
500         txa
501         adc     X1+1
502         sta     X1+1
503
504         ;       y1 = y1 + dy
505         ldx     #$00
506         lda     DY
507         bpl     :+
508         dex
509 :       add     Y1
510         sta     Y1
511         txa
512         adc     Y1+1
513         sta     Y1+1
514
515         ;       err = ub }
516         lda     UB
517         ldx     UB+1
518 next:   sta     ERR
519         stx     ERR+1
520
521         ; } (--count)
522         lda     COUNT
523         sub     #$01
524         sta     COUNT
525         bcc     :+
526         jmp     for
527 :       dec     COUNT+1
528         jmp     for
529
530 ; BAR: Draw a filled rectangle with the corners X1/Y1, X2/Y2, where
531 ; X1/Y1 = ptr1/ptr2 and X2/Y2 = ptr3/ptr4 using the current drawing color.
532 ; Contrary to most other functions, the graphics kernel will sort and clip
533 ; the coordinates before calling the driver, so on entry the following
534 ; conditions are valid:
535 ;       X1 <= X2
536 ;       Y1 <= Y2
537 ;       (X1 >= 0) && (X1 < XRES)
538 ;       (X2 >= 0) && (X2 < XRES)
539 ;       (Y1 >= 0) && (Y1 < YRES)
540 ;       (Y2 >= 0) && (Y2 < YRES)
541 ; Must set an error code: NO
542 BAR:
543         bit     $C082           ; Switch in ROM
544         inc     Y2
545         ldx     X2
546         stx     H2
547 :       ldy     X1
548         lda     Y1
549         jsr     HLINE
550         inc     Y1
551         lda     Y2
552         cmp     Y1
553         bne     :-
554         bit     $C080           ; Switch in LC bank 2 for R/O
555         rts
556
557 ; CIRCLE: Draw a circle around the center X1/Y1 (= ptr1/ptr2) with the
558 ; radius in tmp1 and the current drawing color.
559 ; Must set an error code: NO
560 CIRCLE:
561         lda     RADIUS
562         bne     :+
563         jmp     SETPIXELCLIP    ; Plot as a point
564 :       sta     XX
565
566         ; x = r
567         lda     #$00
568         sta     XX+1
569         sta     YY
570         sta     YY+1
571         sta     MaxO
572         sta     MaxO+1
573
574         ; y = 0, mo = 0
575         lda     X1
576         ldx     X1+1
577         sta     XS
578         stx     XS+1
579         lda     Y1
580         ldx     Y1+1
581         sta     YS
582         stx     YS+1            ; XS/YS to remember the center
583
584         ; while (y < x) {
585 while:  ldx     #YY
586         lda     XX
587         ldy     XX+1
588         jsr     icmp
589         bcc     :+
590         rts
591
592         ; Plot points in 8 slices...
593 :       lda     XS
594         add     XX
595         sta     X1
596         lda     XS+1
597         adc     XX+1
598         sta     X1+1            ; x1 = xs + x
599         lda     YS
600         add     YY
601         sta     Y1
602         pha
603         lda     YS+1
604         adc     YY+1
605         sta     Y1+1            ; (stack) = ys + y, y1 = (stack)
606         pha
607         jsr     SETPIXELCLIP    ; plot (xs + x, ys + y)
608         lda     YS
609         sub     YY
610         sta     Y1
611         sta     Y3
612         lda     YS+1
613         sbc     YY+1
614         sta     Y1+1            ; y3 = y1 = ys - y
615         sta     Y3+1
616         jsr     SETPIXELCLIP    ; plot (xs + x, ys - y)
617         pla
618         sta     Y1+1
619         pla
620         sta     Y1              ; y1 = ys + y
621         lda     XS
622         sub     XX
623         sta     X1
624         lda     XS+1
625         sbc     XX+1
626         sta     X1+1
627         jsr     SETPIXELCLIP    ; plot (xs - x, ys + y)
628         lda     Y3
629         sta     Y1
630         lda     Y3+1
631         sta     Y1+1
632         jsr     SETPIXELCLIP    ; plot (xs - x, ys - y)
633
634         lda     XS
635         add     YY
636         sta     X1
637         lda     XS+1
638         adc     YY+1
639         sta     X1+1            ; x1 = xs + y
640         lda     YS
641         add     XX
642         sta     Y1
643         pha
644         lda     YS+1
645         adc     XX+1
646         sta     Y1+1            ; (stack) = ys + x, y1 = (stack)
647         pha
648         jsr     SETPIXELCLIP    ; plot (xs + y, ys + x)
649         lda     YS
650         sub     XX
651         sta     Y1
652         sta     Y3
653         lda     YS+1
654         sbc     XX+1
655         sta     Y1+1            ; y3 = y1 = ys - x
656         sta     Y3+1
657         jsr     SETPIXELCLIP    ; plot (xs + y, ys - x)
658         pla
659         sta     Y1+1
660         pla
661         sta     Y1              ; y1 = ys + x(stack)
662         lda     XS
663         sub     YY
664         sta     X1
665         lda     XS+1
666         sbc     YY+1
667         sta     X1+1
668         jsr     SETPIXELCLIP    ; plot (xs - y, ys + x)
669         lda     Y3
670         sta     Y1
671         lda     Y3+1
672         sta     Y1+1
673         jsr     SETPIXELCLIP    ; plot (xs - y, ys - x)
674
675         ;    og = mo + y + y + 1
676         lda     MaxO
677         ldx     MaxO+1
678         add     YY
679         tay
680         txa
681         adc     YY+1
682         tax
683         tya
684         add     YY
685         tay
686         txa
687         adc     YY+1
688         tax
689         tya
690         add     #$01
691         bcc     :+
692         inx
693 :       sta     OGora
694         stx     OGora+1
695
696         ;    ou = og - x - x + 1
697         sub     XX
698         tay
699         txa
700         sbc     XX+1
701         tax
702         tya
703         sub     XX
704         tay
705         txa
706         sbc     XX+1
707         tax
708         tya
709         add     #$01
710         bcc     :+
711         inx
712 :       sta     OUkos
713         stx     OUkos+1
714
715         ;    ++y
716         inc     YY
717         bne     :+
718         inc     YY+1
719
720         ;    if (abs (ou) < abs (og)) {
721 :       lda     OUkos
722         ldy     OUkos+1
723         jsr     abs
724         sta     TEMP3
725         sty     TEMP4
726         lda     OGora
727         ldy     OGora+1
728         jsr     abs
729         ldx     #TEMP3
730         jsr     icmp
731         bpl     :++
732
733         ;       --x
734         lda     XX
735         sub     #$01
736         sta     XX
737         bcs     :+
738         dec     XX+1
739
740         ;       mo = ou }
741 :       lda     OUkos
742         ldx     OUkos+1
743         jmp     :++
744
745         ;    else mo = og
746 :       lda     OGora
747         ldx     OGora+1
748 :       sta     MaxO
749         stx     MaxO+1
750
751         ; }
752         jmp     while
753
754 ; Copies of some runtime routines
755
756 abs:
757         ; A/Y := abs (A/Y)
758         cpy     #$00
759         bpl     :+
760         
761         ; A/Y := neg (A/Y)
762 neg:    clc
763         eor     #$FF
764         adc     #$01
765         pha
766         tya
767         eor     #$FF
768         adc     #$00
769         tay
770         pla
771 :       rts
772
773 icmp:
774         ; Compare A/Y to zp,X
775         sta     TEMP            ; TEMP/TEMP2 - arg2
776         sty     TEMP2
777         lda     $00,x
778         pha
779         lda     $01,x
780         tay
781         pla
782         tax
783         tya                     ; X/A - arg1 (a = high)
784
785         sub     TEMP2
786         bne     :++
787         cpx     TEMP
788         beq     :+
789         adc     #$FF
790         ora     #$01
791 :       rts
792 :       bvc     :+
793         eor     #$FF
794         ora     #$01
795 :       rts