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