]> git.sur5r.net Git - cc65/blob - libsrc/c128/mou/c128-joy.s
Make the hooking and unhooking of the interrupt interrupt safe.
[cc65] / libsrc / c128 / mou / c128-joy.s
1 ;
2 ; Driver for a "joystick mouse".
3 ;
4 ; 2009-09-26, Ullrich von Bassewitz
5 ; 2014-03-17, Greg King
6 ;
7
8         .include        "zeropage.inc"
9         .include        "mouse-kernel.inc"
10         .include        "c128.inc"
11
12         .macpack        generic
13
14 IRQInd  = $2FD
15
16 ; ------------------------------------------------------------------------
17 ; Header. Includes jump table
18
19 .segment        "JUMPTABLE"
20
21 HEADER:
22
23 ; Driver signature
24
25         .byte   $6d, $6f, $75           ; "mou"
26         .byte   MOUSE_API_VERSION       ; Mouse driver API version number
27
28 ; Library reference
29
30 libref:
31         .addr   $0000
32
33 ; Jump table
34
35         .addr   INSTALL
36         .addr   UNINSTALL
37         .addr   HIDE
38         .addr   SHOW
39         .addr   SETBOX
40         .addr   GETBOX
41         .addr   MOVE
42         .addr   BUTTONS
43         .addr   POS
44         .addr   INFO
45         .addr   IOCTL
46         .addr   IRQ
47
48 ; Mouse driver flags
49
50         .byte   MOUSE_FLAG_LATE_IRQ
51
52 ; Callback table, set by the kernel before INSTALL is called
53
54 CHIDE:  jmp     $0000                   ; Hide the cursor
55 CSHOW:  jmp     $0000                   ; Show the cursor
56 CPREP:  jmp     $0000                   ; Prepare to move the cursor
57 CDRAW:  jmp     $0000                   ; Draw the cursor
58 CMOVEX: jmp     $0000                   ; Move the cursor to X coord
59 CMOVEY: jmp     $0000                   ; Move the cursor to Y coord
60
61
62 ;----------------------------------------------------------------------------
63 ; Constants
64
65 SCREEN_HEIGHT   = 200
66 SCREEN_WIDTH    = 320
67
68 .enum   JOY
69         UP      = $01
70         DOWN    = $02
71         LEFT    = $04
72         RIGHT   = $08
73         FIRE    = $10
74 .endenum
75
76 ;----------------------------------------------------------------------------
77 ; data segment
78
79 .data
80
81 chainIRQ:
82         .byte   $4c                     ; JMP opcode
83         .word   0                       ; pointer to ROM IRQ handler (will be set at runtime)
84
85 ;----------------------------------------------------------------------------
86 ; Global variables. The bounding box values are sorted so that they can be
87 ; written with the least effort in the SETBOX and GETBOX routines, so don't
88 ; reorder them.
89
90 .bss
91
92 Vars:
93 YPos:           .res    2               ; Current mouse position, Y
94 XPos:           .res    2               ; Current mouse position, X
95 XMin:           .res    2               ; X1 value of bounding box
96 YMin:           .res    2               ; Y1 value of bounding box
97 XMax:           .res    2               ; X2 value of bounding box
98 YMax:           .res    2               ; Y2 value of bounding box
99 Buttons:        .res    1               ; Button mask
100
101 INIT_save:      .res    1
102
103 ; Temporary value used in the int handler
104
105 Temp:           .res    1
106
107 ; Keyboard buffer fill level at start of interrupt
108
109 old_key_count:  .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 ; Disable the BASIC interpreter's interrupt-driven sprite-motion code.
136 ; That allows direct access to the VIC-IIe's sprite registers.
137
138         lda     INIT_STATUS
139         sta     INIT_save
140         lda     #%11000000
141         sta     INIT_STATUS
142
143 ; Initialize variables. Just copy the default stuff over
144
145         ldx     #.sizeof(DefVars)-1
146 @L1:    lda     DefVars,x
147         sta     Vars,x
148         dex
149         bpl     @L1
150
151 ; Be sure the mouse cursor is invisible and at the default location. We
152 ; need to do that here, because our mouse interrupt handler doesn't set the
153 ; mouse position if it hasn't changed.
154
155         sei
156         jsr     CHIDE
157         lda     XPos
158         ldx     XPos+1
159         jsr     CMOVEX
160         lda     YPos
161         ldx     YPos+1
162         jsr     CMOVEY
163
164 ; Initialize our IRQ magic
165
166         lda     IRQInd+1
167         sta     chainIRQ+1
168         lda     IRQInd+2
169         sta     chainIRQ+2
170         lda     libref
171         sta     ptr3
172         lda     libref+1
173         sta     ptr3+1
174         ldy     #2
175         lda     (ptr3),y
176         sta     IRQInd+1
177         iny
178         lda     (ptr3),y
179         sta     IRQInd+2
180         iny
181         lda     #<(callback-1)
182         sta     (ptr3),y
183         iny
184         lda     #>(callback-1)
185         sta     (ptr3),y
186         iny
187         lda     #<(chainIRQ-1)
188         sta     (ptr3),y
189         iny
190         lda     #>(chainIRQ-1)
191         sta     (ptr3),y
192         cli
193
194 ; Done, return zero (= MOUSE_ERR_OK)
195
196         ldx     #$00
197         txa
198         rts
199
200 ;----------------------------------------------------------------------------
201 ; UNINSTALL routine. Is called before the driver is removed from memory.
202 ; No return code required (the driver is removed from memory on return).
203
204 UNINSTALL:
205         lda     chainIRQ+1
206         sei
207         sta     IRQInd+1
208         lda     chainIRQ+2
209         sta     IRQInd+2
210         cli
211
212         jsr     HIDE                    ; Hide cursor on exit
213         lda     INIT_save
214         sta     INIT_STATUS
215         rts
216
217 ;----------------------------------------------------------------------------
218 ; HIDE routine. Is called to hide the mouse pointer. The mouse kernel manages
219 ; a counter for calls to show/hide, and the driver entry point is only called
220 ; if the mouse is currently visible and should get hidden. For most drivers,
221 ; no special action is required besides hiding the mouse cursor.
222 ; No return code required.
223
224 HIDE:   sei
225         jsr     CHIDE
226         cli
227         rts
228
229 ;----------------------------------------------------------------------------
230 ; SHOW routine. Is called to show the mouse pointer. The mouse kernel manages
231 ; a counter for calls to show/hide, and the driver entry point is only called
232 ; if the mouse is currently hidden and should become visible. For most drivers,
233 ; no special action is required besides enabling the mouse cursor.
234 ; No return code required.
235
236 SHOW:   sei
237         jsr     CSHOW
238         cli
239         rts
240
241 ;----------------------------------------------------------------------------
242 ; SETBOX: Set the mouse bounding box. The parameters are passed as they come
243 ; from the C program, that is, a pointer to a mouse_box struct in a/x.
244 ; No checks are done if the mouse is currently inside the box, this is the job
245 ; of the caller. It is not necessary to validate the parameters, trust the
246 ; caller and save some code here. No return code required.
247
248 SETBOX: sta     ptr1
249         stx     ptr1+1                  ; Save data pointer
250
251         ldy     #.sizeof (MOUSE_BOX)-1
252         sei
253
254 @L1:    lda     (ptr1),y
255         sta     XMin,y
256         dey
257         bpl     @L1
258
259         cli
260         rts
261
262 ;----------------------------------------------------------------------------
263 ; GETBOX: Return the mouse bounding box. The parameters are passed as they
264 ; come from the C program, that is, a pointer to a mouse_box struct in a/x.
265
266 GETBOX: sta     ptr1
267         stx     ptr1+1                  ; Save data pointer
268
269         ldy     #.sizeof (MOUSE_BOX)-1
270         sei
271
272 @L1:    lda     XMin,y
273         sta     (ptr1),y
274         dey
275         bpl     @L1
276
277         cli
278         rts
279
280 ;----------------------------------------------------------------------------
281 ; MOVE: Move the mouse to a new position. The position is passed as it comes
282 ; from the C program, that is: X on the stack and Y in a/x. The C wrapper will
283 ; remove the parameter from the stack on return.
284 ; No checks are done if the new position is valid (within the bounding box or
285 ; the screen). No return code required.
286 ;
287
288 MOVE:   sei                             ; No interrupts
289
290         sta     YPos
291         stx     YPos+1                  ; New Y position
292         jsr     CMOVEY                  ; Set it
293
294         ldy     #$01
295         lda     (sp),y
296         sta     XPos+1
297         tax
298         dey
299         lda     (sp),y
300         sta     XPos                    ; New X position
301
302         jsr     CMOVEX                  ; Move the cursor
303
304         cli                             ; Allow interrupts
305         rts
306
307 ;----------------------------------------------------------------------------
308 ; BUTTONS: Return the button mask in a/x.
309
310 BUTTONS:
311         lda     Buttons
312         ldx     #$00
313         rts
314
315 ;----------------------------------------------------------------------------
316 ; POS: Return the mouse position in the MOUSE_POS struct pointed to by ptr1.
317 ; No return code required.
318
319 POS:    ldy     #MOUSE_POS::XCOORD      ; Structure offset
320
321         sei                             ; Disable interrupts
322         lda     XPos                    ; Transfer the position
323         sta     (ptr1),y
324         lda     XPos+1
325         iny
326         sta     (ptr1),y
327         lda     YPos
328         iny
329         sta     (ptr1),y
330         lda     YPos+1
331         cli                             ; Enable interrupts
332
333         iny
334         sta     (ptr1),y                ; Store last byte
335
336         rts                             ; Done
337
338 ;----------------------------------------------------------------------------
339 ; INFO: Returns mouse position and current button mask in the MOUSE_INFO
340 ; struct pointed to by ptr1. No return code required.
341 ;
342 ; We're cheating here to keep the code smaller: The first fields of the
343 ; mouse_info struct are identical to the mouse_pos struct, so we will just
344 ; call _mouse_pos to initialize the struct pointer and fill the position
345 ; fields.
346
347 INFO:   jsr     POS
348
349 ; Fill in the button state
350
351         lda     Buttons
352         ldy     #MOUSE_INFO::BUTTONS
353         sta     (ptr1),y
354
355         rts
356
357 ;----------------------------------------------------------------------------
358 ; IOCTL: Driver defined entry point. The wrapper will pass a pointer to ioctl
359 ; specific data in ptr1, and the ioctl code in A.
360 ; Must return an error code in a/x.
361 ;
362
363 IOCTL:  lda     #<MOUSE_ERR_INV_IOCTL     ; We don't support ioclts for now
364         ldx     #>MOUSE_ERR_INV_IOCTL
365         rts
366
367 ;----------------------------------------------------------------------------
368 ; IRQ: Irq handler entry point. Called as a subroutine but in IRQ context
369 ; (so be careful). The routine MUST return carry set if the interrupt has been
370 ; 'handled' - which means that the interrupt source is gone. Otherwise it
371 ; MUST return carry clear.
372 ;
373
374 IRQ:    jsr     CPREP
375         lda     KEY_COUNT
376         sta     old_key_count
377         lda     #$7F
378         sta     CIA1_PRA
379         lda     CIA1_PRB                ; Read joystick #0
380         and     #$1F
381         eor     #$1F                    ; Make all bits active high
382         sta     Temp
383
384 ; Check for a pressed button and place the result into Buttons
385
386         ldx     #$00                    ; Assume no button pressed
387         and     #JOY::FIRE              ; Check fire button
388         beq     @L0                     ; Jump if not pressed
389         ldx     #MOUSE_BTN_LEFT         ; Left (only) button is pressed
390 @L0:    stx     Buttons
391
392 ; Check left/right
393
394         lda     Temp                    ; Read joystick #0
395         and     #(JOY::LEFT | JOY::RIGHT)
396         beq     @SkipX                  ;
397
398 ; We will cheat here and rely on the fact that either the left, OR the right
399 ; bit can be active
400
401         and     #JOY::RIGHT             ; Check RIGHT bit
402         bne     @Right
403         lda     #$FF
404         tax
405         bne     @AddX                   ; Branch always
406 @Right: lda     #$01
407         ldx     #$00
408
409 ; Calculate the new X coordinate (--> a/y)
410
411 @AddX:  add     XPos
412         tay                             ; Remember low byte
413         txa
414         adc     XPos+1
415         tax
416
417 ; Limit the X coordinate to the bounding box
418
419         cpy     XMin
420         sbc     XMin+1
421         bpl     @L1
422         ldy     XMin
423         ldx     XMin+1
424         jmp     @L2
425 @L1:    txa
426
427         cpy     XMax
428         sbc     XMax+1
429         bmi     @L2
430         ldy     XMax
431         ldx     XMax+1
432 @L2:    sty     XPos
433         stx     XPos+1
434
435 ; Move the mouse pointer to the new X pos
436
437         tya
438         jsr     CMOVEX
439
440 ; Calculate the Y movement vector
441
442 @SkipX: lda     Temp                    ; Read joystick #0
443         and     #(JOY::UP | JOY::DOWN)  ; Check up/down
444         beq     @SkipY                  ;
445
446 ; We will cheat here and rely on the fact that either the up, OR the down
447 ; bit can be active
448
449         lsr     a                       ; Check UP bit
450         bcc     @Down
451         lda     #$FF
452         tax
453         bne     @AddY
454 @Down:  lda     #$01
455         ldx     #$00
456
457 ; Calculate the new Y coordinate (--> a/y)
458
459 @AddY:  add     YPos
460         tay                             ; Remember low byte
461         txa
462         adc     YPos+1
463         tax
464
465 ; Limit the Y coordinate to the bounding box
466
467         cpy     YMin
468         sbc     YMin+1
469         bpl     @L3
470         ldy     YMin
471         ldx     YMin+1
472         jmp     @L4
473 @L3:    txa
474
475         cpy     YMax
476         sbc     YMax+1
477         bmi     @L4
478         ldy     YMax
479         ldx     YMax+1
480 @L4:    sty     YPos
481         stx     YPos+1
482
483 ; Move the mouse pointer to the new X pos
484
485         tya
486         jsr     CMOVEY
487
488 ; Done
489
490 @SkipY: jsr     CDRAW
491         clc                             ; Interrupt not "handled"
492         rts
493
494 ;----------------------------------------------------------------------------
495 ; Called after ROM IRQ handler has been run.
496 ; Check if there was joystick activity before and/or after the ROM handler.
497 ; If there was activity, discard the key presses since they are most
498 ; probably "phantom" key presses.
499
500 callback:
501         ldx     old_key_count
502         cpx     KEY_COUNT
503         beq     @nokey
504
505         lda     Temp                    ; keypress before?
506         bne     @discard_key            ; yes, discard key
507
508         lda     #$7F
509         sta     CIA1_PRA
510         lda     CIA1_PRB                ; Read joystick #0
511         and     #$1F
512         eor     #$1F                    ; keypress after
513         beq     @nokey                  ; no, probably a real key press
514
515 @discard_key:
516         stx     KEY_COUNT               ; set old keyboard buffer fill level
517
518 @nokey: rts