]> git.sur5r.net Git - cc65/blob - libsrc/c64/mou/c64-joy.s
Merge remote-tracking branch 'upstream/master' into a5200
[cc65] / libsrc / c64 / mou / c64-joy.s
1 ;
2 ; Driver for a "joystick mouse".
3 ;
4 ; Ullrich von Bassewitz, 2004-03-29, 2009-09-26
5 ; 2014-03-17, Greg King
6 ;
7 ; The driver prevents the keyboard from interfering by changing the
8 ; keyboard's output port into an input port while the driver reads its
9 ; controller device.  That disables a wire that is left active by the
10 ; Kernal.  That wire is used by the STOP-key to break out of BASIC
11 ; programs -- CC65 programs don't use that feature.  The wire is shared
12 ; by these keys: STOP, "Q", Commodore, Space, "2", CTRL, Left-Arrow, and
13 ; "1".  I listed them, in order, from bit 7 over to bit 0.  The
14 ; rightmost five keys can look like joystick switches.
15 ;
16 ; The driver prevents the mouse/joystick from interfering by "blinding"
17 ; the keyboard scanner while any button/switch is active.  It changes
18 ; the input port into an output port, then stores all zero-bits in that
19 ; port's latch.  Reading from an output port sees the bitwise-AND of the
20 ; latch and the input signals.  Therefore, the scanner thinks that eight
21 ; keys are being pushed at the same time.  It doesn't know what to do
22 ; about that condition; so, it does nothing.  The driver lets the
23 ; scanner see normally, again, when no buttons/switches are active.
24 ;
25
26         .include        "zeropage.inc"
27         .include        "mouse-kernel.inc"
28         .include        "c64.inc"
29
30         .macpack        generic
31
32 ; ------------------------------------------------------------------------
33 ; Header. Includes jump table
34
35 .segment        "JUMPTABLE"
36
37 HEADER:
38
39 ; Driver signature
40
41         .byte   $6d, $6f, $75           ; "mou"
42         .byte   MOUSE_API_VERSION       ; Mouse driver API version number
43
44 ; Library reference
45
46         .addr   $0000
47
48 ; Jump table
49
50         .addr   INSTALL
51         .addr   UNINSTALL
52         .addr   HIDE
53         .addr   SHOW
54         .addr   SETBOX
55         .addr   GETBOX
56         .addr   MOVE
57         .addr   BUTTONS
58         .addr   POS
59         .addr   INFO
60         .addr   IOCTL
61         .addr   IRQ
62
63 ; Mouse driver flags
64
65         .byte   MOUSE_FLAG_LATE_IRQ
66
67 ; Callback table, set by the kernel before INSTALL is called
68
69 CHIDE:  jmp     $0000                   ; Hide the cursor
70 CSHOW:  jmp     $0000                   ; Show the cursor
71 CPREP:  jmp     $0000                   ; Prepare to move the cursor
72 CDRAW:  jmp     $0000                   ; Draw the cursor
73 CMOVEX: jmp     $0000                   ; Move the cursor to X coord
74 CMOVEY: jmp     $0000                   ; Move the cursor to Y coord
75
76
77 ;----------------------------------------------------------------------------
78 ; Constants
79
80 SCREEN_HEIGHT   = 200
81 SCREEN_WIDTH    = 320
82
83 .enum   JOY
84         UP      = $01
85         DOWN    = $02
86         LEFT    = $04
87         RIGHT   = $08
88         FIRE    = $10
89 .endenum
90
91 ;----------------------------------------------------------------------------
92 ; Global variables. The bounding box values are sorted so that they can be
93 ; written with the least effort in the SETBOX and GETBOX routines, so don't
94 ; reorder them.
95
96 .bss
97
98 Vars:
99 YPos:           .res    2               ; Current mouse position, Y
100 XPos:           .res    2               ; Current mouse position, X
101 XMin:           .res    2               ; X1 value of bounding box
102 YMin:           .res    2               ; Y1 value of bounding box
103 XMax:           .res    2               ; X2 value of bounding box
104 YMax:           .res    2               ; Y2 value of bounding box
105 Buttons:        .res    1               ; Button mask
106
107 ; Temporary value used in the int handler
108
109 Temp:           .res    1
110
111 .rodata
112
113 ; Default values for above variables
114 ; (We use ".proc" because we want to define both a label and a scope.)
115
116 .proc   DefVars
117         .word   SCREEN_HEIGHT/2         ; YPos
118         .word   SCREEN_WIDTH/2          ; XPos
119         .word   0                       ; XMin
120         .word   0                       ; YMin
121         .word   SCREEN_WIDTH - 1        ; XMax
122         .word   SCREEN_HEIGHT - 1       ; YMax
123         .byte   0                       ; Buttons
124 .endproc
125
126 .code
127
128 ;----------------------------------------------------------------------------
129 ; INSTALL routine. Is called after the driver is loaded into memory. If
130 ; possible, check if the hardware is present.
131 ; Must return an MOUSE_ERR_xx code in a/x.
132
133 INSTALL:
134
135 ; Initialize variables. Just copy the default stuff over
136
137         ldx     #.sizeof(DefVars)-1
138 @L1:    lda     DefVars,x
139         sta     Vars,x
140         dex
141         bpl     @L1
142
143 ; Be sure the mouse cursor is invisible and at the default location. We
144 ; need to do that here, because our mouse interrupt handler doesn't set the
145 ; mouse position if it hasn't changed.
146
147         sei
148         jsr     CHIDE
149         lda     XPos
150         ldx     XPos+1
151         jsr     CMOVEX
152         lda     YPos
153         ldx     YPos+1
154         jsr     CMOVEY
155         cli
156
157 ; Done, return zero (= MOUSE_ERR_OK)
158
159         ldx     #$00
160         txa
161         rts
162
163 ;----------------------------------------------------------------------------
164 ; UNINSTALL routine. Is called before the driver is removed from memory.
165 ; No return code required (the driver is removed from memory on return).
166
167 UNINSTALL       = HIDE                  ; Hide cursor on exit
168
169 ;----------------------------------------------------------------------------
170 ; HIDE routine. Is called to hide the mouse pointer. The mouse kernel manages
171 ; a counter for calls to show/hide, and the driver entry point is only called
172 ; if the mouse is currently visible and should get hidden. For most drivers,
173 ; no special action is required besides hiding the mouse cursor.
174 ; No return code required.
175
176 HIDE:   sei
177         jsr     CHIDE
178         cli
179         rts
180
181 ;----------------------------------------------------------------------------
182 ; SHOW routine. Is called to show the mouse pointer. The mouse kernel manages
183 ; a counter for calls to show/hide, and the driver entry point is only called
184 ; if the mouse is currently hidden and should become visible. For most drivers,
185 ; no special action is required besides enabling the mouse cursor.
186 ; No return code required.
187
188 SHOW:   sei
189         jsr     CSHOW
190         cli
191         rts
192
193 ;----------------------------------------------------------------------------
194 ; SETBOX: Set the mouse bounding box. The parameters are passed as they come
195 ; from the C program, that is, a pointer to a mouse_box struct in a/x.
196 ; No checks are done if the mouse is currently inside the box, this is the job
197 ; of the caller. It is not necessary to validate the parameters, trust the
198 ; caller and save some code here. No return code required.
199
200 SETBOX: sta     ptr1
201         stx     ptr1+1                  ; Save data pointer
202
203         ldy     #.sizeof (MOUSE_BOX)-1
204         sei
205
206 @L1:    lda     (ptr1),y
207         sta     XMin,y
208         dey
209         bpl     @L1
210
211         cli
212         rts
213
214 ;----------------------------------------------------------------------------
215 ; GETBOX: Return the mouse bounding box. The parameters are passed as they
216 ; come from the C program, that is, a pointer to a mouse_box struct in a/x.
217
218 GETBOX: sta     ptr1
219         stx     ptr1+1                  ; Save data pointer
220
221         ldy     #.sizeof (MOUSE_BOX)-1
222
223 @L1:    lda     XMin,y
224         sta     (ptr1),y
225         dey
226         bpl     @L1
227
228         rts
229
230 ;----------------------------------------------------------------------------
231 ; MOVE: Move the mouse to a new position. The position is passed as it comes
232 ; from the C program, that is: X on the stack and Y in a/x. The C wrapper will
233 ; remove the parameter from the stack on return.
234 ; No checks are done if the new position is valid (within the bounding box or
235 ; the screen). No return code required.
236 ;
237
238 MOVE:   sei                             ; No interrupts
239
240         sta     YPos
241         stx     YPos+1                  ; New Y position
242         jsr     CMOVEY                  ; Set it
243
244         ldy     #$01
245         lda     (sp),y
246         sta     XPos+1
247         tax
248         dey
249         lda     (sp),y
250         sta     XPos                    ; New X position
251
252         jsr     CMOVEX                  ; Move the cursor
253
254         cli                             ; Allow interrupts
255         rts
256
257 ;----------------------------------------------------------------------------
258 ; BUTTONS: Return the button mask in a/x.
259
260 BUTTONS:
261         lda     Buttons
262         ldx     #$00
263         rts
264
265 ;----------------------------------------------------------------------------
266 ; POS: Return the mouse position in the MOUSE_POS struct pointed to by ptr1.
267 ; No return code required.
268
269 POS:    ldy     #MOUSE_POS::XCOORD      ; Structure offset
270
271         sei                             ; Disable interrupts
272         lda     XPos                    ; Transfer the position
273         sta     (ptr1),y
274         lda     XPos+1
275         iny
276         sta     (ptr1),y
277         lda     YPos
278         iny
279         sta     (ptr1),y
280         lda     YPos+1
281         cli                             ; Enable interrupts
282
283         iny
284         sta     (ptr1),y                ; Store last byte
285
286         rts                             ; Done
287
288 ;----------------------------------------------------------------------------
289 ; INFO: Returns mouse position and current button mask in the MOUSE_INFO
290 ; struct pointed to by ptr1. No return code required.
291 ;
292 ; We're cheating here to keep the code smaller: The first fields of the
293 ; mouse_info struct are identical to the mouse_pos struct, so we will just
294 ; call _mouse_pos to initialize the struct pointer and fill the position
295 ; fields.
296
297 INFO:   jsr     POS
298
299 ; Fill in the button state
300
301         lda     Buttons
302         ldy     #MOUSE_INFO::BUTTONS
303         sta     (ptr1),y
304
305         rts
306
307 ;----------------------------------------------------------------------------
308 ; IOCTL: Driver defined entry point. The wrapper will pass a pointer to ioctl
309 ; specific data in ptr1, and the ioctl code in A.
310 ; Must return an error code in a/x.
311 ;
312
313 IOCTL:  lda     #<MOUSE_ERR_INV_IOCTL     ; We don't support ioclts for now
314         ldx     #>MOUSE_ERR_INV_IOCTL
315         rts
316
317 ;----------------------------------------------------------------------------
318 ; IRQ: Irq handler entry point. Called as a subroutine but in IRQ context
319 ; (so be careful). The routine MUST return carry set if the interrupt has been
320 ; 'handled' - which means that the interrupt source is gone. Otherwise it
321 ; MUST return carry clear.
322 ;
323
324 IRQ:    jsr     CPREP
325
326 ; Avoid crosstalk between the keyboard and a joystick.
327
328         ldy     #%00000000              ; Set ports A and B to input
329         sty     CIA1_DDRB
330         sty     CIA1_DDRA               ; Keyboard won't look like joystick
331         lda     CIA1_PRB                ; Read Control-Port 1
332         dec     CIA1_DDRA               ; Set port A back to output
333         eor     #%11111111              ; Bit goes up when switch goes down
334         beq     @Save                   ;(bze)
335         dec     CIA1_DDRB               ; Joystick won't look like keyboard
336         sty     CIA1_PRB                ; Set "all keys pushed"
337 @Save:  sta     Temp
338
339 ; Check for a pressed button and place the result into Buttons
340
341         ldx     #$00                    ; Assume no button pressed
342         and     #JOY::FIRE              ; Check fire button
343         beq     @L0                     ; Jump if not pressed
344         ldx     #MOUSE_BTN_LEFT         ; Left (only) button is pressed
345 @L0:    stx     Buttons
346
347 ; Check left/right
348
349         lda     Temp                    ; Read joystick #0
350         and     #(JOY::LEFT | JOY::RIGHT)
351         beq     @SkipX                  ;
352
353 ; We will cheat here and rely on the fact that either the left, OR the right
354 ; bit can be active
355
356         and     #JOY::RIGHT             ; Check RIGHT bit
357         bne     @Right
358         lda     #$FF
359         tax
360         bne     @AddX                   ; Branch always
361 @Right: lda     #$01
362         ldx     #$00
363
364 ; Calculate the new X coordinate (--> a/y)
365
366 @AddX:  add     XPos
367         tay                             ; Remember low byte
368         txa
369         adc     XPos+1
370         tax
371
372 ; Limit the X coordinate to the bounding box
373
374         cpy     XMin
375         sbc     XMin+1
376         bpl     @L1
377         ldy     XMin
378         ldx     XMin+1
379         jmp     @L2
380 @L1:    txa
381
382         cpy     XMax
383         sbc     XMax+1
384         bmi     @L2
385         ldy     XMax
386         ldx     XMax+1
387 @L2:    sty     XPos
388         stx     XPos+1
389
390 ; Move the mouse pointer to the new X pos
391
392         tya
393         jsr     CMOVEX
394
395 ; Calculate the Y movement vector
396
397 @SkipX: lda     Temp                    ; Read joystick #0
398         and     #(JOY::UP | JOY::DOWN)  ; Check up/down
399         beq     @SkipY                  ;
400
401 ; We will cheat here and rely on the fact that either the up, OR the down
402 ; bit can be active
403
404         lsr     a                       ; Check UP bit
405         bcc     @Down
406         lda     #$FF
407         tax
408         bne     @AddY
409 @Down:  lda     #$01
410         ldx     #$00
411
412 ; Calculate the new Y coordinate (--> a/y)
413
414 @AddY:  add     YPos
415         tay                             ; Remember low byte
416         txa
417         adc     YPos+1
418         tax
419
420 ; Limit the Y coordinate to the bounding box
421
422         cpy     YMin
423         sbc     YMin+1
424         bpl     @L3
425         ldy     YMin
426         ldx     YMin+1
427         jmp     @L4
428 @L3:    txa
429
430         cpy     YMax
431         sbc     YMax+1
432         bmi     @L4
433         ldy     YMax
434         ldx     YMax+1
435 @L4:    sty     YPos
436         stx     YPos+1
437
438 ; Move the mouse pointer to the new X pos
439
440         tya
441         jsr     CMOVEY
442
443 ; Done
444
445 @SkipY: jsr     CDRAW
446         clc                             ; Interrupt not "handled"
447         rts
448