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