]> git.sur5r.net Git - cc65/blob - libsrc/apple2/apple2-280-192-8.s
Added ioctl for mixing graphics with 4 lines of text.
[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 val msb and code to be 0
216         ora     ptr1+1
217         bne     err
218         
219         ; Check val 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         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     #7              ; Adjust X
405         bcs     :+
406         dey
407 :       tax
408         lda     Y1
409         plp                     ; Restore Z flag
410         bne     :+              ; Not vertical
411         sec
412         sbc     #7              ; 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