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