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