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