]> git.sur5r.net Git - cc65/blob - libsrc/c128/mou/c128-pot.s
add gotox, gotoy, and gotoxy
[cc65] / libsrc / c128 / mou / c128-pot.s
1 ;
2 ; Driver for a potentiometer "mouse" e.g. Koala Pad
3 ;
4 ; Ullrich von Bassewitz, 2004-03-29, 2009-09-26
5 ; Stefan Haubenthal, 2006-08-20
6 ;
7
8         .include        "zeropage.inc"
9         .include        "mouse-kernel.inc"
10         .include        "c128.inc"
11
12         .macpack        generic
13
14 ; ------------------------------------------------------------------------
15 ; Header. Includes jump table
16
17 .segment        "JUMPTABLE"
18
19 HEADER:
20
21 ; Driver signature
22
23         .byte   $6d, $6f, $75           ; "mou"
24         .byte   MOUSE_API_VERSION       ; Mouse driver API version number
25
26 ; Library reference
27
28         .addr   $0000
29
30 ; Jump table
31
32         .addr   INSTALL
33         .addr   UNINSTALL
34         .addr   HIDE
35         .addr   SHOW
36         .addr   SETBOX
37         .addr   GETBOX
38         .addr   MOVE
39         .addr   BUTTONS
40         .addr   POS
41         .addr   INFO
42         .addr   IOCTL
43         .addr   IRQ
44
45 ; Callback table, set by the kernel before INSTALL is called
46
47 CHIDE:  jmp     $0000                   ; Hide the cursor
48 CSHOW:  jmp     $0000                   ; Show the cursor
49 CPREP:  jmp     $0000                   ; Prepare to move the cursor
50 CDRAW:  jmp     $0000                   ; Draw the cursor
51 CMOVEX: jmp     $0000                   ; Move the cursor to X coord
52 CMOVEY: jmp     $0000                   ; Move the cursor to Y coord
53
54
55 ;----------------------------------------------------------------------------
56 ; Constants
57
58 SCREEN_HEIGHT   = 200
59 SCREEN_WIDTH    = 320
60
61 .enum   JOY
62         UP      = $01
63         DOWN    = $02
64         LEFT    = $04
65         RIGHT   = $08
66         FIRE    = $10
67 .endenum
68
69 ;----------------------------------------------------------------------------
70 ; Global variables. The bounding box values are sorted so that they can be
71 ; written with the least effort in the SETBOX and GETBOX routines, so don't
72 ; reorder them.
73
74 .bss
75
76 Vars:
77 YPos:           .res    2               ; Current mouse position, Y
78 XPos:           .res    2               ; Current mouse position, X
79 XMin:           .res    2               ; X1 value of bounding box
80 YMin:           .res    2               ; Y1 value of bounding box
81 XMax:           .res    2               ; X2 value of bounding box
82 YMax:           .res    2               ; Y2 value of bounding box
83 Buttons:        .res    1               ; Button mask
84
85 ; Temporary value used in the int handler
86
87 Temp:           .res    1
88
89 .rodata
90
91 ; Default values for above variables
92 ; (We use ".proc" because we want to define both a label and a scope.)
93
94 .proc   DefVars
95         .word   SCREEN_HEIGHT/2         ; YPos
96         .word   SCREEN_WIDTH/2          ; XPos
97         .word   0                       ; XMin
98         .word   0                       ; YMin
99         .word   SCREEN_WIDTH            ; XMax
100         .word   SCREEN_HEIGHT           ; YMax
101         .byte   0                       ; Buttons
102 .endproc
103
104 .code
105
106 ;----------------------------------------------------------------------------
107 ; INSTALL routine. Is called after the driver is loaded into memory. If
108 ; possible, check if the hardware is present.
109 ; Must return an MOUSE_ERR_xx code in a/x.
110
111 INSTALL:
112
113 ; Initialize variables. Just copy the default stuff over
114
115         ldx     #.sizeof(DefVars)-1
116 @L1:    lda     DefVars,x
117         sta     Vars,x
118         dex
119         bpl     @L1
120
121 ; Be sure the mouse cursor is invisible and at the default location. We
122 ; need to do that here, because our mouse interrupt handler doesn't set the
123 ; mouse position if it hasn't changed.
124
125         sei
126         jsr     CHIDE
127         lda     XPos
128         ldx     XPos+1
129         jsr     CMOVEX
130         lda     YPos
131         ldx     YPos+1
132         jsr     CMOVEY
133         cli
134
135 ; Done, return zero (= MOUSE_ERR_OK)
136
137         ldx     #$00
138         txa
139         rts
140
141 ;----------------------------------------------------------------------------
142 ; UNINSTALL routine. Is called before the driver is removed from memory.
143 ; No return code required (the driver is removed from memory on return).
144
145 UNINSTALL       = HIDE                  ; Hide cursor on exit
146
147 ;----------------------------------------------------------------------------
148 ; HIDE routine. Is called to hide the mouse pointer. The mouse kernel manages
149 ; a counter for calls to show/hide, and the driver entry point is only called
150 ; if the mouse is currently visible and should get hidden. For most drivers,
151 ; no special action is required besides hiding the mouse cursor.
152 ; No return code required.
153
154 HIDE:   sei
155         jsr     CHIDE
156         cli
157         rts
158
159 ;----------------------------------------------------------------------------
160 ; SHOW routine. Is called to show the mouse pointer. The mouse kernel manages
161 ; a counter for calls to show/hide, and the driver entry point is only called
162 ; if the mouse is currently hidden and should become visible. For most drivers,
163 ; no special action is required besides enabling the mouse cursor.
164 ; No return code required.
165
166 SHOW:   sei
167         jsr     CSHOW
168         cli
169         rts
170
171 ;----------------------------------------------------------------------------
172 ; SETBOX: Set the mouse bounding box. The parameters are passed as they come
173 ; from the C program, that is, a pointer to a mouse_box struct in a/x.
174 ; No checks are done if the mouse is currently inside the box, this is the job
175 ; of the caller. It is not necessary to validate the parameters, trust the
176 ; caller and save some code here. No return code required.
177
178 SETBOX: sta     ptr1
179         stx     ptr1+1                  ; Save data pointer
180
181         ldy     #.sizeof (MOUSE_BOX)-1
182         sei
183
184 @L1:    lda     (ptr1),y
185         sta     XMin,y
186         dey
187         bpl     @L1
188
189         cli
190         rts
191
192 ;----------------------------------------------------------------------------
193 ; GETBOX: Return the mouse bounding box. The parameters are passed as they
194 ; come from the C program, that is, a pointer to a mouse_box struct in a/x.
195
196 GETBOX: sta     ptr1
197         stx     ptr1+1                  ; Save data pointer
198
199         ldy     #.sizeof (MOUSE_BOX)-1
200         sei
201
202 @L1:    lda     XMin,y
203         sta     (ptr1),y
204         dey
205         bpl     @L1
206
207         cli
208         rts
209
210 ;----------------------------------------------------------------------------
211 ; MOVE: Move the mouse to a new position. The position is passed as it comes
212 ; from the C program, that is: X on the stack and Y in a/x. The C wrapper will
213 ; remove the parameter from the stack on return.
214 ; No checks are done if the new position is valid (within the bounding box or
215 ; the screen). No return code required.
216 ;
217
218 MOVE:   sei                             ; No interrupts
219
220         sta     YPos
221         stx     YPos+1                  ; New Y position
222         jsr     CMOVEY                  ; Set it
223
224         ldy     #$01
225         lda     (sp),y
226         sta     XPos+1
227         tax
228         dey
229         lda     (sp),y
230         sta     XPos                    ; New X position
231
232         jsr     CMOVEX                  ; Move the cursor
233
234         cli                             ; Allow interrupts
235         rts
236
237 ;----------------------------------------------------------------------------
238 ; BUTTONS: Return the button mask in a/x.
239
240 BUTTONS:
241         lda     Buttons
242         ldx     #$00
243         rts
244
245 ;----------------------------------------------------------------------------
246 ; POS: Return the mouse position in the MOUSE_POS struct pointed to by ptr1.
247 ; No return code required.
248
249 POS:    ldy     #MOUSE_POS::XCOORD      ; Structure offset
250
251         sei                             ; Disable interrupts
252         lda     XPos                    ; Transfer the position
253         sta     (ptr1),y
254         lda     XPos+1
255         iny
256         sta     (ptr1),y
257         lda     YPos
258         iny
259         sta     (ptr1),y
260         lda     YPos+1
261         cli                             ; Enable interrupts
262
263         iny
264         sta     (ptr1),y                ; Store last byte
265
266         rts                             ; Done
267
268 ;----------------------------------------------------------------------------
269 ; INFO: Returns mouse position and current button mask in the MOUSE_INFO
270 ; struct pointed to by ptr1. No return code required.
271 ;
272 ; We're cheating here to keep the code smaller: The first fields of the
273 ; mouse_info struct are identical to the mouse_pos struct, so we will just
274 ; call _mouse_pos to initialize the struct pointer and fill the position
275 ; fields.
276
277 INFO:   jsr     POS
278
279 ; Fill in the button state
280
281         lda     Buttons
282         ldy     #MOUSE_INFO::BUTTONS
283         sta     (ptr1),y
284
285         rts
286
287 ;----------------------------------------------------------------------------
288 ; IOCTL: Driver defined entry point. The wrapper will pass a pointer to ioctl
289 ; specific data in ptr1, and the ioctl code in A.
290 ; Must return an error code in a/x.
291 ;
292
293 IOCTL:  lda     #<MOUSE_ERR_INV_IOCTL     ; We don't support ioclts for now
294         ldx     #>MOUSE_ERR_INV_IOCTL
295         rts
296
297 ;----------------------------------------------------------------------------
298 ; IRQ: Irq handler entry point. Called as a subroutine but in IRQ context
299 ; (so be careful).
300 ;
301
302 IRQ:    jsr     CPREP
303         lda     #$7F
304         sta     CIA1_PRA
305         lda     CIA1_PRB                ; Read port #1
306         and     #%00001100
307         eor     #%00001100              ; Make all bits active high
308         asl
309         sta     Buttons
310         lsr
311         lsr
312         lsr
313         and     #%00000001
314         ora     Buttons
315         sta     Buttons
316         ldx     #%01000000
317         stx     CIA1_PRA
318         ldy     #0
319 :       dey
320         bne     :-
321         ldx     SID_ADConv1
322         stx     XPos
323         ldx     SID_ADConv2
324         stx     YPos
325
326         lda     #$FF
327         tax
328         bne     @AddX                   ; Branch always
329         lda     #$01
330         ldx     #$00
331
332 ; Calculate the new X coordinate (--> a/y)
333
334 @AddX:  add     XPos
335         tay                             ; Remember low byte
336         txa
337         adc     XPos+1
338         tax
339
340 ; Limit the X coordinate to the bounding box
341
342         cpy     XMin
343         sbc     XMin+1
344         bpl     @L1
345         ldy     XMin
346         ldx     XMin+1
347         jmp     @L2
348 @L1:    txa
349
350         cpy     XMax
351         sbc     XMax+1
352         bmi     @L2
353         ldy     XMax
354         ldx     XMax+1
355 @L2:    sty     XPos
356         stx     XPos+1
357
358 ; Move the mouse pointer to the new X pos
359
360         tya
361         jsr     CMOVEX
362
363         lda     #$FF
364         tax
365         bne     @AddY
366 @Down:  lda     #$01
367         ldx     #$00
368
369 ; Calculate the new Y coordinate (--> a/y)
370
371 @AddY:  add     YPos
372         tay                             ; Remember low byte
373         txa
374         adc     YPos+1
375         tax
376
377 ; Limit the Y coordinate to the bounding box
378
379         cpy     YMin
380         sbc     YMin+1
381         bpl     @L3
382         ldy     YMin
383         ldx     YMin+1
384         jmp     @L4
385 @L3:    txa
386
387         cpy     YMax
388         sbc     YMax+1
389         bmi     @L4
390         ldy     YMax
391         ldx     YMax+1
392 @L4:    sty     YPos
393         stx     YPos+1
394
395 ; Move the mouse pointer to the new X pos
396
397         tya
398         jsr     CMOVEY
399         jsr     CDRAW
400         clc                             ; Interrupt not "handled"
401         rts