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