]> git.sur5r.net Git - cc65/blob - libsrc/apple2/tgi/a2.hi.s
Renamed JUMPTABLE and cleaned up module.cfg.
[cc65] / libsrc / apple2 / tgi / a2.hi.s
1 ;
2 ; Graphics driver for the 280x192x8 mode on the Apple II
3 ;
4 ; Stefan Haubenthal <polluks@sdf.lonestar.org>
5 ; Oliver Schmidt <ol.sc@web.de>
6 ;
7
8         .include        "zeropage.inc"
9
10         .include        "tgi-kernel.inc"
11         .include        "tgi-error.inc"
12         .include        "apple2.inc"
13
14 ; ------------------------------------------------------------------------
15
16 ; Zero page stuff
17
18 HBASL   :=      $26
19 HMASK   :=      $30
20 PAGE    :=      $E6
21 SCALE   :=      $E7
22 ROT     :=      $F9
23
24 ; Graphics entry points, by cbmnut (applenut??) cbmnut@hushmail.com
25
26 TEXT    :=      $F399   ; Return to text screen
27 HGR2    :=      $F3D8   ; Initialize and clear hi-res page 2.
28 HGR     :=      $F3E2   ; Initialize and clear hi-res page 1.
29 HCLR    :=      $F3F2   ; Clear the current hi-res screen to black.
30 BKGND   :=      $F3F6   ; Clear the current hi-res screen to the
31                         ; last plotted color (from ($1C).
32 HPOSN   :=      $F411   ; Positions the hi-res cursor without
33                         ; plotting a point.
34                         ; Enter with (A) = Y-coordinate, and
35                         ; (Y,X) = X-coordinate.
36 HPLOT   :=      $F457   ; Calls HPOSN and tries to plot a dot at
37                         ; the cursor's position.  If you are
38                         ; trying to plot a non-white color at
39                         ; a complementary color position, no
40                         ; dot will be plotted.
41 HLIN    :=      $F53A   ; Draws a line from the last plotted
42                         ; point or line destination to:
43                         ; (X,A) = X-coordinate, and
44                         ; (Y) = Y-coordinate.
45 HFIND   :=      $F5CB   ; Converts the hi-res coursor's position
46                         ; back to X- and Y-coordinates; stores
47                         ; X-coordinate at $E0,E1 and Y-coordinate
48                         ; at $E2.
49 DRAW    :=      $F601   ; Draws a shape.  Enter with (Y,X) = the
50                         ; address of the shape table, and (A) =
51                         ; the rotation factor.  Uses the current
52                         ; color.
53 XDRAW   :=      $F65D   ; Draws a shape by inverting the existing
54                         ; color of the dots the shape draws over.
55                         ; Same entry parameters as DRAW.
56 SETHCOL :=      $F6EC   ; Set the hi-res color to (X), where (X)
57                         ; must be between 0 and 7.
58
59 ; ------------------------------------------------------------------------
60
61 ; Variables mapped to the zero page segment variables. Some of these are
62 ; used for passing parameters to the driver.
63
64 X1      :=      ptr1
65 Y1      :=      ptr2
66 X2      :=      ptr3
67 Y2      :=      ptr4
68
69 ; ------------------------------------------------------------------------
70
71         .segment        "HEADER"
72
73 ; Header. Includes jump table and constants.
74
75 ; First part of the header is a structure that has a magic and defines the
76 ; capabilities of the driver
77
78         .byte   $74, $67, $69   ; "tgi"
79         .byte   TGI_API_VERSION ; TGI API version number
80         .addr   $0000           ; Library reference
81         .word   280             ; X resolution
82         .word   192             ; Y resolution
83         .byte   8               ; Number of drawing colors
84 pages:  .byte   2               ; Number of screens available
85         .byte   7               ; System font X size
86         .byte   8               ; System font Y size
87         .word   $00EA           ; Aspect ratio (based on 4/3 display)
88         .byte   0               ; TGI driver flags
89
90 ; Next comes the jump table. With the exception of IRQ, all entries must be
91 ; valid and may point to an RTS for test versions (function not implemented).
92
93         .addr   INSTALL
94         .addr   UNINSTALL
95         .addr   INIT
96         .addr   DONE
97         .addr   GETERROR
98         .addr   CONTROL
99         .addr   CLEAR
100         .addr   SETVIEWPAGE
101         .addr   SETDRAWPAGE
102         .addr   SETCOLOR
103         .addr   SETPALETTE
104         .addr   GETPALETTE
105         .addr   GETDEFPALETTE
106         .addr   SETPIXEL
107         .addr   GETPIXEL
108         .addr   LINE
109         .addr   BAR
110         .addr   TEXTSTYLE
111         .addr   OUTTEXT
112         .addr   0               ; IRQ entry is unused
113
114 ; ------------------------------------------------------------------------
115
116         .bss
117
118 ; Absolute variables used in the code
119
120 ERROR:  .res    1               ; Error code
121
122 ; ------------------------------------------------------------------------
123
124         .rodata
125
126 ; Constants and tables
127
128 DEFPALETTE: .byte $00, $01, $02, $03, $04, $05, $06, $07
129
130 FONT:
131         ; Beagle Bros Shape Mechanic font F.ASCII.SMALL
132         ; modified to exactly reproduce the text glyphs
133         .incbin "a2.hi.fnt"
134
135 ; ------------------------------------------------------------------------
136
137         .code
138
139 ; INSTALL routine. Is called after the driver is loaded into memory. May
140 ; initialize anything that has to be done just once. Is probably empty
141 ; most of the time.
142 ; Must set an error code: NO
143 INSTALL:
144         .ifdef  __APPLE2ENH__
145         ; No page switching if 80 column store is enabled
146         bit     RD80COL
147         bpl     :+
148         lda     #$01
149         sta     pages
150 :       .endif
151
152         ; Fall through
153
154 ; UNINSTALL routine. Is called before the driver is removed from memory. May
155 ; clean up anything done by INSTALL but is probably empty most of the time.
156 ; Must set an error code: NO
157 UNINSTALL:
158         rts
159
160 ; INIT: Changes an already installed device from text mode to graphics mode.
161 ; Note that INIT/DONE may be called multiple times while the driver
162 ; is loaded, while INSTALL is only called once, so any code that is needed
163 ; to initializes variables and so on must go here. Setting palette and
164 ; clearing the screen is not needed because this is called by the graphics
165 ; kernel later.
166 ; The graphics kernel will never call INIT when a graphics mode is already
167 ; active, so there is no need to protect against that.
168 ; Must set an error code: YES
169 INIT:
170         ; Switch into graphics mode
171         bit     MIXCLR
172         bit     HIRES
173         bit     TXTCLR
174
175         ; Beagle Bros Shape Mechanic fonts don't
176         ; scale well so use fixed scaling factor
177         lda     #$01
178         sta     SCALE
179
180         ; Done, reset the error code
181         lda     #TGI_ERR_OK
182         sta     ERROR
183         rts
184
185 ; DONE: Will be called to switch the graphics device back into text mode.
186 ; The graphics kernel will never call DONE when no graphics mode is active,
187 ; so there is no need to protect against that.
188 ; Must set an error code: NO
189 DONE:
190         ; Switch into text mode
191         bit     TXTSET
192         bit     LOWSCR
193
194         .ifdef  __APPLE2ENH__
195         ; Limit SET80COL-HISCR to text
196         bit     LORES
197         .endif
198
199         ; Reset the text window top
200         lda     #$00
201         sta     WNDTOP
202         rts
203
204 ; GETERROR: Return the error code in A and clear it.
205 GETERROR:
206         lda     ERROR
207         ldx     #TGI_ERR_OK
208         stx     ERROR
209         rts
210
211 ; CONTROL: Platform/driver specific entry point.
212 ; Must set an error code: YES
213 CONTROL:
214         ; Check data msb and code to be 0
215         ora     ptr1+1
216         bne     err
217
218         ; Check data lsb to be [0..1]
219         lda     ptr1
220         cmp     #1+1
221         bcs     err
222
223         ; Set text window top
224         tax
225         beq     :+
226         lda     #20
227 :       sta     WNDTOP
228
229         ; Switch 4 lines of text
230         .assert MIXCLR + 1 = MIXSET, error
231         lda     MIXCLR,x        ; No BIT absolute,X available
232
233         ; Done, reset the error code
234         lda     #TGI_ERR_OK
235         beq     :+              ; Branch always
236
237         ; Done, set the error code
238 err:    lda     #TGI_ERR_INV_ARG
239 :       sta     ERROR
240         rts
241
242 ; CLEAR: Clears the screen.
243 ; Must set an error code: NO
244 CLEAR:
245         bit     $C082           ; Switch in ROM
246         jsr     HCLR
247         bit     $C080           ; Switch in LC bank 2 for R/O
248         rts
249
250 ; SETVIEWPAGE: Set the visible page. Called with the new page in A (0..n).
251 ; The page number is already checked to be valid by the graphics kernel.
252 ; Must set an error code: NO (will only be called if page ok)
253 SETVIEWPAGE:
254         tax
255         .assert LOWSCR + 1 = HISCR, error
256         lda     LOWSCR,x        ; No BIT absolute,X available
257         rts
258
259 ; SETDRAWPAGE: Set the drawable page. Called with the new page in A (0..n).
260 ; The page number is already checked to be valid by the graphics kernel.
261 ; Must set an error code: NO (will only be called if page ok)
262 SETDRAWPAGE:
263         tax
264         beq     :+
265         lda     #>$4000         ; Page 2
266         .byte   $2C             ; BIT absolute
267 :       lda     #>$2000         ; Page 1
268         sta     PAGE
269         rts
270
271 ; SETCOLOR: Set the drawing color (in A). The new color is already checked
272 ; to be in a valid range (0..maxcolor-1).
273 ; Must set an error code: NO (will only be called if color ok)
274 SETCOLOR:
275         bit     $C082           ; Switch in ROM
276         tax
277         jsr     SETHCOL
278         bit     $C080           ; Switch in LC bank 2 for R/O
279         rts
280
281 ; SETPALETTE: Set the palette (not available with all drivers/hardware).
282 ; A pointer to the palette is passed in ptr1. Must set an error if palettes
283 ; are not supported
284 ; Must set an error code: YES
285 SETPALETTE:
286         lda     #TGI_ERR_INV_FUNC
287         sta     ERROR
288         rts
289
290 ; GETPALETTE: Return the current palette in A/X. Even drivers that cannot
291 ; set the palette should return the default palette here, so there's no
292 ; way for this function to fail.
293 ; Must set an error code: NO
294 GETPALETTE:
295         ; Fall through
296
297 ; GETDEFPALETTE: Return the default palette for the driver in A/X. All
298 ; drivers should return something reasonable here, even drivers that don't
299 ; support palettes, otherwise the caller has no way to determine the colors
300 ; of the (not changeable) palette.
301 ; Must set an error code: NO (all drivers must have a default palette)
302 GETDEFPALETTE:
303         lda     #<DEFPALETTE
304         ldx     #>DEFPALETTE
305         rts
306
307 ; SETPIXEL: Draw one pixel at X1/Y1 = ptr1/ptr2 with the current drawing
308 ; color. The coordinates passed to this function are never outside the
309 ; visible screen area, so there is no need for clipping inside this function.
310 ; Must set an error code: NO
311 SETPIXEL:
312         bit     $C082           ; Switch in ROM
313         ldx     X1
314         ldy     X1+1
315         lda     Y1
316         jsr     HPLOT
317         bit     $C080           ; Switch in LC bank 2 for R/O
318         rts
319
320 ; GETPIXEL: Read the color value of a pixel and return it in A/X. The
321 ; coordinates passed to this function are never outside the visible screen
322 ; area, so there is no need for clipping inside this function.
323 GETPIXEL:
324         bit     $C082           ; Switch in ROM
325         ldx     X1
326         ldy     X1+1
327         lda     Y1
328         jsr     HPOSN
329         lda     (HBASL),y
330         and     HMASK
331         asl
332         beq     :+              ; 0 (black)
333         lda     #$03            ; 3 (white)
334 :       bcc     :+
335         adc     #$03            ; += 4 (black -> black2, white -> white2)
336 :       ldx     #$00
337         bit     $C080           ; Switch in LC bank 2 for R/O
338         rts
339
340 ; LINE: Draw a line from X1/Y1 to X2/Y2, where X1/Y1 = ptr1/ptr2 and
341 ; X2/Y2 = ptr3/ptr4 using the current drawing color.
342 ; Must set an error code: NO
343 LINE:
344         bit     $C082           ; Switch in ROM
345         ldx     X1
346         ldy     X1+1
347         lda     Y1
348         jsr     HPOSN
349         lda     X2
350         ldx     X2+1
351         ldy     Y2
352         jsr     HLIN
353         bit     $C080           ; Switch in LC bank 2 for R/O
354         rts
355
356 ; BAR: Draw a filled rectangle with the corners X1/Y1, X2/Y2, where
357 ; X1/Y1 = ptr1/ptr2 and X2/Y2 = ptr3/ptr4 using the current drawing color.
358 ; Contrary to most other functions, the graphics kernel will sort and clip
359 ; the coordinates before calling the driver, so on entry the following
360 ; conditions are valid:
361 ;       X1 <= X2
362 ;       Y1 <= Y2
363 ;       (X1 >= 0) && (X1 < XRES)
364 ;       (X2 >= 0) && (X2 < XRES)
365 ;       (Y1 >= 0) && (Y1 < YRES)
366 ;       (Y2 >= 0) && (Y2 < YRES)
367 ; Must set an error code: NO
368 BAR:
369         inc     Y2
370 :       lda     Y2
371         pha
372         lda     Y1
373         sta     Y2
374         jsr     LINE
375         pla
376         sta     Y2
377         inc     Y1
378         cmp     Y1
379         bne     :-
380         rts
381
382 ; TEXTSTYLE: Set the style used when calling OUTTEXT. Text scaling in X and Y
383 ; direction is passend in X/Y, the text direction is passed in A.
384 ; Must set an error code: NO
385 TEXTSTYLE:
386         cmp     #TGI_TEXT_VERTICAL
387         bne     :+
388         lda     #48
389 :       sta     ROT
390         rts
391
392 ; OUTTEXT: Output text at X/Y = ptr1/ptr2 using the current color and the
393 ; current text style. The text to output is given as a zero terminated
394 ; string with address in ptr3.
395 ; Must set an error code: NO
396 OUTTEXT:
397         bit     $C082           ; Switch in ROM
398         lda     X1
399         ldy     X1+1
400         ldx     ROT
401         php                     ; Save Z flag
402         beq     :+              ; Not horizontal
403         sec
404         sbc     #$07            ; Adjust X
405         bcs     :+
406         dey
407 :       tax
408         lda     Y1
409         plp                     ; Restore Z flag
410         bne     :+              ; Not vertical
411         sec
412         sbc     #$07            ; Adjust Y
413 :       jsr     HPOSN
414         clc
415         lda     FONT+2*99       ; "connection char"
416         adc     #<FONT
417         sta     ptr4
418         lda     FONT+2*99+1     ; "connection char"
419         adc     #>FONT
420         sta     ptr4+1
421         ldy     #$00
422 :       lda     (ptr3),y
423         beq     :+
424         sty     tmp1            ; Save string index
425         sec
426         sbc     #$1F            ; No control chars
427         asl                     ; Offset * 2
428         tay
429         clc
430         lda     FONT,y
431         adc     #<FONT
432         tax
433         lda     FONT+1,y
434         adc     #>FONT
435         tay
436         lda     ROT
437         jsr     DRAW            ; Draw char from string
438         ldx     ptr4
439         ldy     ptr4+1
440         lda     ROT
441         jsr     DRAW            ; Draw "connection char"
442         ldy     tmp1            ; Restore string index
443         iny
444         bne     :-              ; Branch always
445 :       bit     $C080           ; Switch in LC bank 2 for R/O
446         rts