]> git.sur5r.net Git - cc65/blob - libsrc/c128/mou/c128-joy.s
Add handling of write requests
[cc65] / libsrc / c128 / mou / c128-joy.s
1 ;
2 ; Driver for a "joystick mouse".
3 ;
4 ; Ullrich von Bassewitz, 2004-04-05, 2009-09-26
5 ;
6
7         .include        "zeropage.inc"
8         .include        "mouse-kernel.inc"
9         .include        "c128.inc"
10
11         .macpack        generic
12
13 ; ------------------------------------------------------------------------
14 ; Header. Includes jump table
15
16 .segment        "JUMPTABLE"
17
18 HEADER:
19
20 ; Driver signature
21
22         .byte   $6d, $6f, $75           ; "mou"
23         .byte   MOUSE_API_VERSION       ; Mouse driver API version number
24
25 ; Library reference
26
27         .addr   $0000
28
29 ; Jump table
30
31         .addr   INSTALL
32         .addr   UNINSTALL
33         .addr   HIDE
34         .addr   SHOW
35         .addr   SETBOX
36         .addr   GETBOX
37         .addr   MOVE
38         .addr   BUTTONS
39         .addr   POS
40         .addr   INFO
41         .addr   IOCTL
42         .addr   IRQ
43
44 ; Mouse driver flags
45
46         .byte   MOUSE_FLAG_LATE_IRQ
47
48 ; Callback table, set by the kernel before INSTALL is called
49
50 CHIDE:  jmp     $0000                   ; Hide the cursor
51 CSHOW:  jmp     $0000                   ; Show the cursor
52 CMOVEX: jmp     $0000                   ; Move the cursor to X coord
53 CMOVEY: jmp     $0000                   ; Move the cursor to Y coord
54
55
56 ;----------------------------------------------------------------------------
57 ; Constants
58
59 SCREEN_HEIGHT   = 200
60 SCREEN_WIDTH    = 320
61
62 .enum   JOY
63         UP      = $01
64         DOWN    = $02
65         LEFT    = $04
66         RIGHT   = $08
67         FIRE    = $10
68 .endenum
69
70 ;----------------------------------------------------------------------------
71 ; Global variables. The bounding box values are sorted so that they can be
72 ; written with the least effort in the SETBOX and GETBOX routines, so don't
73 ; reorder them.
74
75 .bss
76
77 Vars:
78 YPos:           .res    2               ; Current mouse position, Y
79 XPos:           .res    2               ; Current mouse position, X
80 XMin:           .res    2               ; X1 value of bounding box
81 YMin:           .res    2               ; Y1 value of bounding box
82 XMax:           .res    2               ; X2 value of bounding box
83 YMax:           .res    2               ; Y2 value of bounding box
84 Buttons:        .res    1               ; Button mask
85
86 ; Temporary value used in the int handler
87
88 Temp:           .res    1
89
90 ; Default values for above variables
91
92 .rodata
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). The routine MUST return carry set if the interrupt has been
300 ; 'handled' - which means that the interrupt source is gone. Otherwise it
301 ; MUST return carry clear.
302 ;
303
304 IRQ:    lda     #$7F
305         sta     CIA1_PRA
306         lda     CIA1_PRB                ; Read joystick #0
307         and     #$1F
308         eor     #$1F                    ; Make all bits active high
309         sta     Temp
310
311 ; Check for a pressed button and place the result into Buttons
312
313         ldx     #$00                    ; Assume no button pressed
314         and     #JOY::FIRE              ; Check fire button
315         beq     @L0                     ; Jump if not pressed
316         ldx     #MOUSE_BTN_LEFT         ; Left (only) button is pressed
317 @L0:    stx     Buttons
318
319 ; Check left/right
320
321         lda     Temp                    ; Read joystick #0
322         and     #(JOY::LEFT | JOY::RIGHT)
323         beq     @SkipX                  ;
324
325 ; We will cheat here and rely on the fact that either the left, OR the right
326 ; bit can be active
327
328         and     #JOY::RIGHT             ; Check RIGHT bit
329         bne     @Right
330         lda     #$FF
331         tax
332         bne     @AddX                   ; Branch always
333 @Right: lda     #$01
334         ldx     #$00
335
336 ; Calculate the new X coordinate (--> a/y)
337
338 @AddX:  add     XPos
339         tay                             ; Remember low byte
340         txa
341         adc     XPos+1
342         tax
343
344 ; Limit the X coordinate to the bounding box
345
346         cpy     XMin
347         sbc     XMin+1
348         bpl     @L1
349         ldy     XMin
350         ldx     XMin+1
351         jmp     @L2
352 @L1:    txa
353
354         cpy     XMax
355         sbc     XMax+1
356         bmi     @L2
357         ldy     XMax
358         ldx     XMax+1
359 @L2:    sty     XPos
360         stx     XPos+1
361
362 ; Move the mouse pointer to the new X pos
363
364         tya
365         jsr     CMOVEX
366
367 ; Calculate the Y movement vector
368
369 @SkipX: lda     Temp                    ; Read joystick #0
370         and     #(JOY::UP | JOY::DOWN)  ; Check up/down
371         beq     @SkipY                  ;
372
373 ; We will cheat here and rely on the fact that either the up, OR the down
374 ; bit can be active
375
376         lsr     a                       ; Check UP bit
377         bcc     @Down
378         lda     #$FF
379         tax
380         bne     @AddY
381 @Down:  lda     #$01
382         ldx     #$00
383
384 ; Calculate the new Y coordinate (--> a/y)
385
386 @AddY:  add     YPos
387         tay                             ; Remember low byte
388         txa
389         adc     YPos+1
390         tax
391
392 ; Limit the Y coordinate to the bounding box
393
394         cpy     YMin
395         sbc     YMin+1
396         bpl     @L3
397         ldy     YMin
398         ldx     YMin+1
399         jmp     @L4
400 @L3:    txa
401
402         cpy     YMax
403         sbc     YMax+1
404         bmi     @L4
405         ldy     YMax
406         ldx     YMax+1
407 @L4:    sty     YPos
408         stx     YPos+1
409
410 ; Move the mouse pointer to the new X pos
411
412         tya
413         jsr     CMOVEY
414
415 ; Done
416
417 @SkipY: clc                             ; Interrupt not "handled"
418         rts
419