]> git.sur5r.net Git - cc65/blob - libsrc/apple2/tgi/a2.hi.s
Merge https://github.com/cc65/cc65 into c1p
[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         .addr   0               ; IRQ entry is unused
119
120 ; ------------------------------------------------------------------------
121
122         .bss
123
124 ; Absolute variables used in the code
125
126 ERROR:  .res    1               ; Error code
127
128 ; ------------------------------------------------------------------------
129
130         .rodata
131
132 ; Constants and tables
133
134 DEFPALETTE: .byte $00, $01, $02, $03, $04, $05, $06, $07
135
136 FONT:
137         ; Beagle Bros Shape Mechanic font F.ASCII.SMALL
138         ; modified to exactly reproduce the text glyphs
139         .incbin "a2.hi.fnt"
140
141 ; ------------------------------------------------------------------------
142
143         .code
144
145 ; INSTALL routine. Is called after the driver is loaded into memory. May
146 ; initialize anything that has to be done just once. Is probably empty
147 ; most of the time.
148 ; Must set an error code: NO
149 INSTALL:
150         .ifdef  __APPLE2ENH__
151         ; No page switching if 80 column store is enabled
152         bit     RD80COL
153         bpl     :+
154         lda     #$01
155         sta     pages
156 :       .endif
157
158         ; Fall through
159
160 ; UNINSTALL routine. Is called before the driver is removed from memory. May
161 ; clean up anything done by INSTALL but is probably empty most of the time.
162 ; Must set an error code: NO
163 UNINSTALL:
164         rts
165
166 ; INIT: Changes an already installed device from text mode to graphics mode.
167 ; Note that INIT/DONE may be called multiple times while the driver
168 ; is loaded, while INSTALL is only called once, so any code that is needed
169 ; to initializes variables and so on must go here. Setting palette and
170 ; clearing the screen is not needed because this is called by the graphics
171 ; kernel later.
172 ; The graphics kernel will never call INIT when a graphics mode is already
173 ; active, so there is no need to protect against that.
174 ; Must set an error code: YES
175 INIT:
176         ; Switch into graphics mode
177         bit     MIXCLR
178         bit     HIRES
179         bit     TXTCLR
180
181         ; Beagle Bros Shape Mechanic fonts don't
182         ; scale well so use fixed scaling factor
183         lda     #$01
184         sta     SCALE
185
186         ; Done, reset the error code
187         lda     #TGI_ERR_OK
188         sta     ERROR
189         rts
190
191 ; DONE: Will be called to switch the graphics device back into text mode.
192 ; The graphics kernel will never call DONE when no graphics mode is active,
193 ; so there is no need to protect against that.
194 ; Must set an error code: NO
195 DONE:
196         ; Switch into text mode
197         bit     TXTSET
198         bit     LOWSCR
199
200         .ifdef  __APPLE2ENH__
201         ; Limit SET80COL-HISCR to text
202         bit     LORES
203         .endif
204
205         ; Reset the text window top
206         lda     #$00
207         sta     WNDTOP
208         rts
209
210 ; GETERROR: Return the error code in A and clear it.
211 GETERROR:
212         lda     ERROR
213         ldx     #TGI_ERR_OK
214         stx     ERROR
215         rts
216
217 ; CONTROL: Platform/driver specific entry point.
218 ; Must set an error code: YES
219 CONTROL:
220         ; Check data msb and code to be 0
221         ora     ptr1+1
222         bne     err
223
224         ; Check data lsb to be [0..1]
225         lda     ptr1
226         cmp     #1+1
227         bcs     err
228
229         ; Set text window top
230         tax
231         beq     :+
232         lda     #20
233 :       sta     WNDTOP
234
235         ; Switch 4 lines of text
236         .assert MIXCLR + 1 = MIXSET, error
237         lda     MIXCLR,x        ; No BIT absolute,X available
238
239         ; Done, reset the error code
240         lda     #TGI_ERR_OK
241         beq     :+              ; Branch always
242
243         ; Done, set the error code
244 err:    lda     #TGI_ERR_INV_ARG
245 :       sta     ERROR
246         rts
247
248 ; CLEAR: Clears the screen.
249 ; Must set an error code: NO
250 CLEAR:
251         bit     $C082           ; Switch in ROM
252         jsr     HCLR
253         bit     $C080           ; Switch in LC bank 2 for R/O
254         rts
255
256 ; SETVIEWPAGE: Set the visible page. Called with the new page in A (0..n).
257 ; The page number is already checked to be valid by the graphics kernel.
258 ; Must set an error code: NO (will only be called if page ok)
259 SETVIEWPAGE:
260         tax
261         .assert LOWSCR + 1 = HISCR, error
262         lda     LOWSCR,x        ; No BIT absolute,X available
263         rts
264
265 ; SETDRAWPAGE: Set the drawable page. Called with the new page in A (0..n).
266 ; The page number is already checked to be valid by the graphics kernel.
267 ; Must set an error code: NO (will only be called if page ok)
268 SETDRAWPAGE:
269         tax
270         beq     :+
271         lda     #>$4000         ; Page 2
272         .byte   $2C             ; BIT absolute
273 :       lda     #>$2000         ; Page 1
274         sta     PAGE
275         rts
276
277 ; SETCOLOR: Set the drawing color (in A). The new color is already checked
278 ; to be in a valid range (0..maxcolor-1).
279 ; Must set an error code: NO (will only be called if color ok)
280 SETCOLOR:
281         bit     $C082           ; Switch in ROM
282         tax
283         jsr     SETHCOL
284         bit     $C080           ; Switch in LC bank 2 for R/O
285         rts
286
287 ; SETPALETTE: Set the palette (not available with all drivers/hardware).
288 ; A pointer to the palette is passed in ptr1. Must set an error if palettes
289 ; are not supported
290 ; Must set an error code: YES
291 SETPALETTE:
292         lda     #TGI_ERR_INV_FUNC
293         sta     ERROR
294         rts
295
296 ; GETPALETTE: Return the current palette in A/X. Even drivers that cannot
297 ; set the palette should return the default palette here, so there's no
298 ; way for this function to fail.
299 ; Must set an error code: NO
300 GETPALETTE:
301         ; Fall through
302
303 ; GETDEFPALETTE: Return the default palette for the driver in A/X. All
304 ; drivers should return something reasonable here, even drivers that don't
305 ; support palettes, otherwise the caller has no way to determine the colors
306 ; of the (not changeable) palette.
307 ; Must set an error code: NO (all drivers must have a default palette)
308 GETDEFPALETTE:
309         lda     #<DEFPALETTE
310         ldx     #>DEFPALETTE
311         rts
312
313 ; SETPIXEL: Draw one pixel at X1/Y1 = ptr1/ptr2 with the current drawing
314 ; color. The coordinates passed to this function are never outside the
315 ; visible screen area, so there is no need for clipping inside this function.
316 ; Must set an error code: NO
317 SETPIXEL:
318         bit     $C082           ; Switch in ROM
319         ldx     X1
320         ldy     X1+1
321         lda     Y1
322         jsr     HPLOT
323         bit     $C080           ; Switch in LC bank 2 for R/O
324         rts
325
326 ; GETPIXEL: Read the color value of a pixel and return it in A/X. The
327 ; coordinates passed to this function are never outside the visible screen
328 ; area, so there is no need for clipping inside this function.
329 GETPIXEL:
330         bit     $C082           ; Switch in ROM
331         ldx     X1
332         ldy     X1+1
333         lda     Y1
334         jsr     HPOSN
335         lda     (HBASL),y
336         and     HMASK
337         asl
338         beq     :+              ; 0 (black)
339         lda     #$03            ; 3 (white)
340 :       bcc     :+
341         adc     #$03            ; += 4 (black -> black2, white -> white2)
342 :       ldx     #$00
343         bit     $C080           ; Switch in LC bank 2 for R/O
344         rts
345
346 ; LINE: Draw a line from X1/Y1 to X2/Y2, where X1/Y1 = ptr1/ptr2 and
347 ; X2/Y2 = ptr3/ptr4 using the current drawing color.
348 ; Must set an error code: NO
349 LINE:
350         bit     $C082           ; Switch in ROM
351         ldx     X1
352         ldy     X1+1
353         lda     Y1
354         jsr     HPOSN
355         lda     X2
356         ldx     X2+1
357         ldy     Y2
358         jsr     HLIN
359         bit     $C080           ; Switch in LC bank 2 for R/O
360         rts
361
362 ; BAR: Draw a filled rectangle with the corners X1/Y1, X2/Y2, where
363 ; X1/Y1 = ptr1/ptr2 and X2/Y2 = ptr3/ptr4 using the current drawing color.
364 ; Contrary to most other functions, the graphics kernel will sort and clip
365 ; the coordinates before calling the driver, so on entry the following
366 ; conditions are valid:
367 ;       X1 <= X2
368 ;       Y1 <= Y2
369 ;       (X1 >= 0) && (X1 < XRES)
370 ;       (X2 >= 0) && (X2 < XRES)
371 ;       (Y1 >= 0) && (Y1 < YRES)
372 ;       (Y2 >= 0) && (Y2 < YRES)
373 ; Must set an error code: NO
374 BAR:
375         inc     Y2
376 :       lda     Y2
377         pha
378         lda     Y1
379         sta     Y2
380         jsr     LINE
381         pla
382         sta     Y2
383         inc     Y1
384         cmp     Y1
385         bne     :-
386         rts
387
388 ; TEXTSTYLE: Set the style used when calling OUTTEXT. Text scaling in X and Y
389 ; direction is passend in X/Y, the text direction is passed in A.
390 ; Must set an error code: NO
391 TEXTSTYLE:
392         cmp     #TGI_TEXT_VERTICAL
393         bne     :+
394         lda     #48
395 :       sta     ROT
396         rts
397
398 ; OUTTEXT: Output text at X/Y = ptr1/ptr2 using the current color and the
399 ; current text style. The text to output is given as a zero terminated
400 ; string with address in ptr3.
401 ; Must set an error code: NO
402 OUTTEXT:
403         bit     $C082           ; Switch in ROM
404         lda     X1
405         ldy     X1+1
406         ldx     ROT
407         php                     ; Save Z flag
408         beq     :+              ; Not horizontal
409         sec
410         sbc     #$07            ; Adjust X
411         bcs     :+
412         dey
413 :       tax
414         lda     Y1
415         plp                     ; Restore Z flag
416         bne     :+              ; Not vertical
417         sec
418         sbc     #$07            ; Adjust Y
419 :       jsr     HPOSN
420         clc
421         lda     FONT+2*99       ; "connection char"
422         adc     #<FONT
423         sta     ptr4
424         lda     FONT+2*99+1     ; "connection char"
425         adc     #>FONT
426         sta     ptr4+1
427         ldy     #$00
428 :       lda     (ptr3),y
429         beq     :+
430         sty     tmp1            ; Save string index
431         sec
432         sbc     #$1F            ; No control chars
433         asl                     ; Offset * 2
434         tay
435         clc
436         lda     FONT,y
437         adc     #<FONT
438         tax
439         lda     FONT+1,y
440         adc     #>FONT
441         tay
442         lda     ROT
443         jsr     DRAW            ; Draw char from string
444         ldx     ptr4
445         ldy     ptr4+1
446         lda     ROT
447         jsr     DRAW            ; Draw "connection char"
448         ldy     tmp1            ; Restore string index
449         iny
450         bne     :-              ; Branch always
451 :       bit     $C080           ; Switch in LC bank 2 for R/O
452         rts