]> git.sur5r.net Git - cc65/blob - libsrc/apple2/apple2-280-192-8.s
Minor comment adjustment.
[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-mode.inc"
12         .include        "tgi-error.inc"
13         .include        "apple2.inc"
14
15 ; ------------------------------------------------------------------------
16
17 ; Zero page stuff
18
19 HBASL   :=      $26
20 HMASK   :=      $30
21 PAGE    :=      $E6
22 SCALE   :=      $E7
23 ROT     :=      $F9
24
25 ; Graphics entry points, by cbmnut (applenut??) cbmnut@hushmail.com
26
27 TEXT    :=      $F399   ; Return to text screen
28 HGR2    :=      $F3D8   ; Initialize and clear hi-res page 2.
29 HGR     :=      $F3E2   ; Initialize and clear hi-res page 1.
30 HCLR    :=      $F3F2   ; Clear the current hi-res screen to black.
31 BKGND   :=      $F3F6   ; Clear the current hi-res screen to the
32                         ; last plotted color (from ($1C).
33 HPOSN   :=      $F411   ; Positions the hi-res cursor without
34                         ; plotting a point.
35                         ; Enter with (A) = Y-coordinate, and
36                         ; (Y,X) = X-coordinate.
37 HPLOT   :=      $F457   ; Calls HPOSN and tries to plot a dot at
38                         ; the cursor's position.  If you are
39                         ; trying to plot a non-white color at
40                         ; a complementary color position, no
41                         ; dot will be plotted.
42 HLIN    :=      $F53A   ; Draws a line from the last plotted
43                         ; point or line destination to:
44                         ; (X,A) = X-coordinate, and
45                         ; (Y) = Y-coordinate.
46 HFIND   :=      $F5CB   ; Converts the hi-res coursor's position
47                         ; back to X- and Y-coordinates; stores
48                         ; X-coordinate at $E0,E1 and Y-coordinate
49                         ; at $E2.
50 DRAW    :=      $F601   ; Draws a shape.  Enter with (Y,X) = the
51                         ; address of the shape table, and (A) =
52                         ; the rotation factor.  Uses the current
53                         ; color.
54 XDRAW   :=      $F65D   ; Draws a shape by inverting the existing
55                         ; color of the dots the shape draws over.
56                         ; Same entry parameters as DRAW.
57 SETHCOL :=      $F6EC   ; Set the hi-res color to (X), where (X)
58                         ; must be between 0 and 7.
59
60 ; ------------------------------------------------------------------------
61
62 ; Variables mapped to the zero page segment variables. Some of these are
63 ; used for passing parameters to the driver.
64
65 X1      :=      ptr1
66 Y1      :=      ptr2
67 X2      :=      ptr3
68 Y2      :=      ptr4
69
70 ; ------------------------------------------------------------------------
71
72         .segment        "JUMPTABLE"
73
74 ; Header. Includes jump table and constants.
75
76 ; First part of the header is a structure that has a magic and defines the
77 ; capabilities of the driver
78
79         .byte   $74, $67, $69   ; "tgi"
80         .byte   TGI_API_VERSION ; TGI API version number
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   $100            ; Aspect ratio
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         lda     #$02
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     LOWSCR
173         bit     HIRES
174         bit     TXTCLR
175
176         ; Beagle Bros Shape Mechanic fonts don't
177         ; scale well so use fixed scaling factor
178         lda     #1
179         sta     SCALE
180
181         ; Done, reset the error code
182         lda     #TGI_ERR_OK
183         sta     ERROR
184         rts
185
186 ; DONE: Will be called to switch the graphics device back into text mode.
187 ; The graphics kernel will never call DONE when no graphics mode is active,
188 ; so there is no need to protect against that.
189 ; Must set an error code: NO
190 DONE:
191         ; Switch into text mode
192         bit     TXTSET
193         bit     LOWSCR
194
195         .ifdef  __APPLE2ENH__
196         ; Limit SET80COL-HISCR to text
197         bit     LORES
198         .endif
199
200         ; Reset the text window top
201         lda     #$00
202         sta     WNDTOP
203         rts
204
205 ; GETERROR: Return the error code in A and clear it.
206 GETERROR:
207         lda     ERROR
208         ldx     #TGI_ERR_OK
209         stx     ERROR
210         rts
211
212 ; CONTROL: Platform/driver specific entry point.
213 ; Must set an error code: YES
214 CONTROL:
215         ; Check data msb and code to be 0
216         ora     ptr1+1
217         bne     err
218
219         ; Check data lsb to be [0..1]
220         lda     ptr1
221         cmp     #1+1
222         bcs     err
223
224         ; Set text window top
225         tax
226         beq     :+
227         lda     #20
228 :       sta     WNDTOP
229
230         ; Switch 4 lines of text
231         .assert MIXCLR + 1 = MIXSET, error
232         lda     MIXCLR,x        ; No BIT absolute,X available
233
234         ; Done, reset the error code
235         lda     #TGI_ERR_OK
236         beq     :+              ; Branch always
237
238         ; Done, set the error code
239 err:    lda     #TGI_ERR_INV_ARG
240 :       sta     ERROR
241         rts
242
243 ; CLEAR: Clears the screen.
244 ; Must set an error code: NO
245 CLEAR:
246         bit     $C082           ; Switch in ROM
247         jsr     HCLR
248         bit     $C080           ; Switch in LC bank 2 for R/O
249         rts
250
251 ; SETVIEWPAGE: Set the visible page. Called with the new page in A (0..n).
252 ; The page number is already checked to be valid by the graphics kernel.
253 ; Must set an error code: NO (will only be called if page ok)
254 SETVIEWPAGE:
255         tax
256         .assert LOWSCR + 1 = HISCR, error
257         lda     LOWSCR,x        ; No BIT absolute,X available
258         rts
259
260 ; SETDRAWPAGE: Set the drawable page. Called with the new page in A (0..n).
261 ; The page number is already checked to be valid by the graphics kernel.
262 ; Must set an error code: NO (will only be called if page ok)
263 SETDRAWPAGE:
264         tax
265         beq     :+
266         lda     #>$4000         ; Page 2
267         .byte   $2C             ; BIT absolute
268 :       lda     #>$2000         ; Page 1
269         sta     PAGE
270         rts
271
272 ; SETCOLOR: Set the drawing color (in A). The new color is already checked
273 ; to be in a valid range (0..maxcolor-1).
274 ; Must set an error code: NO (will only be called if color ok)
275 SETCOLOR:
276         bit     $C082           ; Switch in ROM
277         tax
278         jsr     SETHCOL
279         bit     $C080           ; Switch in LC bank 2 for R/O
280         rts
281
282 ; SETPALETTE: Set the palette (not available with all drivers/hardware).
283 ; A pointer to the palette is passed in ptr1. Must set an error if palettes
284 ; are not supported
285 ; Must set an error code: YES
286 SETPALETTE:
287         lda     #TGI_ERR_INV_FUNC
288         sta     ERROR
289         rts
290
291 ; GETPALETTE: Return the current palette in A/X. Even drivers that cannot
292 ; set the palette should return the default palette here, so there's no
293 ; way for this function to fail.
294 ; Must set an error code: NO
295 GETPALETTE:
296         ; Fall through
297
298 ; GETDEFPALETTE: Return the default palette for the driver in A/X. All
299 ; drivers should return something reasonable here, even drivers that don't
300 ; support palettes, otherwise the caller has no way to determine the colors
301 ; of the (not changeable) palette.
302 ; Must set an error code: NO (all drivers must have a default palette)
303 GETDEFPALETTE:
304         lda     #<DEFPALETTE
305         ldx     #>DEFPALETTE
306         rts
307
308 ; SETPIXEL: Draw one pixel at X1/Y1 = ptr1/ptr2 with the current drawing
309 ; color. The coordinates passed to this function are never outside the
310 ; visible screen area, so there is no need for clipping inside this function.
311 ; Must set an error code: NO
312 SETPIXEL:
313         bit     $C082           ; Switch in ROM
314         ldx     X1
315         ldy     X1+1
316         lda     Y1
317         jsr     HPLOT
318         bit     $C080           ; Switch in LC bank 2 for R/O
319         rts
320
321 ; GETPIXEL: Read the color value of a pixel and return it in A/X. The
322 ; coordinates passed to this function are never outside the visible screen
323 ; area, so there is no need for clipping inside this function.
324 GETPIXEL:
325         bit     $C082           ; Switch in ROM
326         ldx     X1
327         ldy     X1+1
328         lda     Y1
329         jsr     HPOSN
330         lda     (HBASL),y
331         and     HMASK
332         asl
333         beq     :+              ; 0 (black)
334         lda     #$03            ; 3 (white)
335 :       bcc     :+
336         adc     #$03            ; += 4 (black -> black2, white -> white2)
337 :       ldx     #$00
338         bit     $C080           ; Switch in LC bank 2 for R/O
339         rts
340
341 ; LINE: Draw a line from X1/Y1 to X2/Y2, where X1/Y1 = ptr1/ptr2 and
342 ; X2/Y2 = ptr3/ptr4 using the current drawing color.
343 ; Must set an error code: NO
344 LINE:
345         bit     $C082           ; Switch in ROM
346         ldx     X1
347         ldy     X1+1
348         lda     Y1
349         jsr     HPOSN
350         lda     X2
351         ldx     X2+1
352         ldy     Y2
353         jsr     HLIN
354         bit     $C080           ; Switch in LC bank 2 for R/O
355         rts
356
357 ; BAR: Draw a filled rectangle with the corners X1/Y1, X2/Y2, where
358 ; X1/Y1 = ptr1/ptr2 and X2/Y2 = ptr3/ptr4 using the current drawing color.
359 ; Contrary to most other functions, the graphics kernel will sort and clip
360 ; the coordinates before calling the driver, so on entry the following
361 ; conditions are valid:
362 ;       X1 <= X2
363 ;       Y1 <= Y2
364 ;       (X1 >= 0) && (X1 < XRES)
365 ;       (X2 >= 0) && (X2 < XRES)
366 ;       (Y1 >= 0) && (Y1 < YRES)
367 ;       (Y2 >= 0) && (Y2 < YRES)
368 ; Must set an error code: NO
369 BAR:
370         inc     Y2
371 :       lda     Y2
372         pha
373         lda     Y1
374         sta     Y2
375         jsr     LINE
376         pla
377         sta     Y2
378         inc     Y1
379         cmp     Y1
380         bne     :-
381         rts
382
383 ; TEXTSTYLE: Set the style used when calling OUTTEXT. Text scaling in X and Y
384 ; direction is passend in X/Y, the text direction is passed in A.
385 ; Must set an error code: NO
386 TEXTSTYLE:
387         cmp     #TGI_TEXT_VERTICAL
388         bne     :+
389         lda     #48
390 :       sta     ROT
391         rts
392
393 ; OUTTEXT: Output text at X/Y = ptr1/ptr2 using the current color and the
394 ; current text style. The text to output is given as a zero terminated
395 ; string with address in ptr3.
396 ; Must set an error code: NO
397 OUTTEXT:
398         bit     $C082           ; Switch in ROM
399         lda     X1
400         ldy     X1+1
401         ldx     ROT
402         php                     ; Save Z flag
403         beq     :+              ; Not horizontal
404         sec
405         sbc     #7              ; Adjust X
406         bcs     :+
407         dey
408 :       tax
409         lda     Y1
410         plp                     ; Restore Z flag
411         bne     :+              ; Not vertical
412         sec
413         sbc     #7              ; Adjust Y
414 :       jsr     HPOSN
415         clc
416         lda     FONT+2*99       ; "connection char"
417         adc     #<FONT
418         sta     ptr4
419         lda     FONT+2*99+1     ; "connection char"
420         adc     #>FONT
421         sta     ptr4+1
422         ldy     #$00
423 :       lda     (ptr3),y
424         beq     :+
425         sty     tmp1            ; Save string index
426         sec
427         sbc     #$1F            ; No control chars
428         asl                     ; Offset * 2
429         tay
430         clc
431         lda     FONT,y
432         adc     #<FONT
433         tax
434         lda     FONT+1,y
435         adc     #>FONT
436         tay
437         lda     ROT
438         jsr     DRAW            ; Draw char from string
439         ldx     ptr4
440         ldy     ptr4+1
441         lda     ROT
442         jsr     DRAW            ; Draw "connection char"
443         ldy     tmp1            ; Restore string index
444         iny
445         bne     :-              ; Branch always
446 :       bit     $C080           ; Switch in LC bank 2 for R/O
447         rts