]> git.sur5r.net Git - cc65/blob - libsrc/c128/mou/c128-joy.s
c1dc2e0193e82b9d303134280e4a8c1c6bd37206
[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 ; Global variables. The bounding box values are sorted so that they can be
78 ; written with the least effort in the SETBOX and GETBOX routines, so don't
79 ; reorder them.
80
81 .bss
82
83 Vars:
84 YPos:           .res    2               ; Current mouse position, Y
85 XPos:           .res    2               ; Current mouse position, X
86 XMin:           .res    2               ; X1 value of bounding box
87 YMin:           .res    2               ; Y1 value of bounding box
88 XMax:           .res    2               ; X2 value of bounding box
89 YMax:           .res    2               ; Y2 value of bounding box
90 Buttons:        .res    1               ; Button mask
91
92 INIT_save:      .res    1
93
94 ; Temporary value used in the int handler
95
96 Temp:           .res    1
97
98 ; Keyboard buffer fill level at start of interrupt
99
100 old_key_count:  .res    1
101
102 ; original IRQ vector
103
104 old_irq:        .res    2
105
106 .rodata
107
108 ; Default values for above variables
109 ; (We use ".proc" because we want to define both a label and a scope.)
110
111 .proc   DefVars
112         .word   SCREEN_HEIGHT/2         ; YPos
113         .word   SCREEN_WIDTH/2          ; XPos
114         .word   0                       ; XMin
115         .word   0                       ; YMin
116         .word   SCREEN_WIDTH - 1        ; XMax
117         .word   SCREEN_HEIGHT - 1       ; YMax
118         .byte   0                       ; Buttons
119 .endproc
120
121 .code
122
123 ;----------------------------------------------------------------------------
124 ; INSTALL routine. Is called after the driver is loaded into memory. If
125 ; possible, check if the hardware is present.
126 ; Must return an MOUSE_ERR_xx code in a/x.
127
128 INSTALL:
129
130 ; Disable the BASIC interpreter's interrupt-driven sprite-motion code.
131 ; That allows direct access to the VIC-IIe's sprite registers.
132
133         lda     INIT_STATUS
134         sta     INIT_save
135         lda     #%11000000
136         sta     INIT_STATUS
137
138 ; Initialize variables. Just copy the default stuff over
139
140         ldx     #.sizeof(DefVars)-1
141 @L1:    lda     DefVars,x
142         sta     Vars,x
143         dex
144         bpl     @L1
145
146 ; Be sure the mouse cursor is invisible and at the default location. We
147 ; need to do that here, because our mouse interrupt handler doesn't set the
148 ; mouse position if it hasn't changed.
149
150         sei
151         jsr     CHIDE
152         lda     XPos
153         ldx     XPos+1
154         jsr     CMOVEX
155         lda     YPos
156         ldx     YPos+1
157         jsr     CMOVEY
158
159 ; Initialize our IRQ magic
160
161         ; remember ROM IRQ continuation address
162         lda     IRQInd+2
163         sta     old_irq+1
164         lda     IRQInd+1
165         sta     old_irq
166
167         lda     libref
168         sta     ptr3
169         lda     libref+1
170         sta     ptr3+1
171
172         ; set ROM IRQ continuation address to point to the provided routine
173         ldy     #2
174         lda     (ptr3),y
175         sta     IRQInd+1
176         iny
177         lda     (ptr3),y
178         sta     IRQInd+2
179
180         ; set address of our IRQ callback routine
181         ; since it's called via "rts" we have to use "address-1"
182         iny
183         lda     #<(callback-1)
184         sta     (ptr3),y
185         iny
186         lda     #>(callback-1)
187         sta     (ptr3),y
188         iny
189
190         ; set ROM entry point vector
191         ; since it's called via "rts" we have to decrement it by one
192         lda     old_irq
193         sec
194         sbc     #1
195         sta     (ptr3),y
196         iny
197         lda     old_irq+1
198         sbc     #0
199         sta     (ptr3),y
200         cli
201
202 ; Done, return zero (= MOUSE_ERR_OK)
203
204         ldx     #$00
205         txa
206         rts
207
208 ;----------------------------------------------------------------------------
209 ; UNINSTALL routine. Is called before the driver is removed from memory.
210 ; No return code required (the driver is removed from memory on return).
211
212 UNINSTALL:
213         lda     old_irq
214         sei
215         sta     IRQInd+1
216         lda     old_irq+1
217         sta     IRQInd+2
218         cli
219
220         jsr     HIDE                    ; Hide cursor on exit
221         lda     INIT_save
222         sta     INIT_STATUS
223         rts
224
225 ;----------------------------------------------------------------------------
226 ; HIDE routine. Is called to hide the mouse pointer. The mouse kernel manages
227 ; a counter for calls to show/hide, and the driver entry point is only called
228 ; if the mouse is currently visible and should get hidden. For most drivers,
229 ; no special action is required besides hiding the mouse cursor.
230 ; No return code required.
231
232 HIDE:   sei
233         jsr     CHIDE
234         cli
235         rts
236
237 ;----------------------------------------------------------------------------
238 ; SHOW routine. Is called to show the mouse pointer. The mouse kernel manages
239 ; a counter for calls to show/hide, and the driver entry point is only called
240 ; if the mouse is currently hidden and should become visible. For most drivers,
241 ; no special action is required besides enabling the mouse cursor.
242 ; No return code required.
243
244 SHOW:   sei
245         jsr     CSHOW
246         cli
247         rts
248
249 ;----------------------------------------------------------------------------
250 ; SETBOX: Set the mouse bounding box. The parameters are passed as they come
251 ; from the C program, that is, a pointer to a mouse_box struct in a/x.
252 ; No checks are done if the mouse is currently inside the box, this is the job
253 ; of the caller. It is not necessary to validate the parameters, trust the
254 ; caller and save some code here. No return code required.
255
256 SETBOX: sta     ptr1
257         stx     ptr1+1                  ; Save data pointer
258
259         ldy     #.sizeof (MOUSE_BOX)-1
260         sei
261
262 @L1:    lda     (ptr1),y
263         sta     XMin,y
264         dey
265         bpl     @L1
266
267         cli
268         rts
269
270 ;----------------------------------------------------------------------------
271 ; GETBOX: Return the mouse bounding box. The parameters are passed as they
272 ; come from the C program, that is, a pointer to a mouse_box struct in a/x.
273
274 GETBOX: sta     ptr1
275         stx     ptr1+1                  ; Save data pointer
276
277         ldy     #.sizeof (MOUSE_BOX)-1
278         sei
279
280 @L1:    lda     XMin,y
281         sta     (ptr1),y
282         dey
283         bpl     @L1
284
285         cli
286         rts
287
288 ;----------------------------------------------------------------------------
289 ; MOVE: Move the mouse to a new position. The position is passed as it comes
290 ; from the C program, that is: X on the stack and Y in a/x. The C wrapper will
291 ; remove the parameter from the stack on return.
292 ; No checks are done if the new position is valid (within the bounding box or
293 ; the screen). No return code required.
294 ;
295
296 MOVE:   sei                             ; No interrupts
297
298         sta     YPos
299         stx     YPos+1                  ; New Y position
300         jsr     CMOVEY                  ; Set it
301
302         ldy     #$01
303         lda     (sp),y
304         sta     XPos+1
305         tax
306         dey
307         lda     (sp),y
308         sta     XPos                    ; New X position
309
310         jsr     CMOVEX                  ; Move the cursor
311
312         cli                             ; Allow interrupts
313         rts
314
315 ;----------------------------------------------------------------------------
316 ; BUTTONS: Return the button mask in a/x.
317
318 BUTTONS:
319         lda     Buttons
320         ldx     #$00
321         rts
322
323 ;----------------------------------------------------------------------------
324 ; POS: Return the mouse position in the MOUSE_POS struct pointed to by ptr1.
325 ; No return code required.
326
327 POS:    ldy     #MOUSE_POS::XCOORD      ; Structure offset
328
329         sei                             ; Disable interrupts
330         lda     XPos                    ; Transfer the position
331         sta     (ptr1),y
332         lda     XPos+1
333         iny
334         sta     (ptr1),y
335         lda     YPos
336         iny
337         sta     (ptr1),y
338         lda     YPos+1
339         cli                             ; Enable interrupts
340
341         iny
342         sta     (ptr1),y                ; Store last byte
343
344         rts                             ; Done
345
346 ;----------------------------------------------------------------------------
347 ; INFO: Returns mouse position and current button mask in the MOUSE_INFO
348 ; struct pointed to by ptr1. No return code required.
349 ;
350 ; We're cheating here to keep the code smaller: The first fields of the
351 ; mouse_info struct are identical to the mouse_pos struct, so we will just
352 ; call _mouse_pos to initialize the struct pointer and fill the position
353 ; fields.
354
355 INFO:   jsr     POS
356
357 ; Fill in the button state
358
359         lda     Buttons
360         ldy     #MOUSE_INFO::BUTTONS
361         sta     (ptr1),y
362
363         rts
364
365 ;----------------------------------------------------------------------------
366 ; IOCTL: Driver defined entry point. The wrapper will pass a pointer to ioctl
367 ; specific data in ptr1, and the ioctl code in A.
368 ; Must return an error code in a/x.
369 ;
370
371 IOCTL:  lda     #<MOUSE_ERR_INV_IOCTL     ; We don't support ioclts for now
372         ldx     #>MOUSE_ERR_INV_IOCTL
373         rts
374
375 ;----------------------------------------------------------------------------
376 ; IRQ: Irq handler entry point. Called as a subroutine but in IRQ context
377 ; (so be careful). The routine MUST return carry set if the interrupt has been
378 ; 'handled' - which means that the interrupt source is gone. Otherwise it
379 ; MUST return carry clear.
380 ;
381
382 IRQ:    jsr     CPREP
383         lda     KEY_COUNT
384         sta     old_key_count
385         lda     #$7F
386         sta     CIA1_PRA
387         lda     CIA1_PRB                ; Read joystick #0
388         and     #$1F
389         eor     #$1F                    ; Make all bits active high
390         sta     Temp
391
392 ; Check for a pressed button and place the result into Buttons
393
394         ldx     #$00                    ; Assume no button pressed
395         and     #JOY::FIRE              ; Check fire button
396         beq     @L0                     ; Jump if not pressed
397         ldx     #MOUSE_BTN_LEFT         ; Left (only) button is pressed
398 @L0:    stx     Buttons
399
400 ; Check left/right
401
402         lda     Temp                    ; Read joystick #0
403         and     #(JOY::LEFT | JOY::RIGHT)
404         beq     @SkipX                  ;
405
406 ; We will cheat here and rely on the fact that either the left, OR the right
407 ; bit can be active
408
409         and     #JOY::RIGHT             ; Check RIGHT bit
410         bne     @Right
411         lda     #$FF
412         tax
413         bne     @AddX                   ; Branch always
414 @Right: lda     #$01
415         ldx     #$00
416
417 ; Calculate the new X coordinate (--> a/y)
418
419 @AddX:  add     XPos
420         tay                             ; Remember low byte
421         txa
422         adc     XPos+1
423         tax
424
425 ; Limit the X coordinate to the bounding box
426
427         cpy     XMin
428         sbc     XMin+1
429         bpl     @L1
430         ldy     XMin
431         ldx     XMin+1
432         jmp     @L2
433 @L1:    txa
434
435         cpy     XMax
436         sbc     XMax+1
437         bmi     @L2
438         ldy     XMax
439         ldx     XMax+1
440 @L2:    sty     XPos
441         stx     XPos+1
442
443 ; Move the mouse pointer to the new X pos
444
445         tya
446         jsr     CMOVEX
447
448 ; Calculate the Y movement vector
449
450 @SkipX: lda     Temp                    ; Read joystick #0
451         and     #(JOY::UP | JOY::DOWN)  ; Check up/down
452         beq     @SkipY                  ;
453
454 ; We will cheat here and rely on the fact that either the up, OR the down
455 ; bit can be active
456
457         lsr     a                       ; Check UP bit
458         bcc     @Down
459         lda     #$FF
460         tax
461         bne     @AddY
462 @Down:  lda     #$01
463         ldx     #$00
464
465 ; Calculate the new Y coordinate (--> a/y)
466
467 @AddY:  add     YPos
468         tay                             ; Remember low byte
469         txa
470         adc     YPos+1
471         tax
472
473 ; Limit the Y coordinate to the bounding box
474
475         cpy     YMin
476         sbc     YMin+1
477         bpl     @L3
478         ldy     YMin
479         ldx     YMin+1
480         jmp     @L4
481 @L3:    txa
482
483         cpy     YMax
484         sbc     YMax+1
485         bmi     @L4
486         ldy     YMax
487         ldx     YMax+1
488 @L4:    sty     YPos
489         stx     YPos+1
490
491 ; Move the mouse pointer to the new X pos
492
493         tya
494         jsr     CMOVEY
495
496 ; Done
497
498 @SkipY: jsr     CDRAW
499         clc                             ; Interrupt not "handled"
500         rts
501
502 .define  OLD_BUTTONS Temp               ; tells callback.inc where the old port status is stored
503 .include "callback.inc"