]> git.sur5r.net Git - cc65/blob - libsrc/c64/mouse.s
First few nes files by groepaz
[cc65] / libsrc / c64 / mouse.s
1 ;
2 ; Ullrich von Bassewitz, 24.04.1999
3 ;
4 ; Routines for the 1351 proportional mouse. Parts of the code are from
5 ; the Commodore 1351 mouse users guide.
6 ;
7
8         .export         _mouse_init, _mouse_done
9         .export         _mouse_hide, _mouse_show
10         .export         _mouse_box, _mouse_info
11         .export         _mouse_move, _mouse_pos
12         .export         _mouse_buttons, _mouse_info
13
14         .import         popax, addysp1
15         .importzp       ptr1, sp
16
17         .include        "c64.inc"
18
19         .macpack        generic
20
21
22 .code
23
24 ; --------------------------------------------------------------------------
25 ;
26 ; Constants
27 ;
28
29 SPRITE_HEIGHT   = 21
30 SPRITE_WIDTH    = 24
31 SCREEN_HEIGHT   = 200
32 SCREEN_WIDTH    = 320
33 XCORR           = SPRITE_WIDTH
34
35 ; --------------------------------------------------------------------------
36 ;
37 ; unsigned char __fastcall__ mouse_init (unsigned char type);
38 ;
39
40 _mouse_init:
41         lda     OldIRQ+1                ; Already initialized?
42         bne     AlreadyInitialized      ; Jump if yes
43
44 ; Initialize variables
45
46         ldx     #0
47         lda     #XCORR
48         sta     XPos
49         stx     XPos+1
50         stx     YPos
51         stx     YPos+1
52         stx     OldPotX
53         stx     OldPotY
54         stx     XMin
55         stx     XMin+1                  ; XMin = 0
56         lda     #50                     ; ## FIXME: This is the PAL value
57         sta     YCorr
58         sta     YPos
59         stx     YPos+1
60         sec
61         sbc     #SPRITE_HEIGHT          ; Sprite height in pixels
62         sta     YMin
63         stx     YMin+1                  ; YMin = 29
64         lda     #SCREEN_HEIGHT          ; Vertical screen res
65         add     YCorr                   ; Add correction factor
66         sta     YMax
67         stx     YMax+1
68         inx                             ; X = 1
69         stx     Invisible               ; Mouse *not* visible
70         lda     #<(SCREEN_WIDTH + SPRITE_WIDTH)
71         sta     XMax
72         stx     XMax+1                  ; XMax = 320 + sprite width
73
74 ; Remember the old IRQ vector
75
76         lda     IRQVec
77         sta     OldIRQ
78         lda     IRQVec+1
79         sta     OldIRQ+1
80
81 ; Set our own IRQ vector.
82
83         ldx     #<MouseIRQ
84         ldy     #>MouseIRQ
85         jsr     SetIRQ                  ; Set our IRQ vector, disable sprite 0
86         lda     #1                      ; Mouse successfully initialized
87         rts
88
89 AlreadyInitialized:
90         lda     #0                      ; Error
91         rts
92
93 ; --------------------------------------------------------------------------
94 ;
95 ; void mouse_done (void);
96 ;
97
98 _mouse_done:
99         ldx     OldIRQ
100         ldy     OldIRQ+1                ; Initialized?
101         beq     Done                    ; Jump if no
102         lda     #0
103         sta     OldIRQ+1                ; Reset the initialized flag
104 SetIRQ: sei                             ; Disable interrupts
105         stx     IRQVec                  ; Set the new/old vector
106         sty     IRQVec+1
107         lda     VIC_SPR_ENA             ; Get sprite enable register
108         and     #$FE                    ; Disable sprite #0
109         sta     VIC_SPR_ENA             ; Write back
110         cli                             ; Enable interrupts
111 Done:   rts
112
113
114 ; --------------------------------------------------------------------------
115 ;
116 ; void mouse_hide (void);
117 ;
118
119 _mouse_hide:
120         lda     Invisible               ; Get the flag
121         bne     @L1                     ; Jump if already invisible
122
123         lda     #$FE                    ; Clear bit for sprite #0
124         sei                             ; Disable interrupts
125         and     VIC_SPR_ENA
126         sta     VIC_SPR_ENA             ; Disable sprite
127         cli                             ; Enable interrupts
128
129 @L1:    inc     Invisible               ; Set the flag to invisible
130         rts
131
132 ; --------------------------------------------------------------------------
133 ;
134 ; void mouse_show (void);
135 ;
136
137 _mouse_show:
138         lda     Invisible               ; Mouse invisible?
139         beq     @L1                     ; Jump if no
140         dec     Invisible               ; Set the flag
141         bne     @L1                     ; Jump if still invisible
142
143         sei                             ; Disable interrupts
144         jsr     MoveSprite1             ; Move the sprite to it's position
145         lda     VIC_SPR_ENA             ; Get sprite enable register
146         ora     #$01                    ; Enable sprite #0
147         sta     VIC_SPR_ENA             ; Write back
148         cli                             ; Enable interrupts
149
150 @L1:    rts
151
152 ; --------------------------------------------------------------------------
153 ;
154 ; void __fastcall__ mouse_box (int minx, int miny, int maxx, int maxy);
155 ;
156
157 _mouse_box:
158         ldy     #0                      ; Stack offset
159
160         add     YCorr                   ; Adjust the Y value
161         bcc     @L1
162         inx
163         clc
164 @L1:    sei                             ; Disable interrupts
165
166         sta     YMax
167         stx     YMax+1                  ; maxy
168
169         lda     (sp),y
170         adc     #XCORR
171         sta     XMax
172         iny
173         lda     (sp),y
174         adc     #$00
175         sta     XMax+1                  ; maxx
176
177         iny
178         lda     (sp),y
179         add     YCorr
180         sta     YMin
181         iny
182         lda     (sp),y
183         adc     #$00
184         sta     YMin+1                  ; miny
185
186         iny
187         lda     (sp),y
188         add     #XCORR
189         sta     XMin
190         iny
191         lda     (sp),y
192         adc     #$00
193         sta     XMin+1                  ; minx
194
195         cli                             ; Enable interrupts
196
197         jmp     addysp1                 ; Drop params, return
198
199 ; --------------------------------------------------------------------------
200 ;
201 ; void __fastcall__ mouse_pos (struct mouse_pos* pos);
202 ; /* Return the current mouse position */
203 ;
204
205 _mouse_pos:
206         sta     ptr1
207         stx     ptr1+1                  ; Remember the argument pointer
208
209         ldy     #0                      ; Structure offset
210         sec                             ; Needed for the SBC later
211
212         sei                             ; Disable interrupts
213         lda     XPos                    ; Transfer the position
214         sbc     #XCORR
215         sta     (ptr1),y
216         lda     XPos+1
217         sbc     #$00
218         iny
219         sta     (ptr1),y
220         lda     YPos
221         ldx     YPos+1
222         cli                             ; Restore initial interrupt state
223
224         sub     YCorr                   ; Apply the Y correction value
225         bcs     @L1
226         dex
227 @L1:    iny
228         sta     (ptr1),y                ; Store YPos
229         txa
230         iny
231         sta     (ptr1),y
232
233         rts                             ; Done
234
235 ; --------------------------------------------------------------------------
236 ;
237 ; void __fastcall__ mouse_info (struct mouse_info* info);
238 ; /* Return the state of the mouse buttons and the position of the mouse */
239 ;
240
241 _mouse_info:
242
243 ; We're cheating here to keep the code smaller: The first fields of the
244 ; mouse_info struct are identical to the mouse_pos struct, so we will just
245 ; call _mouse_pos to initialize the struct pointer and fill the position
246 ; fields.
247
248         jsr     _mouse_pos
249
250 ; Fill in the button state
251
252         jsr     _mouse_buttons          ; Will not touch ptr1
253         ldy     #4
254         sta     (ptr1),y
255
256         rts
257
258 ; --------------------------------------------------------------------------
259 ;
260 ; void __fastcall__ mouse_move (int x, int y);
261 ;
262
263 _mouse_move:
264         add     YCorr                   ; Add Y coordinate correction
265         bcc     @L1
266         inx
267         clc
268 @L1:    sei
269         sta     YPos
270         stx     YPos+1
271         cli
272
273         jsr     popax                   ; Get X
274         adc     #XCORR                  ; Adjust X coordinate
275         bcc     @L2
276         inx
277 @L2:    sei
278         sta     XPos
279         stx     XPos+1                  ; Set new position
280         jsr     MoveSprite              ; Move the sprite to the mouse pos
281         cli                             ; Enable interrupts
282
283         rts
284
285 ; --------------------------------------------------------------------------
286 ;
287 ; unsigned char mouse_buttons (void);
288 ;
289
290 .proc   _mouse_buttons
291
292         lda     #$7F
293         sei
294         sta     CIA1_PRA
295         lda     CIA1_PRB                ; Read joystick #0
296         cli
297         ldx     #0
298         and     #$1F
299         eor     #$1F
300         rts
301
302 .endproc
303
304 ; --------------------------------------------------------------------------
305 ;
306 ; Mouse interrupt handler
307 ;
308
309 MouseIRQ:
310         cld
311         lda     SID_ADConv1             ; Get mouse X movement
312         ldy     OldPotX
313         jsr     MoveCheck               ; Calculate movement vector
314         sty     OldPotX
315
316 ; Calculate the new X coordinate (--> a/y)
317
318         add     XPos
319         tay                             ; Remember low byte
320         txa
321         adc     XPos+1
322         tax
323
324 ; Limit the X coordinate to the bounding box
325
326         cpy     XMin
327         sbc     XMin+1
328         bpl     @L1
329         ldy     XMin
330         ldx     XMin+1
331         jmp     @L2
332 @L1:    txa
333
334         cpy     XMax
335         sbc     XMax+1
336         bmi     @L2
337         ldy     XMax
338         ldx     XMax+1
339 @L2:    sty     XPos
340         stx     XPos+1
341
342 ; Calculate the Y movement vector
343
344         lda     SID_ADConv2             ; Get mouse Y movement
345         ldy     OldPotY
346         jsr     MoveCheck               ; Calculate movement
347         sty     OldPotY
348
349 ; Calculate the new Y coordinate (--> a/y)
350
351         sta     OldValue
352         lda     YPos
353         sub     OldValue
354         tay
355         stx     OldValue
356         lda     YPos+1
357         sbc     OldValue
358         tax
359
360         cpy     YMin
361         sbc     YMin+1
362         bpl     @L3
363         ldy     YMin
364         ldx     YMin+1
365         jmp     @L4
366 @L3:    txa
367
368         cpy     YMax
369         sbc     YMax+1
370         bmi     @L4
371         ldy     YMax
372         ldx     YMax+1
373 @L4:    sty     YPos
374         stx     YPos+1
375
376 ; Move the mouse sprite if it is enabled
377
378         jsr     MoveSprite              ; Move the sprite
379
380 ; Jump to the next IRQ handler
381
382         jmp     (OldIRQ)
383
384
385 ; --------------------------------------------------------------------------
386 ;
387 ; Move check routine, called for both coordinates.
388 ;
389 ; Entry:        y = old value of pot register
390 ;               a = current value of pot register
391 ; Exit:         y = value to use for old value
392 ;               x/a = delta value for position
393 ;
394
395 MoveCheck:
396         sty     OldValue
397         sta     NewValue
398         ldx     #$00
399
400         sub     OldValue                ; a = mod64 (new - old)
401         and     #%01111111
402         cmp     #%01000000              ; if (a > 0)
403         bcs     @L1                     ;
404         lsr     a                       ;   a /= 2;
405         beq     @L2                     ;   if (a != 0)
406         ldy     NewValue                ;     y = NewValue
407         rts                             ;   return
408
409 @L1:    ora     #%11000000              ; else or in high order bits
410         cmp     #$FF                    ; if (a != -1)
411         beq     @L2
412         sec
413         ror     a                       ;   a /= 2
414         dex                             ;   high byte = -1 (X = $FF)
415         ldy     NewValue
416         rts
417
418 @L2:    txa                             ; A = $00
419         rts
420
421 ; --------------------------------------------------------------------------
422 ;
423 ; Move the mouse sprite to the current mouse position. Must be called
424 ; with interrupts off. MoveSprite1 is an entry without checking.
425 ;
426
427 MoveSprite:
428
429         lda     Invisible               ; Mouse visible?
430         bne     MoveSpriteDone          ; Jump if no
431
432 ; Set the high X bit
433
434 MoveSprite1:
435         lda     VIC_SPR_HI_X            ; Get high X bits of all sprites
436         and     #$FE                    ; Clear bit for sprite #0
437         ldy     XPos+1                  ; Test Y position
438         beq     @L1
439         ora     #$01                    ; Set high X bit
440 @L1:    sta     VIC_SPR_HI_X            ; Set hi X sprite values
441
442 ; Set the low X byte
443
444         lda     XPos
445         sta     VIC_SPR0_X              ; Set low byte
446
447 ; Set the Y position
448
449         ldy     YPos+1                  ; Negative or too large?
450         bne     MoveSpriteDone          ; Jump if yes
451         lda     YPos
452         sta     VIC_SPR0_Y              ; Set Y position
453
454 ; Done
455
456 MoveSpriteDone:
457         rts
458
459 ; --------------------------------------------------------------------------
460 ; Data
461
462 .bss
463
464 OldIRQ:         .res    2               ; Old IRQ vector
465 OldValue:       .res    1               ; Temp for MoveCheck routine
466 NewValue:       .res    1               ; Temp for MoveCheck routine
467 YCorr:          .res    1               ; Correction for Y coordinate
468
469 Invisible:      .res    1               ; Is the mouse invisible?
470 OldPotX:        .res    1               ; Old hw counter values
471 OldPotY:        .res    1
472
473 XPos:           .res    2               ; Current mouse position, X
474 YPos:           .res    2               ; Current mouse position, Y
475
476 XMin:           .res    2               ; X1 value of bounding box
477 YMin:           .res    2               ; Y1 value of bounding box
478 XMax:           .res    2               ; X2 value of bounding box
479 YMax:           .res    2               ; Y2 value of bounding box
480
481