Home » Archimedes archive » Archimedes World » AW-1996-12.adf » !AcornAns_AcornAns » November/!Balls/Balls

November/!Balls/Balls

This website contains an archive of files for the Acorn Electron, BBC Micro, Acorn Archimedes, Commodore 16 and Commodore 64 computers, which Dominic Ford has rescued from his private collection of floppy disks and cassettes.

Some of these files were originally commercial releases in the 1980s and 1990s, but they are now widely available online. I assume that copyright over them is no longer being asserted. If you own the copyright and would like files to be removed, please contact me.

Tape/disk: Home » Archimedes archive » Archimedes World » AW-1996-12.adf » !AcornAns_AcornAns
Filename: November/!Balls/Balls
Read OK:
File size: 4154 bytes
Load address: 0000
Exec address: 0000
File contents
   10REM >Balls
   20REM
   30:
   40REM NB program will produce a beep if animation speed falls
   50REM below the target fps rate.
   60targetfps% = 50
   70IF 100MODtargetfps%<>0 ERROR 1, "Require targetfps divides into 100"
   80:
   90SYS &20280, 0, -1 TO ;flags%
  100IF flags% AND 1 THEN arm3%=FALSE ELSE arm3%=TRUE
  110:
  120ON ERROR SYS 6,112,1:SYS 6,113,1:PRINT REPORT$;" at line ";ERL:END
  130D% = RND(-TIME)
  140:
  150CLS
  160PRINT "                    B A L L S   D E M O"'
  170PRINT "� Program will beep if animation speed falls below the target of ";targetfps%;" fps."
  180PRINT "� Pressing any key during demo will add one more ball."
  190PRINT "� Press Escape to end program."'
  200INPUT "Please input Standard (0) or VGA (1) display";VGA%
  210IF VGA%<>1 VGA%=0
  220:
  230hpix%=288
  240vpix%=200
  250IF VGA% THEN
  260 mode%=99
  270 avpix%=400
  280 hadd%=hpix%*2
  290 lhadd%=6
  300ELSE
  310 mode%=98
  320 avpix%=200
  330 hadd%=hpix%
  340 lhadd%=5
  350ENDIF
  360:
  370DIM balldata% 2560
  380SYS "OS_File", 255, "<Balls$Dir>.Resources.BallData", balldata%, 0
  390DIM backdata% 57656
  400SYS "OS_File", 255, "<Balls$Dir>.Resources.BackSpr", backdata%, 0
  410:
  420DIM vblin% 8, vblout% 8
  430!vblin%=148:vblin%!4=-1
  440MODE mode%+128
  450SYS "OS_ReadVduVariables", vblin%, vblout%
  460scrst2%=!vblout%
  470MODE mode%
  480SYS "OS_ReadVduVariables", vblin%, vblout%
  490scrst1%=!vblout%
  500OFF
  510:
  520maxn%=200
  530DIM b% maxn%*20
  540REM NB b% stores array (of size n%) of structure:
  550REM {x coord, y coord, x increment, y increment, sticking count}
  560:
  570PROCass
  580:
  590SYS 6,112,1:SYS 6,113,1
  600n%=1
  610!an%=n%
  620:
  630REM initialise ball locations & velocities
  640FOR i% = 0 TO n%*20-1 STEP 20
  650  b%!(i%+0)  = 259*256
  660  b%!(i%+4)  = 174*256
  670  b%!(i%+8)  = RND(64)-32
  680  b%!(i%+12) = -4*256+RND(128)-64
  690  b%!(i%+16) = 0
  700NEXT
  710:
  720REPEAT
  730 CALL anim%
  740 IF n%<maxn% THEN
  750  i%=20*n%
  760  b%!(i%+0)  = 259*256
  770  b%!(i%+4)  = 174*256
  780  b%!(i%+8)  = RND(64)-32
  790  b%!(i%+12) = -4*256+RND(128)-64
  800  b%!(i%+16) = 0
  810  n%+=1
  820  !an%=n%
  830 ENDIF
  840UNTIL FALSE
  850:
  860END
  870:
  880DEF PROCass
  890DIM code% 10240, sqrt% 257*4, sincos% 256*8
  900FOR i%=0 TO 256
  910 sqrt%!(4*i%) = 0.5+SQR(256*i%)
  920NEXT
  930FOR i%=0 TO 255
  940 sincos%!(8*i%  ) = 0.5+256*SIN(2*PI*i%/256)
  950 sincos%!(8*i%+4) = 0.5+256*COS(2*PI*i%/256)
  960NEXT
  970scrst%=scrst1%
  980FOR pass% = 0 TO 2 STEP 2
  990 P%=code%
 1000 [OPT pass%
 1010 .aspframe%         EQUD 0
 1020 .ascrstsum%        EQUD scrst1%+scrst2%
 1030 .an%     EQUD 0
 1040 .ab%     EQUD b%
 1050 .atime%  EQUD 0              ;time storage for frame speed calc
 1060 .afc%    EQUD 0              ;frame counter
 1070 .anim%
 1080 STMFD    13!, {14}
 1090 STR      13, aspframe%       ;store sp to free up r13
 1100 .nextframe%
 1110 :
 1120 SWI      "OS_ReadMonotonicTime"        ;track frame speed
 1130 STR      0, atime%
 1140 :
 1150 MOV      0, #19
 1160 SWI      "OS_Byte"                     ;wait for vsync
 1170 MOV      0, #113
 1180 LDR      1, abank%
 1190 RSB      3, 1, #3
 1200 STR      3, abank%
 1210 SWI      "OS_Byte"           ;swap displayed screen bank
 1220 LDR      0, ascrstsum%
 1230 LDR      1, ascrst%
 1240 SUB      1, 0, 1
 1250 STR      1, ascrst%          ;swap ptr to other bank
 1260 BL       copyback%           ;cls that bank to background
 1270 :
 1280 LDR      12, ab%
 1290 LDR      13, an%
 1300 .framemoveloop%              ;then move each ball
 1310 LDMIA    12, {0,1,2,3,4}     ; read x,y,xi,yi,sc
 1320 BL       movencheck%
 1330 STMIA    12!, {0,1,2,3,4}    ; restore x,y,xi,yi,sc
 1340 SUBS     13, 13, #1
 1350 BNE      framemoveloop%      ;then do next ball
 1360 :
 1370 LDR      12, ab%
 1380 LDR      13, an%
 1390 .frameplotloop%              ;now plot each ball:
 1400 LDMIA    12, {0,1}           ; read x,y coords from data
 1410 MOV      0, 0, ASR #8
 1420 MOV      1, 1, ASR #8
 1430 BL       plot%               ; plot ball at x,y
 1440 ADD      12, 12, #20
 1450 SUBS     13, 13, #1
 1460 BNE      frameplotloop%      ;then do next ball
 1470 LDR      11, afc%
 1480 ADD      11, 11, #1
 1490 STR      11, afc%            ;update frame count
 1500 :
 1510 ]
 1520 IF VGA% THEN
 1530 [OPT pass%
 1540 LDR      14, ascrst%         ;if in VGA mode, fill in the extra
 1550 ADD      13, 14, #hadd%-hpix%;blank lines by copying the line
 1560 MOV      12, #vpix%          ;above
 1570 .interlacel1%
 1580 LDMIA    14!, {0-11}
 1590 STMIA    13!, {0-11}
 1600 LDMIA    14!, {0-11}
 1610 STMIA    13!, {0-11}
 1620 LDMIA    14!, {0-11}
 1630 STMIA    13!, {0-11}
 1640 LDMIA    14!, {0-11}
 1650 STMIA    13!, {0-11}
 1660 LDMIA    14!, {0-11}
 1670 STMIA    13!, {0-11}
 1680 LDMIA    14!, {0-11}
 1690 STMIA    13!, {0-11}
 1700 ADD      13, 13, #hadd%-hpix%
 1710 ADD      14, 14, #hadd%-hpix%
 1720 SUBS     12, 12, #1
 1730 BNE      interlacel1%
 1740 ]
 1750 ENDIF
 1760 [OPT pass%
 1770 :
 1780 SWI      "OS_ReadMonotonicTime"        ;calculate frame speed
 1790 LDR      1, atime%
 1800 SUB      0, 0, 1
 1810 CMP      0, #100/targetfps%
 1820 SWIGT    256+7               ;beep if it falls below target fps
 1830 :
 1840 MOV      0, #129
 1850 MOV      1, #0
 1860 MOV      2, #0
 1870 SWI      "OS_Byte"
 1880 CMP      2, #&FF
 1890 BEQ      nextframe%          ;if no key pressed, do next frame
 1900 LDR      13, aspframe%       ;restore sp
 1910 LDMFD    13!, {PC}           ;return to BASIC
 1920 :
 1930 .ascrst% EQUD scrst%
 1940 .adata%  EQUD balldata%
 1950 .abackdata%        EQUD backdata%
 1960 .abank%  EQUD 1
 1970 .aplotregs%        EQUD 0:EQUD 0:EQUD 0
 1980 .plot%   ;plot our ball sprite at coords r0,r1
 1990          ;where 0,0 is top left & 287,199 is bottom right
 2000          ;NB sprite MUST lie entirely within screen
 2010 ADR      11, aplotregs%
 2020 STMIA    11, {12,13,14}
 2030 AND      2, 0, #3            ;calc which of 4 sprite alignments
 2040 ADD      3, 2, 2, ASL #2     ;we need via (xAND3)*20*2*16 + data%
 2050 BIC      0, 0, #3            ;round x down to mult of 3
 2060 ADD      1, 1, 1, ASL #3
 2070 LDR      2, ascrst%
 2080 ADD      2, 2, 1, ASL #lhadd%
 2090 ADD      0, 2, 0             ;calc (screen ptr + hadd%*y + x)
 2100 LDR      1, adata%
 2110 ADD      1, 1, 3, ASL #7     ;finally calc (xAND3)*20*2*16+data%
 2120 MOV      2, #4
 2130 ADD      3, 1, #20*16
 2140 .loop1%                      ;now plot sprite
 2150 FNplotfrag(pass%)            ;plot 1st row
 2160 ADD      0, 0, #hadd%-20     ;move screen ptr to start next row
 2170 FNplotfrag(pass%)
 2180 ADD      0, 0, #hadd%-20
 2190 FNplotfrag(pass%)
 2200 ADD      0, 0, #hadd%-20
 2210 FNplotfrag(pass%)            ;plot 4th row
 2220 ADD      0, 0, #hadd%-20
 2230 SUBS     2, 2, #1
 2240 BNE      loop1%          ;repeat above 4 times to do all 16 rows
 2250 ADR      11, aplotregs%      ;plot completed - return to caller
 2260 LDMIA    11, {12,13,PC}      ;preserving r12 & r13.
 2270 :
 2280 .acollregs%    EQUD 0:EQUD 0:EQUD 0:EQUD 0
 2290                EQUD 0:EQUD 0:EQUD 0:EQUD 0
 2300 .movencheck%     ;move then collision check our
 2310                  ;ball sprite at coords r0,r1
 2320                  ;where 0,0 is top left & 287,199 is bottom right
 2330                  ;NB sprite MUST lie entirely within screen
 2340 ADR      11, acollregs%
 2350 ADD      0, 0, 2
 2360 ADD      1, 1, 3
 2370 STMIA    11, {0-4,12,13,14}
 2380 MOV      0, 0, ASR #8
 2390 MOV      1, 1, ASR #8
 2400 AND      2, 0, #3            ;calc which of 4 sprite alignments
 2410 ADD      3, 2, 2, ASL #2     ;we need via (xAND3)*20*2*16 + data%
 2420 BIC      0, 0, #3            ;round x down to mult of 3
 2430 ADD      1, 1, 1, ASL #3
 2440 LDR      2, ascrst%
 2450 ADD      2, 2, 1, ASL #lhadd%
 2460 ADD      0, 2, 0             ;calc (screen ptr + hadd%*y + x)
 2470 LDR      1, adata%
 2480 ADD      1, 1, 3, ASL #7     ;finally calc (xAND3)*20*2*16+data%
 2490 ADD      1, 1, #20*16
 2500 ADR      2, colladdrbuf%     ;store screen and sprite data addrs
 2510 STMIA    2, {0,1}            ;corresponding to top left of ball
 2520 MOV      2, #4
 2530 .collloop1%                  ;now check sprite
 2540 FNcollfrag(pass%)            ;check 1st row (if coll B gotcoll%)
 2550 ADD      0, 0, #hadd%-20     ;move screen ptr to start next row
 2560 FNcollfrag(pass%)
 2570 ADD      0, 0, #hadd%-20
 2580 FNcollfrag(pass%)
 2590 ADD      0, 0, #hadd%-20
 2600 FNcollfrag(pass%)            ;check 4th row
 2610 ADD      0, 0, #hadd%-20
 2620 SUBS     2, 2, #1
 2630 BNE      collloop1%      ;repeat above 4 times to do all 16 rows
 2640 ADR      11, acollregs%
 2650 LDMIA    11, {0-4,12,13,14}
 2660 ADD      3, 3, #8            ; accelerate ball downwards
 2670 MOV      4, #0
 2680 MOV      PC, 14
 2690 .colladdrbuf%      EQUD 0:EQUD 0
 2700 .gotcoll%
 2710 ADR      11, acollregs%
 2720 LDMIA    11, {0-3}
 2730 SUB      0, 0, 2             ;reset position, moving it out of
 2740 SUB      1, 1, 3             ;collision
 2750 STMIA    11, {0,1}
 2760 MOV      6, #0               ;in my lin reg notes, n
 2770 MOV      7, #0                                   ; u
 2780 MOV      8, #0                                   ; v
 2790 MOV      9, #0                                   ; p
 2800 MOV      10, #0                                  ; q
 2810 ADR      2, colladdrbuf%
 2820 LDMIA    2, {0,1}            ;recall screen/data addrs for top
 2830 MOV      3, #0     ;row 0    ;left of sprite
 2840 .statloop1%
 2850 MOV      2, #0     ;col 0
 2860 .statloop2%
 2870 LDR      4, [0], #4          ;rescan each pixel in collision area
 2880 LDR      5, [1], #4          ;and for each collided pixel add its
 2890 AND      4, 4, 5             ;coords (relative to topleft sprite)
 2900 FNstatfrag(pass%, 255)       ;onto the regression statistics
 2910 ADD      2, 2, #1
 2920 FNstatfrag(pass%, 255<<8)
 2930 ADD      2, 2, #1
 2940 FNstatfrag(pass%, 255<<16)
 2950 ADD      2, 2, #1
 2960 FNstatfrag(pass%, 255<<24)
 2970 ADD      2, 2, #1
 2980 CMP      2, #20
 2990 BLT      statloop2%
 3000 ADD      0, 0, #hadd%-20
 3010 ADD      3, 3, #1
 3020 CMP      3, #16
 3030 BLT      statloop1%          ;when done, n, u & v computed
 3040 MUL      9, 6, 9
 3050 ADD      5, 7, 8
 3060 SUB      14, 7, 8
 3070 MLA      9, 5, 14, 9         ;p computed
 3080 MUL      10, 6, 10
 3090 MUL      14, 7, 8
 3100 SUB      10, 10, 14
 3110 ADD      10, 10, 10          ;q computed
 3120 MOVS     6, 9
 3130 RSBMI    6, 6, #0            ;ap = abs p
 3140 MOVS     7, 10
 3150 RSBMI    7, 7, #0            ;aq = abs q
 3160 CMP      6, 7
 3170 MOV      8, 6
 3180 MOVLT    8, 7                ; m = max {ap,aq}
 3190 CMP      8, #0               ;if have degenerate collision
 3200 BEQ      patch1%             ;(eg with single pixel), can't calc
 3210 .statloop3%                  ;a linear regression, so go patch1%
 3220 CMP      8, #1<<12           ;which simply reverses velocities!
 3230 MOVGE    8, 8, ASR #1
 3240 MOVGE    6, 6, ASR #1        ;proportionately reduce ap and aq in
 3250 MOVGE    7, 7, ASR #1        ;magnitude, until in necessary range
 3260 BGE      statloop3%
 3270 MUL      11, 6, 6            ;ap^2 in low range
 3280 MUL      12, 7, 7            ;aq^2 in low range
 3290 ADD      13, 11, 12          ;divisor ap^2+aq^2
 3300 MOV      0, 11, ASL #8
 3310 FNdiv(pass%, 0, 13, 11, 1)   ;t  in r11 = 256ap^2/(ap^2+aq^2)
 3320 MOV      0, 12, ASL #8
 3330 FNdiv(pass%, 0, 13, 12, 1)   ;tb in r12 = 256aq^2/(ap^2+aq^2)
 3340 LDR      13, asqrt%
 3350 LDR      7, [13, 11, LSL #2] ;square root t
 3360 LDR      8, [13, 12, LSL #2] ;and tb, via look-up-table
 3370 CMP      9, #0
 3380 RSBLT    7, 7, #0            ;final t  in r7
 3390 CMP      10, #0
 3400 RSBPL    8, 8, #0            ;final tb in r8
 3410 ADR      11, acollregs%
 3420 LDMIA    11, {0-4,12,13,14}
 3430 MUL      5, 7, 2             ;now modify velocity by
 3440 MLA      5, 8, 3, 5          ;reflecting it in the
 3450 RSB      5, 5, #0            ;line generated by the linear
 3460 MUL      6, 7, 3             ;regression calculation
 3470 MUL      9, 8, 2             ;(which we use to approximate the
 3480 SUB      6, 6, 9             ; tangent at the collision surface)
 3490 RSB      5, 5, 5, ASL #8
 3500 RSB      6, 6, 6, ASL #8     ;& then attenuate by factor 255/256
 3510 MOV      2, 5, ASR #16       ;(simulate energy loss on coll)
 3520 MOV      3, 6, ASR #16
 3530 ADD      4, 4, #1            ;track how many consecutive frames
 3540 :                            ;this ball has been stuck in a
 3550 CMP      4,#2                ;collision and if 2 or more, try to
 3560 BLT      movencheck%         ;escape it via a bodge:
 3570 .bodge1%                     ;bodge begin ...
 3580 ADR      7, seed%
 3590 LDMIA    7, {5, 6}
 3600 MOVS     6, 6, LSR #1        ;generate random 32-bit number
 3610 MOVS     8, 5, RRX
 3620 ADC      6, 6, 6
 3630 EOR      8, 8, 5, LSL #12
 3640 EOR      5, 8, 8, LSR #20
 3650 STMIA    7, {5, 6}
 3660 LDR      7, asincos%         ;when balls get stuck
 3670 AND      5, 5, #255          ;due to conflict between correct
 3680 ADD      7, 7, 5, ASL #3     ;reflection & small velocity or
 3690 LDMIA    7, {5, 6}           ;jagged overlap problems ...
 3700 MUL      7, 2, 5
 3710 MLA      7, 3, 6, 7          ;try a 'fix' - rotate velocity by
 3720 MUL      8, 2, 6             ;a random angle, so eventually
 3730 MUL      9, 3, 5             ;should pick some velocity that
 3740 SUB      8, 8, 9             ;extricates ball from stuck position
 3750 MOV      2, 7, ASR #8
 3760 MOV      3, 8, ASR #8        ;... bodge end
 3770 CMP      4, #16
 3780 BLT      movencheck%
 3790 MOV      PC, 14
 3800 :
 3810 .asincos%          EQUD sincos%
 3820 .seed%   EQUD -1:EQUD -1
 3830 .patch1%                     ;a patch to deal with collision case
 3840 ADR      11, acollregs%      ;where no linear regression exists
 3850 LDMIA    11, {0-4,12,13,14}  ;(eg where collision involves only
 3860 SUB      2, 2, 2, ASL #8     ; one pixel)
 3870 SUB      3, 3, 3, ASL #8     ;- simply reverse velocity!
 3880 MOV      2, 2, ASR #8
 3890 MOV      3, 3, ASR #8        ;nb also attenuate by factor 255/256
 3900 ADD      4, 4, #1            ;(simulate energy loss on coll)
 3910 CMP      4,#2
 3920 BLT      movencheck%
 3930 B        bodge1%             ;if been stuck in collision for >= 2
 3940 :                            ;frames go and apply bodged 'escape'
 3950 .asqrt%  EQUD sqrt%
 3960 .alrcls% EQUD 0
 3970 .aspcls% EQUD 0
 3980 .copyback%                   ;simple routine to clear screen to
 3990 STR      14, alrcls%         ;background as rapidly as possible -
 4000 STR      13, aspcls%         ;note the heavy use of LDM/STM.
 4010 LDR      0, ascrst%
 4020 LDR      1, abackdata%
 4030 ADD      1, 1, #56
 4040 MOV      2, #200
 4050 .clsloop%
 4060 LDMIA    1!, {3-14}
 4070 STMIA    0!, {3-14}
 4080 LDMIA    1!, {3-14}
 4090 STMIA    0!, {3-14}
 4100 LDMIA    1!, {3-14}
 4110 STMIA    0!, {3-14}
 4120 LDMIA    1!, {3-14}
 4130 STMIA    0!, {3-14}
 4140 LDMIA    1!, {3-14}
 4150 STMIA    0!, {3-14}
 4160 LDMIA    1!, {3-14}
 4170 STMIA    0!, {3-14}
 4180 ]
 4190 IF VGA% THEN
 4200 [OPT pass%
 4210 ADD      0, 0, #hadd%-hpix%
 4220 ]
 4230 ENDIF
 4240 [OPT pass%
 4250 SUBS     2, 2, #1
 4260 BNE      clsloop%
 4270 LDR      13, aspcls%
 4280 LDR      PC, alrcls%
 4290 ]
 4300NEXT
 4310ENDPROC
 4320:
 4330DEF FNplotfrag(pass%)    :REM macro to plot a row (20 pixels)
 4340[OPT pass%               :REM of our sprite
 4350LDMIA    0, {4-6}             ;read 3 words of screen (12 pixels)
 4360LDMIA    1!, {7-9}            ;read 12 sprite pixels
 4370LDMIA    3!, {10-12}          ;& 12 masks
 4380BIC      4, 4, 10             ;apply mask to screen, zeroing
 4390BIC      5, 5, 11             ; those bits where will write
 4400BIC      6, 6, 12             ; sprite image in a moment
 4410ORR      4, 4, 7              ;write in the sprite image
 4420ORR      5, 5, 8
 4430ORR      6, 6, 9
 4440STMIA    0!, {4-6}            ;restore the data back to screen
 4450LDMIA    0, {4-5}             ;read 2 words of screen (8 pixels)
 4460LDMIA    1!, {7-8}            ;read 8 sprite pixels
 4470LDMIA    3!, {10-11}          ;& 8 masks
 4480BIC      4, 4, 10
 4490BIC      5, 5, 11
 4500ORR      4, 4, 7
 4510ORR      5, 5, 8
 4520STMIA    0!, {4-5}            ;restore the data back to screen
 4530]
 4540=pass%
 4550:
 4560DEF FNcollfrag(pass%)    :REM macro to coll check a row
 4570[OPT pass%               :REM (20 pixels) of our sprite
 4580LDMIA    0!, {3-7}            ;read 5 words of screen (20 pixels)
 4590LDMIA    1!, {8-12}           ;read 20 sprite pixel masks
 4600TST      3, 8
 4610TSTEQ    4, 9
 4620TSTEQ    5, 10
 4630TSTEQ    6, 11
 4640TSTEQ    7, 12
 4650BNE      gotcoll%             ;branch to gotcoll% if any overlap
 4660]                        :REM  else continue with code after macro
 4670=pass%
 4680:
 4690DEF FNstatfrag(pass%, m%):REM macro to add in regression stats
 4700[OPT pass%               :REM for one pixel (coords u(i),v(i))
 4710TST       4, #m%
 4720BEQ       P%+8*4
 4730ADDNE     6, 6, #1            ; n = n + 1
 4740ADDNE     7, 7, 2             ; u = u + u(i)
 4750ADDNE     8, 8, 3             ; v = v + v(i)
 4760ADDNE     5, 2, 3
 4770SUBNE     14, 3, 2
 4780MLANE     9, 5, 14, 9         ; p = p + v(i)^2-u(i)^2
 4790MLANE     10, 2, 3, 10        ; q = q + u(i)*v(i)
 4800]
 4810=pass%
 4820:
 4830DEF FNdiv(pass%, ra, rb, rc, rd) :REM macro to set rc=raDIVrb
 4840[OPT pass%
 4850MOV       rd, rb
 4860CMP       rd, ra, LSR #1
 4870MOVLS     rd, rd, LSL #1
 4880CMP       rd, ra, LSR #1
 4890BLS       P%-2*4
 4900MOV       rc, #0
 4910CMP       ra, rd
 4920SUBCS     ra, ra, rd
 4930ADC       rc, rc, rc
 4940MOV       rd, rd, LSR #1
 4950CMP       rd, rb
 4960BHS       P%-5*4
 4970]
 4980=pass%

� >Balls
�
:
(=� NB program will produce a beep if animation speed falls
2 � below the target fps rate.
<targetfps% = 50
FA� 100�targetfps%<>0 � 1, "Require targetfps divides into 100"
P:
Zș &20280, 0, -1 � ;flags%
d$� flags% � 1 � arm3%=� � arm3%=�
n:
x2� � ș 6,112,1:ș 6,113,1:� �$;" at line ";�:�
�D% = �(-�)
�:
��
�0� "                    B A L L S   D E M O"'
�\� "� Program will beep if animation speed falls below the target of ";targetfps%;" fps."
�>� "� Pressing any key during demo will add one more ball."
�'� "� Press Escape to end program."'
�9� "Please input Standard (0) or VGA (1) display";VGA%
�� VGA%<>1 VGA%=0
�:
�
hpix%=288
�
vpix%=200
�� VGA% �

 mode%=99
 avpix%=400
 hadd%=hpix%*2
"
 lhadd%=6
,�
6
 mode%=98
@ avpix%=200
J hadd%=hpix%
T
 lhadd%=5
^�
h:
r� balldata% 2560
|Eș "OS_File", 255, "<Balls$Dir>.Resources.BallData", balldata%, 0
�� backdata% 57656
�Dș "OS_File", 255, "<Balls$Dir>.Resources.BackSpr", backdata%, 0
�:
�� vblin% 8, vblout% 8
�!vblin%=148:vblin%!4=-1
�� mode%+128
�-ș "OS_ReadVduVariables", vblin%, vblout%
�scrst2%=!vblout%
�� mode%
�-ș "OS_ReadVduVariables", vblin%, vblout%
�scrst1%=!vblout%
��
�:

maxn%=200
� b% maxn%*20
3� NB b% stores array (of size n%) of structure:
&B� {x coord, y coord, x increment, y increment, sticking count}
0:
:�ass
D:
Nș 6,112,1:ș 6,113,1
Xn%=1
b!an%=n%
l:
v,� initialise ball locations & velocities
�� i% = 0 � n%*20-1 � 20
�  b%!(i%+0)  = 259*256
�  b%!(i%+4)  = 174*256
�  b%!(i%+8)  = �(64)-32
�#  b%!(i%+12) = -4*256+�(128)-64
�  b%!(i%+16) = 0
��
�:
��
� � anim%
� � n%<maxn% �
�  i%=20*n%
�  b%!(i%+0)  = 259*256
  b%!(i%+4)  = 174*256
  b%!(i%+8)  = �(64)-32
#  b%!(i%+12) = -4*256+�(128)-64
   b%!(i%+16) = 0
*  n%+=1
4
  !an%=n%
> �
H� �
R:
\�
f:
p
� �ass
z-� code% 10240, sqrt% 257*4, sincos% 256*8
�� i%=0 � 256
�! sqrt%!(4*i%) = 0.5+�(256*i%)
��
�� i%=0 � 255
�- sincos%!(8*i%  ) = 0.5+256*�(2*�*i%/256)
�- sincos%!(8*i%+4) = 0.5+256*�(2*�*i%/256)
��
�scrst%=scrst1%
�� pass% = 0 � 2 � 2
�
 P%=code%
� [OPT pass%
� .aspframe%         EQUD 0
�, .ascrstsum%        EQUD scrst1%+scrst2%
 .an%     EQUD 0
 .ab%     EQUD b%
D .atime%  EQUD 0              ;time storage for frame speed calc
$0 .afc%    EQUD 0              ;frame counter
. .anim%
8 STMFD    13!, {14}
B: STR      13, aspframe%       ;store sp to free up r13
L .nextframe%
V :
`> SWI      "OS_ReadMonotonicTime"        ;track frame speed
j STR      0, atime%
t :
~ MOV      0, #19
�; SWI      "OS_Byte"                     ;wait for vsync
� MOV      0, #113
� LDR      1, abank%
� RSB      3, 1, #3
� STR      3, abank%
�= SWI      "OS_Byte"           ;swap displayed screen bank
� LDR      0, ascrstsum%
� LDR      1, ascrst%
� SUB      1, 0, 1
�9 STR      1, ascrst%          ;swap ptr to other bank
�> BL       copyback%           ;cls that bank to background
� :
 LDR      12, ab%

 LDR      13, an%
6 .framemoveloop%              ;then move each ball
5 LDMIA    12, {0,1,2,3,4}     ; read x,y,xi,yi,sc
( BL       movencheck%
28 STMIA    12!, {0,1,2,3,4}    ; restore x,y,xi,yi,sc
< SUBS     13, 13, #1
F4 BNE      framemoveloop%      ;then do next ball
P :
Z LDR      12, ab%
d LDR      13, an%
n6 .frameplotloop%              ;now plot each ball:
x= LDMIA    12, {0,1}           ; read x,y coords from data
� MOV      0, 0, ASR #8
� MOV      1, 1, ASR #8
�4 BL       plot%               ; plot ball at x,y
� ADD      12, 12, #20
� SUBS     13, 13, #1
�4 BNE      frameplotloop%      ;then do next ball
� LDR      11, afc%
� ADD      11, 11, #1
�5 STR      11, afc%            ;update frame count
� :
� ]
�
 � VGA% �
� [OPT pass%
D LDR      14, ascrst%         ;if in VGA mode, fill in the extra
B ADD      13, 14, #hadd%-hpix%;blank lines by copying the line
( MOV      12, #vpix%          ;above
" .interlacel1%
, LDMIA    14!, {0-11}
6 STMIA    13!, {0-11}
@ LDMIA    14!, {0-11}
J STMIA    13!, {0-11}
T LDMIA    14!, {0-11}
^ STMIA    13!, {0-11}
h LDMIA    14!, {0-11}
r STMIA    13!, {0-11}
| LDMIA    14!, {0-11}
� STMIA    13!, {0-11}
� LDMIA    14!, {0-11}
� STMIA    13!, {0-11}
�" ADD      13, 13, #hadd%-hpix%
�" ADD      14, 14, #hadd%-hpix%
� SUBS     12, 12, #1
� BNE      interlacel1%
� ]
� �
� [OPT pass%
� :
�B SWI      "OS_ReadMonotonicTime"        ;calculate frame speed
� LDR      1, atime%
 SUB      0, 0, 1
  CMP      0, #100/targetfps%
D SWIGT    256+7               ;beep if it falls below target fps
& :
0 MOV      0, #129
: MOV      1, #0
D MOV      2, #0
N SWI      "OS_Byte"
X CMP      2, #&FF
bC BEQ      nextframe%          ;if no key pressed, do next frame
l- LDR      13, aspframe%       ;restore sp
v2 LDMFD    13!, {PC}           ;return to BASIC
� :
� .ascrst% EQUD scrst%
� .adata%  EQUD balldata%
�& .abackdata%        EQUD backdata%
� .abank%  EQUD 1
�, .aplotregs%        EQUD 0:EQUD 0:EQUD 0
�3 .plot%   ;plot our ball sprite at coords r0,r1
�>          ;where 0,0 is top left & 287,199 is bottom right
�8          ;NB sprite MUST lie entirely within screen
� ADR      11, aplotregs%
� STMIA    11, {12,13,14}
�B �      2, 0, #3            ;calc which of 4 sprite alignments
�F ADD      3, 2, 2, ASL #2     ;we need via (xAND3)*20*2*16 + data%
< BIC      0, 0, #3            ;round x down to mult of 3
 ADD      1, 1, 1, ASL #3
 LDR      2, ascrst%
 " ADD      2, 2, 1, ASL #lhadd%
*B ADD      0, 2, 0             ;calc (screen ptr + hadd%*y + x)
4 LDR      1, adata%
>E ADD      1, 1, 3, ASL #7     ;finally calc (xAND3)*20*2*16+data%
H MOV      2, #4
R ADD      3, 1, #20*16
\2 .loop1%                      ;now plot sprite
f. �plotfrag(pass%)            ;plot 1st row
pD ADD      0, 0, #hadd%-20     ;move screen ptr to start next row
z �plotfrag(pass%)
� ADD      0, 0, #hadd%-20
� �plotfrag(pass%)
� ADD      0, 0, #hadd%-20
�. �plotfrag(pass%)            ;plot 4th row
� ADD      0, 0, #hadd%-20
� SUBS     2, 2, #1
�E BNE      loop1%          ;repeat above 4 times to do all 16 rows
�D ADR      11, aplotregs%      ;plot completed - return to caller
�8 LDMIA    11, {12,13,PC}      ;preserving r12 & r13.
� :
�/ .acollregs%    EQUD 0:EQUD 0:EQUD 0:EQUD 0
�/                EQUD 0:EQUD 0:EQUD 0:EQUD 0
�4 .movencheck%     ;move then collision check our
	2                  ;ball sprite at coords r0,r1
	F                  ;where 0,0 is top left & 287,199 is bottom right
	@                  ;NB sprite MUST lie entirely within screen
	$ ADR      11, acollregs%
	. ADD      0, 0, 2
	8 ADD      1, 1, 3
	B  STMIA    11, {0-4,12,13,14}
	L MOV      0, 0, ASR #8
	V MOV      1, 1, ASR #8
	`B �      2, 0, #3            ;calc which of 4 sprite alignments
	jF ADD      3, 2, 2, ASL #2     ;we need via (xAND3)*20*2*16 + data%
	t< BIC      0, 0, #3            ;round x down to mult of 3
	~ ADD      1, 1, 1, ASL #3
	� LDR      2, ascrst%
	�" ADD      2, 2, 1, ASL #lhadd%
	�B ADD      0, 2, 0             ;calc (screen ptr + hadd%*y + x)
	� LDR      1, adata%
	�E ADD      1, 1, 3, ASL #7     ;finally calc (xAND3)*20*2*16+data%
	� ADD      1, 1, #20*16
	�E ADR      2, colladdrbuf%     ;store screen and sprite data addrs
	�D STMIA    2, {0,1}            ;corresponding to top left of ball
	� MOV      2, #4
	�3 .collloop1%                  ;now check sprite
	�D �collfrag(pass%)            ;check 1st row (if coll B gotcoll%)
	�D ADD      0, 0, #hadd%-20     ;move screen ptr to start next row
 �collfrag(pass%)

 ADD      0, 0, #hadd%-20
 �collfrag(pass%)
 ADD      0, 0, #hadd%-20
(/ �collfrag(pass%)            ;check 4th row
2 ADD      0, 0, #hadd%-20
< SUBS     2, 2, #1
FE BNE      collloop1%      ;repeat above 4 times to do all 16 rows
P ADR      11, acollregs%
Z  LDMIA    11, {0-4,12,13,14}
d= ADD      3, 3, #8            ; accelerate ball downwards
n MOV      4, #0
x MOV      PC, 14
�% .colladdrbuf%      EQUD 0:EQUD 0
� .gotcoll%
� ADR      11, acollregs%
� LDMIA    11, {0-3}
�C SUB      0, 0, 2             ;reset position, moving it out of
�, SUB      1, 1, 3             ;collision
� STMIA    11, {0,1}
�9 MOV      6, #0               ;in my lin reg notes, n
�9 MOV      7, #0                                   ; u
�9 MOV      8, #0                                   ; v
�9 MOV      9, #0                                   ; p
�9 MOV      10, #0                                  ; q
� ADR      2, colladdrbuf%
C LDMIA    2, {0,1}            ;recall screen/data addrs for top
1 MOV      3, #0     ;row 0    ;left of sprite
 .statloop1%
" MOV      2, #0     ;col 0
, .statloop2%
6F LDR      4, [0], #4          ;rescan each pixel in collision area
@F LDR      5, [1], #4          ;and for each collided pixel add its
JD �      4, 4, 5             ;coords (relative to topleft sprite)
T@ �statfrag(pass%, 255)       ;onto the regression statistics
^ ADD      2, 2, #1
h �statfrag(pass%, 255<<8)
r ADD      2, 2, #1
| �statfrag(pass%, 255<<16)
� ADD      2, 2, #1
� �statfrag(pass%, 255<<24)
� ADD      2, 2, #1
� CMP      2, #20
� BLT      statloop2%
� ADD      0, 0, #hadd%-20
� ADD      3, 3, #1
� CMP      3, #16
�? BLT      statloop1%          ;when done, n, u & v computed
� MUL      9, 6, 9
� ADD      5, 7, 8
� SUB      14, 7, 8
�- MLA      9, 5, 14, 9         ;p computed
 MUL      10, 6, 10
 MUL      14, 7, 8
 SUB      10, 10, 14
&- ADD      10, 10, 10          ;q computed
0 MOVS     6, 9
:- RSBMI    6, 6, #0            ;ap = abs p
D MOVS     7, 10
N- RSBMI    7, 7, #0            ;aq = abs q
X CMP      6, 7
b MOV      8, 6
l3 MOVLT    8, 7                ; m = max {ap,aq}
v? CMP      8, #0               ;if have degenerate collision
�E BEQ      patch1%             ;(eg with single pixel), can't calc
�E .statloop3%                  ;a linear regression, so go patch1%
�D CMP      8, #1<<12           ;which simply reverses velocities!
� MOVGE    8, 8, ASR #1
�F MOVGE    6, 6, ASR #1        ;proportionately reduce ap and aq in
�F MOVGE    7, 7, ASR #1        ;magnitude, until in necessary range
� BGE      statloop3%
�4 MUL      11, 6, 6            ;ap^2 in low range
�4 MUL      12, 7, 7            ;aq^2 in low range
�4 ADD      13, 11, 12          ;divisor ap^2+aq^2
� MOV      0, 11, ASL #8
�A �div(pass%, 0, 13, 11, 1)   ;t  in r11 = 256ap^2/(ap^2+aq^2)
� MOV      0, 12, ASL #8

A �div(pass%, 0, 13, 12, 1)   ;tb in r12 = 256aq^2/(ap^2+aq^2)

 LDR      13, asqrt%

0 LDR      7, [13, 11, LSL #2] ;square root t

 < LDR      8, [13, 12, LSL #2] ;and tb, via look-up-table

* CMP      9, #0

41 RSBLT    7, 7, #0            ;final t  in r7

> CMP      10, #0

H1 RSBPL    8, 8, #0            ;final tb in r8

R ADR      11, acollregs%

\  LDMIA    11, {0-4,12,13,14}

f9 MUL      5, 7, 2             ;now modify velocity by

p7 MLA      5, 8, 3, 5          ;reflecting it in the

z? RSB      5, 5, #0            ;line generated by the linear

�9 MUL      6, 7, 3             ;regression calculation

�C MUL      9, 8, 2             ;(which we use to approximate the

�E SUB      6, 6, 9             ; tangent at the collision surface)

� RSB      5, 5, 5, ASL #8

�E RSB      6, 6, 6, ASL #8     ;& then attenuate by factor 255/256

�A MOV      2, 5, ASR #16       ;(simulate energy loss on coll)

� MOV      3, 6, ASR #16

�D ADD      4, 4, #1            ;track how many consecutive frames

�@ :                            ;this ball has been stuck in a

�E CMP      4,#2                ;collision and if 2 or more, try to

�9 BLT      movencheck%         ;escape it via a bodge:

�2 .bodge1%                     ;bodge begin ...

� ADR      7, seed%
 LDMIA    7, {5, 6}
@ MOVS     6, 6, LSR #1        ;generate random 32-bit number
 MOVS     8, 5, RRX
$ ADC      6, 6, 6
. �      8, 8, 5, LSL #12
8 �      5, 8, 8, LSR #20
B STMIA    7, {5, 6}
L7 LDR      7, asincos%         ;when balls get stuck
V@ �      5, 5, #255          ;due to conflict between correct
`A ADD      7, 7, 5, ASL #3     ;reflection & small velocity or
j> LDMIA    7, {5, 6}           ;jagged overlap problems ...
t MUL      7, 2, 5
~C MLA      7, 3, 6, 7          ;try a 'fix' - rotate velocity by
�@ MUL      8, 2, 6             ;a random angle, so eventually
�A MUL      9, 3, 5             ;should pick some velocity that
�F SUB      8, 8, 9             ;extricates ball from stuck position
� MOV      2, 7, ASR #8
�0 MOV      3, 8, ASR #8        ;... bodge end
� CMP      4, #16
� BLT      movencheck%
� MOV      PC, 14
� :
�$ .asincos%          EQUD sincos%
� .seed%   EQUD -1:EQUD -1
�F .patch1%                     ;a patch to deal with collision case
D ADR      11, acollregs%      ;where no linear regression exists

D LDMIA    11, {0-4,12,13,14}  ;(eg where collision involves only
. SUB      2, 2, 2, ASL #8     ; one pixel)
= SUB      3, 3, 3, ASL #8     ;- simply reverse velocity!
( MOV      2, 2, ASR #8
2F MOV      3, 3, ASR #8        ;nb also attenuate by factor 255/256
<A ADD      4, 4, #1            ;(simulate energy loss on coll)
F CMP      4,#2
P BLT      movencheck%
ZF B        bodge1%             ;if been stuck in collision for >= 2
dF :                            ;frames go and apply bodged 'escape'
n .asqrt%  EQUD sqrt%
x .alrcls% EQUD 0
� .aspcls% EQUD 0
�D .copyback%                   ;simple routine to clear screen to
�F STR      14, alrcls%         ;background as rapidly as possible -
�A STR      13, aspcls%         ;note the heavy use of LDM/STM.
� LDR      0, ascrst%
� LDR      1, abackdata%
� ADD      1, 1, #56
� MOV      2, #200
� .clsloop%
� LDMIA    1!, {3-14}
� STMIA    0!, {3-14}
� LDMIA    1!, {3-14}
� STMIA    0!, {3-14}
 LDMIA    1!, {3-14}
 STMIA    0!, {3-14}
 LDMIA    1!, {3-14}
" STMIA    0!, {3-14}
, LDMIA    1!, {3-14}
6 STMIA    0!, {3-14}
@ LDMIA    1!, {3-14}
J STMIA    0!, {3-14}
T ]
^
 � VGA% �
h [OPT pass%
r  ADD      0, 0, #hadd%-hpix%
| ]
� �
� [OPT pass%
� SUBS     2, 2, #1
� BNE      clsloop%
� LDR      13, aspcls%
� LDR      PC, alrcls%
� ]
��
��
�:
�<� �plotfrag(pass%)    :� macro to plot a row (20 pixels)
�-[OPT pass%               :� of our sprite
�ELDMIA    0, {4-6}             ;read 3 words of screen (12 pixels)
8LDMIA    1!, {7-9}            ;read 12 sprite pixels
-LDMIA    3!, {10-12}          ;& 12 masks
@BIC      4, 4, 10             ;apply mask to screen, zeroing
&?BIC      5, 5, 11             ; those bits where will write
0<BIC      6, 6, 12             ; sprite image in a moment
:;�R      4, 4, 7              ;write in the sprite image
D�R      5, 5, 8
N�R      6, 6, 9
XBSTMIA    0!, {4-6}            ;restore the data back to screen
bDLDMIA    0, {4-5}             ;read 2 words of screen (8 pixels)
l7LDMIA    1!, {7-8}            ;read 8 sprite pixels
v,LDMIA    3!, {10-11}          ;& 8 masks
�BIC      4, 4, 10
�BIC      5, 5, 11
��R      4, 4, 7
��R      5, 5, 8
�BSTMIA    0!, {4-5}            ;restore the data back to screen
�]
�
=pass%
�:
�6� �collfrag(pass%)    :� macro to coll check a row
�9[OPT pass%               :� (20 pixels) of our sprite
�ELDMIA    0!, {3-7}            ;read 5 words of screen (20 pixels)
�=LDMIA    1!, {8-12}           ;read 20 sprite pixel masks
�TST      3, 8
TSTEQ    4, 9
TSTEQ    5, 10
TSTEQ    6, 11
 TSTEQ    7, 12
*DBNE      gotcoll%             ;branch to gotcoll% if any overlap
4D]                        :�  else continue with code after macro
>
=pass%
H:
R=� �statfrag(pass%, m%):� macro to add in regression stats
\@[OPT pass%               :� for one pixel (coords u(i),v(i))
fTST       4, #m%
pBEQ       P%+8*4
z-ADDNE     6, 6, #1            ; n = n + 1
�0ADDNE     7, 7, 2             ; u = u + u(i)
�0ADDNE     8, 8, 3             ; v = v + v(i)
�ADDNE     5, 2, 3
�SUBNE     14, 3, 2
�9MLANE     9, 5, 14, 9         ; p = p + v(i)^2-u(i)^2
�5MLANE     10, 2, 3, 10        ; q = q + u(i)*v(i)
�]
�
=pass%
�:
�<� �div(pass%, ra, rb, rc, rd) :� macro to set rc=raDIVrb
�[OPT pass%
�MOV       rd, rb
�CMP       rd, ra, LSR #1
MOVLS     rd, rd, LSL #1
CMP       rd, ra, LSR #1
BLS       P%-2*4
$MOV       rc, #0
.CMP       ra, rd
8SUBCS     ra, ra, rd
BADC       rc, rc, rc
LMOV       rd, rd, LSR #1
VCMP       rd, rb
`BHS       P%-5*4
j]
t
=pass%
�
00000000  0d 00 0a 0c f4 20 3e 42  61 6c 6c 73 0d 00 14 05  |..... >Balls....|
00000010  f4 0d 00 1e 05 3a 0d 00  28 3d f4 20 4e 42 20 70  |.....:..(=. NB p|
00000020  72 6f 67 72 61 6d 20 77  69 6c 6c 20 70 72 6f 64  |rogram will prod|
00000030  75 63 65 20 61 20 62 65  65 70 20 69 66 20 61 6e  |uce a beep if an|
00000040  69 6d 61 74 69 6f 6e 20  73 70 65 65 64 20 66 61  |imation speed fa|
00000050  6c 6c 73 0d 00 32 20 f4  20 62 65 6c 6f 77 20 74  |lls..2 . below t|
00000060  68 65 20 74 61 72 67 65  74 20 66 70 73 20 72 61  |he target fps ra|
00000070  74 65 2e 0d 00 3c 13 74  61 72 67 65 74 66 70 73  |te...<.targetfps|
00000080  25 20 3d 20 35 30 0d 00  46 41 e7 20 31 30 30 83  |% = 50..FA. 100.|
00000090  74 61 72 67 65 74 66 70  73 25 3c 3e 30 20 85 20  |targetfps%<>0 . |
000000a0  31 2c 20 22 52 65 71 75  69 72 65 20 74 61 72 67  |1, "Require targ|
000000b0  65 74 66 70 73 20 64 69  76 69 64 65 73 20 69 6e  |etfps divides in|
000000c0  74 6f 20 31 30 30 22 0d  00 50 05 3a 0d 00 5a 1e  |to 100"..P.:..Z.|
000000d0  c8 99 20 26 32 30 32 38  30 2c 20 30 2c 20 2d 31  |.. &20280, 0, -1|
000000e0  20 b8 20 3b 66 6c 61 67  73 25 0d 00 64 24 e7 20  | . ;flags%..d$. |
000000f0  66 6c 61 67 73 25 20 80  20 31 20 8c 20 61 72 6d  |flags% . 1 . arm|
00000100  33 25 3d a3 20 8b 20 61  72 6d 33 25 3d b9 0d 00  |3%=. . arm3%=...|
00000110  6e 05 3a 0d 00 78 32 ee  20 85 20 c8 99 20 36 2c  |n.:..x2. . .. 6,|
00000120  31 31 32 2c 31 3a c8 99  20 36 2c 31 31 33 2c 31  |112,1:.. 6,113,1|
00000130  3a f1 20 f6 24 3b 22 20  61 74 20 6c 69 6e 65 20  |:. .$;" at line |
00000140  22 3b 9e 3a e0 0d 00 82  0e 44 25 20 3d 20 b3 28  |";.:.....D% = .(|
00000150  2d 91 29 0d 00 8c 05 3a  0d 00 96 05 db 0d 00 a0  |-.)....:........|
00000160  30 f1 20 22 20 20 20 20  20 20 20 20 20 20 20 20  |0. "            |
00000170  20 20 20 20 20 20 20 20  42 20 41 20 4c 20 4c 20  |        B A L L |
00000180  53 20 20 20 44 20 45 20  4d 20 4f 22 27 0d 00 aa  |S   D E M O"'...|
00000190  5c f1 20 22 8f 20 50 72  6f 67 72 61 6d 20 77 69  |\. ". Program wi|
000001a0  6c 6c 20 62 65 65 70 20  69 66 20 61 6e 69 6d 61  |ll beep if anima|
000001b0  74 69 6f 6e 20 73 70 65  65 64 20 66 61 6c 6c 73  |tion speed falls|
000001c0  20 62 65 6c 6f 77 20 74  68 65 20 74 61 72 67 65  | below the targe|
000001d0  74 20 6f 66 20 22 3b 74  61 72 67 65 74 66 70 73  |t of ";targetfps|
000001e0  25 3b 22 20 66 70 73 2e  22 0d 00 b4 3e f1 20 22  |%;" fps."...>. "|
000001f0  8f 20 50 72 65 73 73 69  6e 67 20 61 6e 79 20 6b  |. Pressing any k|
00000200  65 79 20 64 75 72 69 6e  67 20 64 65 6d 6f 20 77  |ey during demo w|
00000210  69 6c 6c 20 61 64 64 20  6f 6e 65 20 6d 6f 72 65  |ill add one more|
00000220  20 62 61 6c 6c 2e 22 0d  00 be 27 f1 20 22 8f 20  | ball."...'. ". |
00000230  50 72 65 73 73 20 45 73  63 61 70 65 20 74 6f 20  |Press Escape to |
00000240  65 6e 64 20 70 72 6f 67  72 61 6d 2e 22 27 0d 00  |end program."'..|
00000250  c8 39 e8 20 22 50 6c 65  61 73 65 20 69 6e 70 75  |.9. "Please inpu|
00000260  74 20 53 74 61 6e 64 61  72 64 20 28 30 29 20 6f  |t Standard (0) o|
00000270  72 20 56 47 41 20 28 31  29 20 64 69 73 70 6c 61  |r VGA (1) displa|
00000280  79 22 3b 56 47 41 25 0d  00 d2 14 e7 20 56 47 41  |y";VGA%..... VGA|
00000290  25 3c 3e 31 20 56 47 41  25 3d 30 0d 00 dc 05 3a  |%<>1 VGA%=0....:|
000002a0  0d 00 e6 0d 68 70 69 78  25 3d 32 38 38 0d 00 f0  |....hpix%=288...|
000002b0  0d 76 70 69 78 25 3d 32  30 30 0d 00 fa 0c e7 20  |.vpix%=200..... |
000002c0  56 47 41 25 20 8c 0d 01  04 0d 20 6d 6f 64 65 25  |VGA% ..... mode%|
000002d0  3d 39 39 0d 01 0e 0f 20  61 76 70 69 78 25 3d 34  |=99.... avpix%=4|
000002e0  30 30 0d 01 18 12 20 68  61 64 64 25 3d 68 70 69  |00.... hadd%=hpi|
000002f0  78 25 2a 32 0d 01 22 0d  20 6c 68 61 64 64 25 3d  |x%*2..". lhadd%=|
00000300  36 0d 01 2c 05 cc 0d 01  36 0d 20 6d 6f 64 65 25  |6..,....6. mode%|
00000310  3d 39 38 0d 01 40 0f 20  61 76 70 69 78 25 3d 32  |=98..@. avpix%=2|
00000320  30 30 0d 01 4a 10 20 68  61 64 64 25 3d 68 70 69  |00..J. hadd%=hpi|
00000330  78 25 0d 01 54 0d 20 6c  68 61 64 64 25 3d 35 0d  |x%..T. lhadd%=5.|
00000340  01 5e 05 cd 0d 01 68 05  3a 0d 01 72 14 de 20 62  |.^....h.:..r.. b|
00000350  61 6c 6c 64 61 74 61 25  20 32 35 36 30 0d 01 7c  |alldata% 2560..||
00000360  45 c8 99 20 22 4f 53 5f  46 69 6c 65 22 2c 20 32  |E.. "OS_File", 2|
00000370  35 35 2c 20 22 3c 42 61  6c 6c 73 24 44 69 72 3e  |55, "<Balls$Dir>|
00000380  2e 52 65 73 6f 75 72 63  65 73 2e 42 61 6c 6c 44  |.Resources.BallD|
00000390  61 74 61 22 2c 20 62 61  6c 6c 64 61 74 61 25 2c  |ata", balldata%,|
000003a0  20 30 0d 01 86 15 de 20  62 61 63 6b 64 61 74 61  | 0..... backdata|
000003b0  25 20 35 37 36 35 36 0d  01 90 44 c8 99 20 22 4f  |% 57656...D.. "O|
000003c0  53 5f 46 69 6c 65 22 2c  20 32 35 35 2c 20 22 3c  |S_File", 255, "<|
000003d0  42 61 6c 6c 73 24 44 69  72 3e 2e 52 65 73 6f 75  |Balls$Dir>.Resou|
000003e0  72 63 65 73 2e 42 61 63  6b 53 70 72 22 2c 20 62  |rces.BackSpr", b|
000003f0  61 63 6b 64 61 74 61 25  2c 20 30 0d 01 9a 05 3a  |ackdata%, 0....:|
00000400  0d 01 a4 19 de 20 76 62  6c 69 6e 25 20 38 2c 20  |..... vblin% 8, |
00000410  76 62 6c 6f 75 74 25 20  38 0d 01 ae 1b 21 76 62  |vblout% 8....!vb|
00000420  6c 69 6e 25 3d 31 34 38  3a 76 62 6c 69 6e 25 21  |lin%=148:vblin%!|
00000430  34 3d 2d 31 0d 01 b8 0f  eb 20 6d 6f 64 65 25 2b  |4=-1..... mode%+|
00000440  31 32 38 0d 01 c2 2d c8  99 20 22 4f 53 5f 52 65  |128...-.. "OS_Re|
00000450  61 64 56 64 75 56 61 72  69 61 62 6c 65 73 22 2c  |adVduVariables",|
00000460  20 76 62 6c 69 6e 25 2c  20 76 62 6c 6f 75 74 25  | vblin%, vblout%|
00000470  0d 01 cc 14 73 63 72 73  74 32 25 3d 21 76 62 6c  |....scrst2%=!vbl|
00000480  6f 75 74 25 0d 01 d6 0b  eb 20 6d 6f 64 65 25 0d  |out%..... mode%.|
00000490  01 e0 2d c8 99 20 22 4f  53 5f 52 65 61 64 56 64  |..-.. "OS_ReadVd|
000004a0  75 56 61 72 69 61 62 6c  65 73 22 2c 20 76 62 6c  |uVariables", vbl|
000004b0  69 6e 25 2c 20 76 62 6c  6f 75 74 25 0d 01 ea 14  |in%, vblout%....|
000004c0  73 63 72 73 74 31 25 3d  21 76 62 6c 6f 75 74 25  |scrst1%=!vblout%|
000004d0  0d 01 f4 05 87 0d 01 fe  05 3a 0d 02 08 0d 6d 61  |.........:....ma|
000004e0  78 6e 25 3d 32 30 30 0d  02 12 11 de 20 62 25 20  |xn%=200..... b% |
000004f0  6d 61 78 6e 25 2a 32 30  0d 02 1c 33 f4 20 4e 42  |maxn%*20...3. NB|
00000500  20 62 25 20 73 74 6f 72  65 73 20 61 72 72 61 79  | b% stores array|
00000510  20 28 6f 66 20 73 69 7a  65 20 6e 25 29 20 6f 66  | (of size n%) of|
00000520  20 73 74 72 75 63 74 75  72 65 3a 0d 02 26 42 f4  | structure:..&B.|
00000530  20 7b 78 20 63 6f 6f 72  64 2c 20 79 20 63 6f 6f  | {x coord, y coo|
00000540  72 64 2c 20 78 20 69 6e  63 72 65 6d 65 6e 74 2c  |rd, x increment,|
00000550  20 79 20 69 6e 63 72 65  6d 65 6e 74 2c 20 73 74  | y increment, st|
00000560  69 63 6b 69 6e 67 20 63  6f 75 6e 74 7d 0d 02 30  |icking count}..0|
00000570  05 3a 0d 02 3a 08 f2 61  73 73 0d 02 44 05 3a 0d  |.:..:..ass..D.:.|
00000580  02 4e 19 c8 99 20 36 2c  31 31 32 2c 31 3a c8 99  |.N... 6,112,1:..|
00000590  20 36 2c 31 31 33 2c 31  0d 02 58 08 6e 25 3d 31  | 6,113,1..X.n%=1|
000005a0  0d 02 62 0b 21 61 6e 25  3d 6e 25 0d 02 6c 05 3a  |..b.!an%=n%..l.:|
000005b0  0d 02 76 2c f4 20 69 6e  69 74 69 61 6c 69 73 65  |..v,. initialise|
000005c0  20 62 61 6c 6c 20 6c 6f  63 61 74 69 6f 6e 73 20  | ball locations |
000005d0  26 20 76 65 6c 6f 63 69  74 69 65 73 0d 02 80 1b  |& velocities....|
000005e0  e3 20 69 25 20 3d 20 30  20 b8 20 6e 25 2a 32 30  |. i% = 0 . n%*20|
000005f0  2d 31 20 88 20 32 30 0d  02 8a 1a 20 20 62 25 21  |-1 . 20....  b%!|
00000600  28 69 25 2b 30 29 20 20  3d 20 32 35 39 2a 32 35  |(i%+0)  = 259*25|
00000610  36 0d 02 94 1a 20 20 62  25 21 28 69 25 2b 34 29  |6....  b%!(i%+4)|
00000620  20 20 3d 20 31 37 34 2a  32 35 36 0d 02 9e 1b 20  |  = 174*256.... |
00000630  20 62 25 21 28 69 25 2b  38 29 20 20 3d 20 b3 28  | b%!(i%+8)  = .(|
00000640  36 34 29 2d 33 32 0d 02  a8 23 20 20 62 25 21 28  |64)-32...#  b%!(|
00000650  69 25 2b 31 32 29 20 3d  20 2d 34 2a 32 35 36 2b  |i%+12) = -4*256+|
00000660  b3 28 31 32 38 29 2d 36  34 0d 02 b2 14 20 20 62  |.(128)-64....  b|
00000670  25 21 28 69 25 2b 31 36  29 20 3d 20 30 0d 02 bc  |%!(i%+16) = 0...|
00000680  05 ed 0d 02 c6 05 3a 0d  02 d0 05 f5 0d 02 da 0c  |......:.........|
00000690  20 d6 20 61 6e 69 6d 25  0d 02 e4 11 20 e7 20 6e  | . anim%.... . n|
000006a0  25 3c 6d 61 78 6e 25 20  8c 0d 02 ee 0e 20 20 69  |%<maxn% .....  i|
000006b0  25 3d 32 30 2a 6e 25 0d  02 f8 1a 20 20 62 25 21  |%=20*n%....  b%!|
000006c0  28 69 25 2b 30 29 20 20  3d 20 32 35 39 2a 32 35  |(i%+0)  = 259*25|
000006d0  36 0d 03 02 1a 20 20 62  25 21 28 69 25 2b 34 29  |6....  b%!(i%+4)|
000006e0  20 20 3d 20 31 37 34 2a  32 35 36 0d 03 0c 1b 20  |  = 174*256.... |
000006f0  20 62 25 21 28 69 25 2b  38 29 20 20 3d 20 b3 28  | b%!(i%+8)  = .(|
00000700  36 34 29 2d 33 32 0d 03  16 23 20 20 62 25 21 28  |64)-32...#  b%!(|
00000710  69 25 2b 31 32 29 20 3d  20 2d 34 2a 32 35 36 2b  |i%+12) = -4*256+|
00000720  b3 28 31 32 38 29 2d 36  34 0d 03 20 14 20 20 62  |.(128)-64.. .  b|
00000730  25 21 28 69 25 2b 31 36  29 20 3d 20 30 0d 03 2a  |%!(i%+16) = 0..*|
00000740  0b 20 20 6e 25 2b 3d 31  0d 03 34 0d 20 20 21 61  |.  n%+=1..4.  !a|
00000750  6e 25 3d 6e 25 0d 03 3e  06 20 cd 0d 03 48 07 fd  |n%=n%..>. ...H..|
00000760  20 a3 0d 03 52 05 3a 0d  03 5c 05 e0 0d 03 66 05  | ...R.:..\....f.|
00000770  3a 0d 03 70 0a dd 20 f2  61 73 73 0d 03 7a 2d de  |:..p.. .ass..z-.|
00000780  20 63 6f 64 65 25 20 31  30 32 34 30 2c 20 73 71  | code% 10240, sq|
00000790  72 74 25 20 32 35 37 2a  34 2c 20 73 69 6e 63 6f  |rt% 257*4, sinco|
000007a0  73 25 20 32 35 36 2a 38  0d 03 84 10 e3 20 69 25  |s% 256*8..... i%|
000007b0  3d 30 20 b8 20 32 35 36  0d 03 8e 21 20 73 71 72  |=0 . 256...! sqr|
000007c0  74 25 21 28 34 2a 69 25  29 20 3d 20 30 2e 35 2b  |t%!(4*i%) = 0.5+|
000007d0  b6 28 32 35 36 2a 69 25  29 0d 03 98 05 ed 0d 03  |.(256*i%).......|
000007e0  a2 10 e3 20 69 25 3d 30  20 b8 20 32 35 35 0d 03  |... i%=0 . 255..|
000007f0  ac 2d 20 73 69 6e 63 6f  73 25 21 28 38 2a 69 25  |.- sincos%!(8*i%|
00000800  20 20 29 20 3d 20 30 2e  35 2b 32 35 36 2a b5 28  |  ) = 0.5+256*.(|
00000810  32 2a af 2a 69 25 2f 32  35 36 29 0d 03 b6 2d 20  |2*.*i%/256)...- |
00000820  73 69 6e 63 6f 73 25 21  28 38 2a 69 25 2b 34 29  |sincos%!(8*i%+4)|
00000830  20 3d 20 30 2e 35 2b 32  35 36 2a 9b 28 32 2a af  | = 0.5+256*.(2*.|
00000840  2a 69 25 2f 32 35 36 29  0d 03 c0 05 ed 0d 03 ca  |*i%/256)........|
00000850  12 73 63 72 73 74 25 3d  73 63 72 73 74 31 25 0d  |.scrst%=scrst1%.|
00000860  03 d4 17 e3 20 70 61 73  73 25 20 3d 20 30 20 b8  |.... pass% = 0 .|
00000870  20 32 20 88 20 32 0d 03  de 0d 20 50 25 3d 63 6f  | 2 . 2.... P%=co|
00000880  64 65 25 0d 03 e8 0f 20  5b 4f 50 54 20 70 61 73  |de%.... [OPT pas|
00000890  73 25 0d 03 f2 1e 20 2e  61 73 70 66 72 61 6d 65  |s%.... .aspframe|
000008a0  25 20 20 20 20 20 20 20  20 20 45 51 55 44 20 30  |%         EQUD 0|
000008b0  0d 03 fc 2c 20 2e 61 73  63 72 73 74 73 75 6d 25  |..., .ascrstsum%|
000008c0  20 20 20 20 20 20 20 20  45 51 55 44 20 73 63 72  |        EQUD scr|
000008d0  73 74 31 25 2b 73 63 72  73 74 32 25 0d 04 06 14  |st1%+scrst2%....|
000008e0  20 2e 61 6e 25 20 20 20  20 20 45 51 55 44 20 30  | .an%     EQUD 0|
000008f0  0d 04 10 15 20 2e 61 62  25 20 20 20 20 20 45 51  |.... .ab%     EQ|
00000900  55 44 20 62 25 0d 04 1a  44 20 2e 61 74 69 6d 65  |UD b%...D .atime|
00000910  25 20 20 45 51 55 44 20  30 20 20 20 20 20 20 20  |%  EQUD 0       |
00000920  20 20 20 20 20 20 20 3b  74 69 6d 65 20 73 74 6f  |       ;time sto|
00000930  72 61 67 65 20 66 6f 72  20 66 72 61 6d 65 20 73  |rage for frame s|
00000940  70 65 65 64 20 63 61 6c  63 0d 04 24 30 20 2e 61  |peed calc..$0 .a|
00000950  66 63 25 20 20 20 20 45  51 55 44 20 30 20 20 20  |fc%    EQUD 0   |
00000960  20 20 20 20 20 20 20 20  20 20 20 3b 66 72 61 6d  |           ;fram|
00000970  65 20 63 6f 75 6e 74 65  72 0d 04 2e 0b 20 2e 61  |e counter.... .a|
00000980  6e 69 6d 25 0d 04 38 17  20 53 54 4d 46 44 20 20  |nim%..8. STMFD  |
00000990  20 20 31 33 21 2c 20 7b  31 34 7d 0d 04 42 3a 20  |  13!, {14}..B: |
000009a0  53 54 52 20 20 20 20 20  20 31 33 2c 20 61 73 70  |STR      13, asp|
000009b0  66 72 61 6d 65 25 20 20  20 20 20 20 20 3b 73 74  |frame%       ;st|
000009c0  6f 72 65 20 73 70 20 74  6f 20 66 72 65 65 20 75  |ore sp to free u|
000009d0  70 20 72 31 33 0d 04 4c  10 20 2e 6e 65 78 74 66  |p r13..L. .nextf|
000009e0  72 61 6d 65 25 0d 04 56  06 20 3a 0d 04 60 3e 20  |rame%..V. :..`> |
000009f0  53 57 49 20 20 20 20 20  20 22 4f 53 5f 52 65 61  |SWI      "OS_Rea|
00000a00  64 4d 6f 6e 6f 74 6f 6e  69 63 54 69 6d 65 22 20  |dMonotonicTime" |
00000a10  20 20 20 20 20 20 20 3b  74 72 61 63 6b 20 66 72  |       ;track fr|
00000a20  61 6d 65 20 73 70 65 65  64 0d 04 6a 17 20 53 54  |ame speed..j. ST|
00000a30  52 20 20 20 20 20 20 30  2c 20 61 74 69 6d 65 25  |R      0, atime%|
00000a40  0d 04 74 06 20 3a 0d 04  7e 14 20 4d 4f 56 20 20  |..t. :..~. MOV  |
00000a50  20 20 20 20 30 2c 20 23  31 39 0d 04 88 3b 20 53  |    0, #19...; S|
00000a60  57 49 20 20 20 20 20 20  22 4f 53 5f 42 79 74 65  |WI      "OS_Byte|
00000a70  22 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |"               |
00000a80  20 20 20 20 20 20 3b 77  61 69 74 20 66 6f 72 20  |      ;wait for |
00000a90  76 73 79 6e 63 0d 04 92  15 20 4d 4f 56 20 20 20  |vsync.... MOV   |
00000aa0  20 20 20 30 2c 20 23 31  31 33 0d 04 9c 17 20 4c  |   0, #113.... L|
00000ab0  44 52 20 20 20 20 20 20  31 2c 20 61 62 61 6e 6b  |DR      1, abank|
00000ac0  25 0d 04 a6 16 20 52 53  42 20 20 20 20 20 20 33  |%.... RSB      3|
00000ad0  2c 20 31 2c 20 23 33 0d  04 b0 17 20 53 54 52 20  |, 1, #3.... STR |
00000ae0  20 20 20 20 20 33 2c 20  61 62 61 6e 6b 25 0d 04  |     3, abank%..|
00000af0  ba 3d 20 53 57 49 20 20  20 20 20 20 22 4f 53 5f  |.= SWI      "OS_|
00000b00  42 79 74 65 22 20 20 20  20 20 20 20 20 20 20 20  |Byte"           |
00000b10  3b 73 77 61 70 20 64 69  73 70 6c 61 79 65 64 20  |;swap displayed |
00000b20  73 63 72 65 65 6e 20 62  61 6e 6b 0d 04 c4 1b 20  |screen bank.... |
00000b30  4c 44 52 20 20 20 20 20  20 30 2c 20 61 73 63 72  |LDR      0, ascr|
00000b40  73 74 73 75 6d 25 0d 04  ce 18 20 4c 44 52 20 20  |stsum%.... LDR  |
00000b50  20 20 20 20 31 2c 20 61  73 63 72 73 74 25 0d 04  |    1, ascrst%..|
00000b60  d8 15 20 53 55 42 20 20  20 20 20 20 31 2c 20 30  |.. SUB      1, 0|
00000b70  2c 20 31 0d 04 e2 39 20  53 54 52 20 20 20 20 20  |, 1...9 STR     |
00000b80  20 31 2c 20 61 73 63 72  73 74 25 20 20 20 20 20  | 1, ascrst%     |
00000b90  20 20 20 20 20 3b 73 77  61 70 20 70 74 72 20 74  |     ;swap ptr t|
00000ba0  6f 20 6f 74 68 65 72 20  62 61 6e 6b 0d 04 ec 3e  |o other bank...>|
00000bb0  20 42 4c 20 20 20 20 20  20 20 63 6f 70 79 62 61  | BL       copyba|
00000bc0  63 6b 25 20 20 20 20 20  20 20 20 20 20 20 3b 63  |ck%           ;c|
00000bd0  6c 73 20 74 68 61 74 20  62 61 6e 6b 20 74 6f 20  |ls that bank to |
00000be0  62 61 63 6b 67 72 6f 75  6e 64 0d 04 f6 06 20 3a  |background.... :|
00000bf0  0d 05 00 15 20 4c 44 52  20 20 20 20 20 20 31 32  |.... LDR      12|
00000c00  2c 20 61 62 25 0d 05 0a  15 20 4c 44 52 20 20 20  |, ab%.... LDR   |
00000c10  20 20 20 31 33 2c 20 61  6e 25 0d 05 14 36 20 2e  |   13, an%...6 .|
00000c20  66 72 61 6d 65 6d 6f 76  65 6c 6f 6f 70 25 20 20  |framemoveloop%  |
00000c30  20 20 20 20 20 20 20 20  20 20 20 20 3b 74 68 65  |            ;the|
00000c40  6e 20 6d 6f 76 65 20 65  61 63 68 20 62 61 6c 6c  |n move each ball|
00000c50  0d 05 1e 35 20 4c 44 4d  49 41 20 20 20 20 31 32  |...5 LDMIA    12|
00000c60  2c 20 7b 30 2c 31 2c 32  2c 33 2c 34 7d 20 20 20  |, {0,1,2,3,4}   |
00000c70  20 20 3b 20 72 65 61 64  20 78 2c 79 2c 78 69 2c  |  ; read x,y,xi,|
00000c80  79 69 2c 73 63 0d 05 28  19 20 42 4c 20 20 20 20  |yi,sc..(. BL    |
00000c90  20 20 20 6d 6f 76 65 6e  63 68 65 63 6b 25 0d 05  |   movencheck%..|
00000ca0  32 38 20 53 54 4d 49 41  20 20 20 20 31 32 21 2c  |28 STMIA    12!,|
00000cb0  20 7b 30 2c 31 2c 32 2c  33 2c 34 7d 20 20 20 20  | {0,1,2,3,4}    |
00000cc0  3b 20 72 65 73 74 6f 72  65 20 78 2c 79 2c 78 69  |; restore x,y,xi|
00000cd0  2c 79 69 2c 73 63 0d 05  3c 18 20 53 55 42 53 20  |,yi,sc..<. SUBS |
00000ce0  20 20 20 20 31 33 2c 20  31 33 2c 20 23 31 0d 05  |    13, 13, #1..|
00000cf0  46 34 20 42 4e 45 20 20  20 20 20 20 66 72 61 6d  |F4 BNE      fram|
00000d00  65 6d 6f 76 65 6c 6f 6f  70 25 20 20 20 20 20 20  |emoveloop%      |
00000d10  3b 74 68 65 6e 20 64 6f  20 6e 65 78 74 20 62 61  |;then do next ba|
00000d20  6c 6c 0d 05 50 06 20 3a  0d 05 5a 15 20 4c 44 52  |ll..P. :..Z. LDR|
00000d30  20 20 20 20 20 20 31 32  2c 20 61 62 25 0d 05 64  |      12, ab%..d|
00000d40  15 20 4c 44 52 20 20 20  20 20 20 31 33 2c 20 61  |. LDR      13, a|
00000d50  6e 25 0d 05 6e 36 20 2e  66 72 61 6d 65 70 6c 6f  |n%..n6 .frameplo|
00000d60  74 6c 6f 6f 70 25 20 20  20 20 20 20 20 20 20 20  |tloop%          |
00000d70  20 20 20 20 3b 6e 6f 77  20 70 6c 6f 74 20 65 61  |    ;now plot ea|
00000d80  63 68 20 62 61 6c 6c 3a  0d 05 78 3d 20 4c 44 4d  |ch ball:..x= LDM|
00000d90  49 41 20 20 20 20 31 32  2c 20 7b 30 2c 31 7d 20  |IA    12, {0,1} |
00000da0  20 20 20 20 20 20 20 20  20 20 3b 20 72 65 61 64  |          ; read|
00000db0  20 78 2c 79 20 63 6f 6f  72 64 73 20 66 72 6f 6d  | x,y coords from|
00000dc0  20 64 61 74 61 0d 05 82  1a 20 4d 4f 56 20 20 20  | data.... MOV   |
00000dd0  20 20 20 30 2c 20 30 2c  20 41 53 52 20 23 38 0d  |   0, 0, ASR #8.|
00000de0  05 8c 1a 20 4d 4f 56 20  20 20 20 20 20 31 2c 20  |... MOV      1, |
00000df0  31 2c 20 41 53 52 20 23  38 0d 05 96 34 20 42 4c  |1, ASR #8...4 BL|
00000e00  20 20 20 20 20 20 20 70  6c 6f 74 25 20 20 20 20  |       plot%    |
00000e10  20 20 20 20 20 20 20 20  20 20 20 3b 20 70 6c 6f  |           ; plo|
00000e20  74 20 62 61 6c 6c 20 61  74 20 78 2c 79 0d 05 a0  |t ball at x,y...|
00000e30  19 20 41 44 44 20 20 20  20 20 20 31 32 2c 20 31  |. ADD      12, 1|
00000e40  32 2c 20 23 32 30 0d 05  aa 18 20 53 55 42 53 20  |2, #20.... SUBS |
00000e50  20 20 20 20 31 33 2c 20  31 33 2c 20 23 31 0d 05  |    13, 13, #1..|
00000e60  b4 34 20 42 4e 45 20 20  20 20 20 20 66 72 61 6d  |.4 BNE      fram|
00000e70  65 70 6c 6f 74 6c 6f 6f  70 25 20 20 20 20 20 20  |eplotloop%      |
00000e80  3b 74 68 65 6e 20 64 6f  20 6e 65 78 74 20 62 61  |;then do next ba|
00000e90  6c 6c 0d 05 be 16 20 4c  44 52 20 20 20 20 20 20  |ll.... LDR      |
00000ea0  31 31 2c 20 61 66 63 25  0d 05 c8 18 20 41 44 44  |11, afc%.... ADD|
00000eb0  20 20 20 20 20 20 31 31  2c 20 31 31 2c 20 23 31  |      11, 11, #1|
00000ec0  0d 05 d2 35 20 53 54 52  20 20 20 20 20 20 31 31  |...5 STR      11|
00000ed0  2c 20 61 66 63 25 20 20  20 20 20 20 20 20 20 20  |, afc%          |
00000ee0  20 20 3b 75 70 64 61 74  65 20 66 72 61 6d 65 20  |  ;update frame |
00000ef0  63 6f 75 6e 74 0d 05 dc  06 20 3a 0d 05 e6 06 20  |count.... :.... |
00000f00  5d 0d 05 f0 0d 20 e7 20  56 47 41 25 20 8c 0d 05  |].... . VGA% ...|
00000f10  fa 0f 20 5b 4f 50 54 20  70 61 73 73 25 0d 06 04  |.. [OPT pass%...|
00000f20  44 20 4c 44 52 20 20 20  20 20 20 31 34 2c 20 61  |D LDR      14, a|
00000f30  73 63 72 73 74 25 20 20  20 20 20 20 20 20 20 3b  |scrst%         ;|
00000f40  69 66 20 69 6e 20 56 47  41 20 6d 6f 64 65 2c 20  |if in VGA mode, |
00000f50  66 69 6c 6c 20 69 6e 20  74 68 65 20 65 78 74 72  |fill in the extr|
00000f60  61 0d 06 0e 42 20 41 44  44 20 20 20 20 20 20 31  |a...B ADD      1|
00000f70  33 2c 20 31 34 2c 20 23  68 61 64 64 25 2d 68 70  |3, 14, #hadd%-hp|
00000f80  69 78 25 3b 62 6c 61 6e  6b 20 6c 69 6e 65 73 20  |ix%;blank lines |
00000f90  62 79 20 63 6f 70 79 69  6e 67 20 74 68 65 20 6c  |by copying the l|
00000fa0  69 6e 65 0d 06 18 28 20  4d 4f 56 20 20 20 20 20  |ine...( MOV     |
00000fb0  20 31 32 2c 20 23 76 70  69 78 25 20 20 20 20 20  | 12, #vpix%     |
00000fc0  20 20 20 20 20 3b 61 62  6f 76 65 0d 06 22 12 20  |     ;above..". |
00000fd0  2e 69 6e 74 65 72 6c 61  63 65 6c 31 25 0d 06 2c  |.interlacel1%..,|
00000fe0  19 20 4c 44 4d 49 41 20  20 20 20 31 34 21 2c 20  |. LDMIA    14!, |
00000ff0  7b 30 2d 31 31 7d 0d 06  36 19 20 53 54 4d 49 41  |{0-11}..6. STMIA|
00001000  20 20 20 20 31 33 21 2c  20 7b 30 2d 31 31 7d 0d  |    13!, {0-11}.|
00001010  06 40 19 20 4c 44 4d 49  41 20 20 20 20 31 34 21  |.@. LDMIA    14!|
00001020  2c 20 7b 30 2d 31 31 7d  0d 06 4a 19 20 53 54 4d  |, {0-11}..J. STM|
00001030  49 41 20 20 20 20 31 33  21 2c 20 7b 30 2d 31 31  |IA    13!, {0-11|
00001040  7d 0d 06 54 19 20 4c 44  4d 49 41 20 20 20 20 31  |}..T. LDMIA    1|
00001050  34 21 2c 20 7b 30 2d 31  31 7d 0d 06 5e 19 20 53  |4!, {0-11}..^. S|
00001060  54 4d 49 41 20 20 20 20  31 33 21 2c 20 7b 30 2d  |TMIA    13!, {0-|
00001070  31 31 7d 0d 06 68 19 20  4c 44 4d 49 41 20 20 20  |11}..h. LDMIA   |
00001080  20 31 34 21 2c 20 7b 30  2d 31 31 7d 0d 06 72 19  | 14!, {0-11}..r.|
00001090  20 53 54 4d 49 41 20 20  20 20 31 33 21 2c 20 7b  | STMIA    13!, {|
000010a0  30 2d 31 31 7d 0d 06 7c  19 20 4c 44 4d 49 41 20  |0-11}..|. LDMIA |
000010b0  20 20 20 31 34 21 2c 20  7b 30 2d 31 31 7d 0d 06  |   14!, {0-11}..|
000010c0  86 19 20 53 54 4d 49 41  20 20 20 20 31 33 21 2c  |.. STMIA    13!,|
000010d0  20 7b 30 2d 31 31 7d 0d  06 90 19 20 4c 44 4d 49  | {0-11}.... LDMI|
000010e0  41 20 20 20 20 31 34 21  2c 20 7b 30 2d 31 31 7d  |A    14!, {0-11}|
000010f0  0d 06 9a 19 20 53 54 4d  49 41 20 20 20 20 31 33  |.... STMIA    13|
00001100  21 2c 20 7b 30 2d 31 31  7d 0d 06 a4 22 20 41 44  |!, {0-11}..." AD|
00001110  44 20 20 20 20 20 20 31  33 2c 20 31 33 2c 20 23  |D      13, 13, #|
00001120  68 61 64 64 25 2d 68 70  69 78 25 0d 06 ae 22 20  |hadd%-hpix%..." |
00001130  41 44 44 20 20 20 20 20  20 31 34 2c 20 31 34 2c  |ADD      14, 14,|
00001140  20 23 68 61 64 64 25 2d  68 70 69 78 25 0d 06 b8  | #hadd%-hpix%...|
00001150  18 20 53 55 42 53 20 20  20 20 20 31 32 2c 20 31  |. SUBS     12, 1|
00001160  32 2c 20 23 31 0d 06 c2  1a 20 42 4e 45 20 20 20  |2, #1.... BNE   |
00001170  20 20 20 69 6e 74 65 72  6c 61 63 65 6c 31 25 0d  |   interlacel1%.|
00001180  06 cc 06 20 5d 0d 06 d6  06 20 cd 0d 06 e0 0f 20  |... ].... ..... |
00001190  5b 4f 50 54 20 70 61 73  73 25 0d 06 ea 06 20 3a  |[OPT pass%.... :|
000011a0  0d 06 f4 42 20 53 57 49  20 20 20 20 20 20 22 4f  |...B SWI      "O|
000011b0  53 5f 52 65 61 64 4d 6f  6e 6f 74 6f 6e 69 63 54  |S_ReadMonotonicT|
000011c0  69 6d 65 22 20 20 20 20  20 20 20 20 3b 63 61 6c  |ime"        ;cal|
000011d0  63 75 6c 61 74 65 20 66  72 61 6d 65 20 73 70 65  |culate frame spe|
000011e0  65 64 0d 06 fe 17 20 4c  44 52 20 20 20 20 20 20  |ed.... LDR      |
000011f0  31 2c 20 61 74 69 6d 65  25 0d 07 08 15 20 53 55  |1, atime%.... SU|
00001200  42 20 20 20 20 20 20 30  2c 20 30 2c 20 31 0d 07  |B      0, 0, 1..|
00001210  12 20 20 43 4d 50 20 20  20 20 20 20 30 2c 20 23  |.  CMP      0, #|
00001220  31 30 30 2f 74 61 72 67  65 74 66 70 73 25 0d 07  |100/targetfps%..|
00001230  1c 44 20 53 57 49 47 54  20 20 20 20 32 35 36 2b  |.D SWIGT    256+|
00001240  37 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |7               |
00001250  3b 62 65 65 70 20 69 66  20 69 74 20 66 61 6c 6c  |;beep if it fall|
00001260  73 20 62 65 6c 6f 77 20  74 61 72 67 65 74 20 66  |s below target f|
00001270  70 73 0d 07 26 06 20 3a  0d 07 30 15 20 4d 4f 56  |ps..&. :..0. MOV|
00001280  20 20 20 20 20 20 30 2c  20 23 31 32 39 0d 07 3a  |      0, #129..:|
00001290  13 20 4d 4f 56 20 20 20  20 20 20 31 2c 20 23 30  |. MOV      1, #0|
000012a0  0d 07 44 13 20 4d 4f 56  20 20 20 20 20 20 32 2c  |..D. MOV      2,|
000012b0  20 23 30 0d 07 4e 17 20  53 57 49 20 20 20 20 20  | #0..N. SWI     |
000012c0  20 22 4f 53 5f 42 79 74  65 22 0d 07 58 15 20 43  | "OS_Byte"..X. C|
000012d0  4d 50 20 20 20 20 20 20  32 2c 20 23 26 46 46 0d  |MP      2, #&FF.|
000012e0  07 62 43 20 42 45 51 20  20 20 20 20 20 6e 65 78  |.bC BEQ      nex|
000012f0  74 66 72 61 6d 65 25 20  20 20 20 20 20 20 20 20  |tframe%         |
00001300  20 3b 69 66 20 6e 6f 20  6b 65 79 20 70 72 65 73  | ;if no key pres|
00001310  73 65 64 2c 20 64 6f 20  6e 65 78 74 20 66 72 61  |sed, do next fra|
00001320  6d 65 0d 07 6c 2d 20 4c  44 52 20 20 20 20 20 20  |me..l- LDR      |
00001330  31 33 2c 20 61 73 70 66  72 61 6d 65 25 20 20 20  |13, aspframe%   |
00001340  20 20 20 20 3b 72 65 73  74 6f 72 65 20 73 70 0d  |    ;restore sp.|
00001350  07 76 32 20 4c 44 4d 46  44 20 20 20 20 31 33 21  |.v2 LDMFD    13!|
00001360  2c 20 7b 50 43 7d 20 20  20 20 20 20 20 20 20 20  |, {PC}          |
00001370  20 3b 72 65 74 75 72 6e  20 74 6f 20 42 41 53 49  | ;return to BASI|
00001380  43 0d 07 80 06 20 3a 0d  07 8a 19 20 2e 61 73 63  |C.... :.... .asc|
00001390  72 73 74 25 20 45 51 55  44 20 73 63 72 73 74 25  |rst% EQUD scrst%|
000013a0  0d 07 94 1c 20 2e 61 64  61 74 61 25 20 20 45 51  |.... .adata%  EQ|
000013b0  55 44 20 62 61 6c 6c 64  61 74 61 25 0d 07 9e 26  |UD balldata%...&|
000013c0  20 2e 61 62 61 63 6b 64  61 74 61 25 20 20 20 20  | .abackdata%    |
000013d0  20 20 20 20 45 51 55 44  20 62 61 63 6b 64 61 74  |    EQUD backdat|
000013e0  61 25 0d 07 a8 14 20 2e  61 62 61 6e 6b 25 20 20  |a%.... .abank%  |
000013f0  45 51 55 44 20 31 0d 07  b2 2c 20 2e 61 70 6c 6f  |EQUD 1..., .aplo|
00001400  74 72 65 67 73 25 20 20  20 20 20 20 20 20 45 51  |tregs%        EQ|
00001410  55 44 20 30 3a 45 51 55  44 20 30 3a 45 51 55 44  |UD 0:EQUD 0:EQUD|
00001420  20 30 0d 07 bc 33 20 2e  70 6c 6f 74 25 20 20 20  | 0...3 .plot%   |
00001430  3b 70 6c 6f 74 20 6f 75  72 20 62 61 6c 6c 20 73  |;plot our ball s|
00001440  70 72 69 74 65 20 61 74  20 63 6f 6f 72 64 73 20  |prite at coords |
00001450  72 30 2c 72 31 0d 07 c6  3e 20 20 20 20 20 20 20  |r0,r1...>       |
00001460  20 20 20 3b 77 68 65 72  65 20 30 2c 30 20 69 73  |   ;where 0,0 is|
00001470  20 74 6f 70 20 6c 65 66  74 20 26 20 32 38 37 2c  | top left & 287,|
00001480  31 39 39 20 69 73 20 62  6f 74 74 6f 6d 20 72 69  |199 is bottom ri|
00001490  67 68 74 0d 07 d0 38 20  20 20 20 20 20 20 20 20  |ght...8         |
000014a0  20 3b 4e 42 20 73 70 72  69 74 65 20 4d 55 53 54  | ;NB sprite MUST|
000014b0  20 6c 69 65 20 65 6e 74  69 72 65 6c 79 20 77 69  | lie entirely wi|
000014c0  74 68 69 6e 20 73 63 72  65 65 6e 0d 07 da 1c 20  |thin screen.... |
000014d0  41 44 52 20 20 20 20 20  20 31 31 2c 20 61 70 6c  |ADR      11, apl|
000014e0  6f 74 72 65 67 73 25 0d  07 e4 1c 20 53 54 4d 49  |otregs%.... STMI|
000014f0  41 20 20 20 20 31 31 2c  20 7b 31 32 2c 31 33 2c  |A    11, {12,13,|
00001500  31 34 7d 0d 07 ee 42 20  80 20 20 20 20 20 20 32  |14}...B .      2|
00001510  2c 20 30 2c 20 23 33 20  20 20 20 20 20 20 20 20  |, 0, #3         |
00001520  20 20 20 3b 63 61 6c 63  20 77 68 69 63 68 20 6f  |   ;calc which o|
00001530  66 20 34 20 73 70 72 69  74 65 20 61 6c 69 67 6e  |f 4 sprite align|
00001540  6d 65 6e 74 73 0d 07 f8  46 20 41 44 44 20 20 20  |ments...F ADD   |
00001550  20 20 20 33 2c 20 32 2c  20 32 2c 20 41 53 4c 20  |   3, 2, 2, ASL |
00001560  23 32 20 20 20 20 20 3b  77 65 20 6e 65 65 64 20  |#2     ;we need |
00001570  76 69 61 20 28 78 41 4e  44 33 29 2a 32 30 2a 32  |via (xAND3)*20*2|
00001580  2a 31 36 20 2b 20 64 61  74 61 25 0d 08 02 3c 20  |*16 + data%...< |
00001590  42 49 43 20 20 20 20 20  20 30 2c 20 30 2c 20 23  |BIC      0, 0, #|
000015a0  33 20 20 20 20 20 20 20  20 20 20 20 20 3b 72 6f  |3            ;ro|
000015b0  75 6e 64 20 78 20 64 6f  77 6e 20 74 6f 20 6d 75  |und x down to mu|
000015c0  6c 74 20 6f 66 20 33 0d  08 0c 1d 20 41 44 44 20  |lt of 3.... ADD |
000015d0  20 20 20 20 20 31 2c 20  31 2c 20 31 2c 20 41 53  |     1, 1, 1, AS|
000015e0  4c 20 23 33 0d 08 16 18  20 4c 44 52 20 20 20 20  |L #3.... LDR    |
000015f0  20 20 32 2c 20 61 73 63  72 73 74 25 0d 08 20 22  |  2, ascrst%.. "|
00001600  20 41 44 44 20 20 20 20  20 20 32 2c 20 32 2c 20  | ADD      2, 2, |
00001610  31 2c 20 41 53 4c 20 23  6c 68 61 64 64 25 0d 08  |1, ASL #lhadd%..|
00001620  2a 42 20 41 44 44 20 20  20 20 20 20 30 2c 20 32  |*B ADD      0, 2|
00001630  2c 20 30 20 20 20 20 20  20 20 20 20 20 20 20 20  |, 0             |
00001640  3b 63 61 6c 63 20 28 73  63 72 65 65 6e 20 70 74  |;calc (screen pt|
00001650  72 20 2b 20 68 61 64 64  25 2a 79 20 2b 20 78 29  |r + hadd%*y + x)|
00001660  0d 08 34 17 20 4c 44 52  20 20 20 20 20 20 31 2c  |..4. LDR      1,|
00001670  20 61 64 61 74 61 25 0d  08 3e 45 20 41 44 44 20  | adata%..>E ADD |
00001680  20 20 20 20 20 31 2c 20  31 2c 20 33 2c 20 41 53  |     1, 1, 3, AS|
00001690  4c 20 23 37 20 20 20 20  20 3b 66 69 6e 61 6c 6c  |L #7     ;finall|
000016a0  79 20 63 61 6c 63 20 28  78 41 4e 44 33 29 2a 32  |y calc (xAND3)*2|
000016b0  30 2a 32 2a 31 36 2b 64  61 74 61 25 0d 08 48 13  |0*2*16+data%..H.|
000016c0  20 4d 4f 56 20 20 20 20  20 20 32 2c 20 23 34 0d  | MOV      2, #4.|
000016d0  08 52 1a 20 41 44 44 20  20 20 20 20 20 33 2c 20  |.R. ADD      3, |
000016e0  31 2c 20 23 32 30 2a 31  36 0d 08 5c 32 20 2e 6c  |1, #20*16..\2 .l|
000016f0  6f 6f 70 31 25 20 20 20  20 20 20 20 20 20 20 20  |oop1%           |
00001700  20 20 20 20 20 20 20 20  20 20 20 3b 6e 6f 77 20  |           ;now |
00001710  70 6c 6f 74 20 73 70 72  69 74 65 0d 08 66 2e 20  |plot sprite..f. |
00001720  a4 70 6c 6f 74 66 72 61  67 28 70 61 73 73 25 29  |.plotfrag(pass%)|
00001730  20 20 20 20 20 20 20 20  20 20 20 20 3b 70 6c 6f  |            ;plo|
00001740  74 20 31 73 74 20 72 6f  77 0d 08 70 44 20 41 44  |t 1st row..pD AD|
00001750  44 20 20 20 20 20 20 30  2c 20 30 2c 20 23 68 61  |D      0, 0, #ha|
00001760  64 64 25 2d 32 30 20 20  20 20 20 3b 6d 6f 76 65  |dd%-20     ;move|
00001770  20 73 63 72 65 65 6e 20  70 74 72 20 74 6f 20 73  | screen ptr to s|
00001780  74 61 72 74 20 6e 65 78  74 20 72 6f 77 0d 08 7a  |tart next row..z|
00001790  15 20 a4 70 6c 6f 74 66  72 61 67 28 70 61 73 73  |. .plotfrag(pass|
000017a0  25 29 0d 08 84 1d 20 41  44 44 20 20 20 20 20 20  |%).... ADD      |
000017b0  30 2c 20 30 2c 20 23 68  61 64 64 25 2d 32 30 0d  |0, 0, #hadd%-20.|
000017c0  08 8e 15 20 a4 70 6c 6f  74 66 72 61 67 28 70 61  |... .plotfrag(pa|
000017d0  73 73 25 29 0d 08 98 1d  20 41 44 44 20 20 20 20  |ss%).... ADD    |
000017e0  20 20 30 2c 20 30 2c 20  23 68 61 64 64 25 2d 32  |  0, 0, #hadd%-2|
000017f0  30 0d 08 a2 2e 20 a4 70  6c 6f 74 66 72 61 67 28  |0.... .plotfrag(|
00001800  70 61 73 73 25 29 20 20  20 20 20 20 20 20 20 20  |pass%)          |
00001810  20 20 3b 70 6c 6f 74 20  34 74 68 20 72 6f 77 0d  |  ;plot 4th row.|
00001820  08 ac 1d 20 41 44 44 20  20 20 20 20 20 30 2c 20  |... ADD      0, |
00001830  30 2c 20 23 68 61 64 64  25 2d 32 30 0d 08 b6 16  |0, #hadd%-20....|
00001840  20 53 55 42 53 20 20 20  20 20 32 2c 20 32 2c 20  | SUBS     2, 2, |
00001850  23 31 0d 08 c0 45 20 42  4e 45 20 20 20 20 20 20  |#1...E BNE      |
00001860  6c 6f 6f 70 31 25 20 20  20 20 20 20 20 20 20 20  |loop1%          |
00001870  3b 72 65 70 65 61 74 20  61 62 6f 76 65 20 34 20  |;repeat above 4 |
00001880  74 69 6d 65 73 20 74 6f  20 64 6f 20 61 6c 6c 20  |times to do all |
00001890  31 36 20 72 6f 77 73 0d  08 ca 44 20 41 44 52 20  |16 rows...D ADR |
000018a0  20 20 20 20 20 31 31 2c  20 61 70 6c 6f 74 72 65  |     11, aplotre|
000018b0  67 73 25 20 20 20 20 20  20 3b 70 6c 6f 74 20 63  |gs%      ;plot c|
000018c0  6f 6d 70 6c 65 74 65 64  20 2d 20 72 65 74 75 72  |ompleted - retur|
000018d0  6e 20 74 6f 20 63 61 6c  6c 65 72 0d 08 d4 38 20  |n to caller...8 |
000018e0  4c 44 4d 49 41 20 20 20  20 31 31 2c 20 7b 31 32  |LDMIA    11, {12|
000018f0  2c 31 33 2c 50 43 7d 20  20 20 20 20 20 3b 70 72  |,13,PC}      ;pr|
00001900  65 73 65 72 76 69 6e 67  20 72 31 32 20 26 20 72  |eserving r12 & r|
00001910  31 33 2e 0d 08 de 06 20  3a 0d 08 e8 2f 20 2e 61  |13..... :.../ .a|
00001920  63 6f 6c 6c 72 65 67 73  25 20 20 20 20 45 51 55  |collregs%    EQU|
00001930  44 20 30 3a 45 51 55 44  20 30 3a 45 51 55 44 20  |D 0:EQUD 0:EQUD |
00001940  30 3a 45 51 55 44 20 30  0d 08 f2 2f 20 20 20 20  |0:EQUD 0.../    |
00001950  20 20 20 20 20 20 20 20  20 20 20 20 45 51 55 44  |            EQUD|
00001960  20 30 3a 45 51 55 44 20  30 3a 45 51 55 44 20 30  | 0:EQUD 0:EQUD 0|
00001970  3a 45 51 55 44 20 30 0d  08 fc 34 20 2e 6d 6f 76  |:EQUD 0...4 .mov|
00001980  65 6e 63 68 65 63 6b 25  20 20 20 20 20 3b 6d 6f  |encheck%     ;mo|
00001990  76 65 20 74 68 65 6e 20  63 6f 6c 6c 69 73 69 6f  |ve then collisio|
000019a0  6e 20 63 68 65 63 6b 20  6f 75 72 0d 09 06 32 20  |n check our...2 |
000019b0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
000019c0  20 3b 62 61 6c 6c 20 73  70 72 69 74 65 20 61 74  | ;ball sprite at|
000019d0  20 63 6f 6f 72 64 73 20  72 30 2c 72 31 0d 09 10  | coords r0,r1...|
000019e0  46 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |F               |
000019f0  20 20 20 3b 77 68 65 72  65 20 30 2c 30 20 69 73  |   ;where 0,0 is|
00001a00  20 74 6f 70 20 6c 65 66  74 20 26 20 32 38 37 2c  | top left & 287,|
00001a10  31 39 39 20 69 73 20 62  6f 74 74 6f 6d 20 72 69  |199 is bottom ri|
00001a20  67 68 74 0d 09 1a 40 20  20 20 20 20 20 20 20 20  |ght...@         |
00001a30  20 20 20 20 20 20 20 20  20 3b 4e 42 20 73 70 72  |         ;NB spr|
00001a40  69 74 65 20 4d 55 53 54  20 6c 69 65 20 65 6e 74  |ite MUST lie ent|
00001a50  69 72 65 6c 79 20 77 69  74 68 69 6e 20 73 63 72  |irely within scr|
00001a60  65 65 6e 0d 09 24 1c 20  41 44 52 20 20 20 20 20  |een..$. ADR     |
00001a70  20 31 31 2c 20 61 63 6f  6c 6c 72 65 67 73 25 0d  | 11, acollregs%.|
00001a80  09 2e 15 20 41 44 44 20  20 20 20 20 20 30 2c 20  |... ADD      0, |
00001a90  30 2c 20 32 0d 09 38 15  20 41 44 44 20 20 20 20  |0, 2..8. ADD    |
00001aa0  20 20 31 2c 20 31 2c 20  33 0d 09 42 20 20 53 54  |  1, 1, 3..B  ST|
00001ab0  4d 49 41 20 20 20 20 31  31 2c 20 7b 30 2d 34 2c  |MIA    11, {0-4,|
00001ac0  31 32 2c 31 33 2c 31 34  7d 0d 09 4c 1a 20 4d 4f  |12,13,14}..L. MO|
00001ad0  56 20 20 20 20 20 20 30  2c 20 30 2c 20 41 53 52  |V      0, 0, ASR|
00001ae0  20 23 38 0d 09 56 1a 20  4d 4f 56 20 20 20 20 20  | #8..V. MOV     |
00001af0  20 31 2c 20 31 2c 20 41  53 52 20 23 38 0d 09 60  | 1, 1, ASR #8..`|
00001b00  42 20 80 20 20 20 20 20  20 32 2c 20 30 2c 20 23  |B .      2, 0, #|
00001b10  33 20 20 20 20 20 20 20  20 20 20 20 20 3b 63 61  |3            ;ca|
00001b20  6c 63 20 77 68 69 63 68  20 6f 66 20 34 20 73 70  |lc which of 4 sp|
00001b30  72 69 74 65 20 61 6c 69  67 6e 6d 65 6e 74 73 0d  |rite alignments.|
00001b40  09 6a 46 20 41 44 44 20  20 20 20 20 20 33 2c 20  |.jF ADD      3, |
00001b50  32 2c 20 32 2c 20 41 53  4c 20 23 32 20 20 20 20  |2, 2, ASL #2    |
00001b60  20 3b 77 65 20 6e 65 65  64 20 76 69 61 20 28 78  | ;we need via (x|
00001b70  41 4e 44 33 29 2a 32 30  2a 32 2a 31 36 20 2b 20  |AND3)*20*2*16 + |
00001b80  64 61 74 61 25 0d 09 74  3c 20 42 49 43 20 20 20  |data%..t< BIC   |
00001b90  20 20 20 30 2c 20 30 2c  20 23 33 20 20 20 20 20  |   0, 0, #3     |
00001ba0  20 20 20 20 20 20 20 3b  72 6f 75 6e 64 20 78 20  |       ;round x |
00001bb0  64 6f 77 6e 20 74 6f 20  6d 75 6c 74 20 6f 66 20  |down to mult of |
00001bc0  33 0d 09 7e 1d 20 41 44  44 20 20 20 20 20 20 31  |3..~. ADD      1|
00001bd0  2c 20 31 2c 20 31 2c 20  41 53 4c 20 23 33 0d 09  |, 1, 1, ASL #3..|
00001be0  88 18 20 4c 44 52 20 20  20 20 20 20 32 2c 20 61  |.. LDR      2, a|
00001bf0  73 63 72 73 74 25 0d 09  92 22 20 41 44 44 20 20  |scrst%..." ADD  |
00001c00  20 20 20 20 32 2c 20 32  2c 20 31 2c 20 41 53 4c  |    2, 2, 1, ASL|
00001c10  20 23 6c 68 61 64 64 25  0d 09 9c 42 20 41 44 44  | #lhadd%...B ADD|
00001c20  20 20 20 20 20 20 30 2c  20 32 2c 20 30 20 20 20  |      0, 2, 0   |
00001c30  20 20 20 20 20 20 20 20  20 20 3b 63 61 6c 63 20  |          ;calc |
00001c40  28 73 63 72 65 65 6e 20  70 74 72 20 2b 20 68 61  |(screen ptr + ha|
00001c50  64 64 25 2a 79 20 2b 20  78 29 0d 09 a6 17 20 4c  |dd%*y + x).... L|
00001c60  44 52 20 20 20 20 20 20  31 2c 20 61 64 61 74 61  |DR      1, adata|
00001c70  25 0d 09 b0 45 20 41 44  44 20 20 20 20 20 20 31  |%...E ADD      1|
00001c80  2c 20 31 2c 20 33 2c 20  41 53 4c 20 23 37 20 20  |, 1, 3, ASL #7  |
00001c90  20 20 20 3b 66 69 6e 61  6c 6c 79 20 63 61 6c 63  |   ;finally calc|
00001ca0  20 28 78 41 4e 44 33 29  2a 32 30 2a 32 2a 31 36  | (xAND3)*20*2*16|
00001cb0  2b 64 61 74 61 25 0d 09  ba 1a 20 41 44 44 20 20  |+data%.... ADD  |
00001cc0  20 20 20 20 31 2c 20 31  2c 20 23 32 30 2a 31 36  |    1, 1, #20*16|
00001cd0  0d 09 c4 45 20 41 44 52  20 20 20 20 20 20 32 2c  |...E ADR      2,|
00001ce0  20 63 6f 6c 6c 61 64 64  72 62 75 66 25 20 20 20  | colladdrbuf%   |
00001cf0  20 20 3b 73 74 6f 72 65  20 73 63 72 65 65 6e 20  |  ;store screen |
00001d00  61 6e 64 20 73 70 72 69  74 65 20 64 61 74 61 20  |and sprite data |
00001d10  61 64 64 72 73 0d 09 ce  44 20 53 54 4d 49 41 20  |addrs...D STMIA |
00001d20  20 20 20 32 2c 20 7b 30  2c 31 7d 20 20 20 20 20  |   2, {0,1}     |
00001d30  20 20 20 20 20 20 20 3b  63 6f 72 72 65 73 70 6f  |       ;correspo|
00001d40  6e 64 69 6e 67 20 74 6f  20 74 6f 70 20 6c 65 66  |nding to top lef|
00001d50  74 20 6f 66 20 62 61 6c  6c 0d 09 d8 13 20 4d 4f  |t of ball.... MO|
00001d60  56 20 20 20 20 20 20 32  2c 20 23 34 0d 09 e2 33  |V      2, #4...3|
00001d70  20 2e 63 6f 6c 6c 6c 6f  6f 70 31 25 20 20 20 20  | .collloop1%    |
00001d80  20 20 20 20 20 20 20 20  20 20 20 20 20 20 3b 6e  |              ;n|
00001d90  6f 77 20 63 68 65 63 6b  20 73 70 72 69 74 65 0d  |ow check sprite.|
00001da0  09 ec 44 20 a4 63 6f 6c  6c 66 72 61 67 28 70 61  |..D .collfrag(pa|
00001db0  73 73 25 29 20 20 20 20  20 20 20 20 20 20 20 20  |ss%)            |
00001dc0  3b 63 68 65 63 6b 20 31  73 74 20 72 6f 77 20 28  |;check 1st row (|
00001dd0  69 66 20 63 6f 6c 6c 20  42 20 67 6f 74 63 6f 6c  |if coll B gotcol|
00001de0  6c 25 29 0d 09 f6 44 20  41 44 44 20 20 20 20 20  |l%)...D ADD     |
00001df0  20 30 2c 20 30 2c 20 23  68 61 64 64 25 2d 32 30  | 0, 0, #hadd%-20|
00001e00  20 20 20 20 20 3b 6d 6f  76 65 20 73 63 72 65 65  |     ;move scree|
00001e10  6e 20 70 74 72 20 74 6f  20 73 74 61 72 74 20 6e  |n ptr to start n|
00001e20  65 78 74 20 72 6f 77 0d  0a 00 15 20 a4 63 6f 6c  |ext row.... .col|
00001e30  6c 66 72 61 67 28 70 61  73 73 25 29 0d 0a 0a 1d  |lfrag(pass%)....|
00001e40  20 41 44 44 20 20 20 20  20 20 30 2c 20 30 2c 20  | ADD      0, 0, |
00001e50  23 68 61 64 64 25 2d 32  30 0d 0a 14 15 20 a4 63  |#hadd%-20.... .c|
00001e60  6f 6c 6c 66 72 61 67 28  70 61 73 73 25 29 0d 0a  |ollfrag(pass%)..|
00001e70  1e 1d 20 41 44 44 20 20  20 20 20 20 30 2c 20 30  |.. ADD      0, 0|
00001e80  2c 20 23 68 61 64 64 25  2d 32 30 0d 0a 28 2f 20  |, #hadd%-20..(/ |
00001e90  a4 63 6f 6c 6c 66 72 61  67 28 70 61 73 73 25 29  |.collfrag(pass%)|
00001ea0  20 20 20 20 20 20 20 20  20 20 20 20 3b 63 68 65  |            ;che|
00001eb0  63 6b 20 34 74 68 20 72  6f 77 0d 0a 32 1d 20 41  |ck 4th row..2. A|
00001ec0  44 44 20 20 20 20 20 20  30 2c 20 30 2c 20 23 68  |DD      0, 0, #h|
00001ed0  61 64 64 25 2d 32 30 0d  0a 3c 16 20 53 55 42 53  |add%-20..<. SUBS|
00001ee0  20 20 20 20 20 32 2c 20  32 2c 20 23 31 0d 0a 46  |     2, 2, #1..F|
00001ef0  45 20 42 4e 45 20 20 20  20 20 20 63 6f 6c 6c 6c  |E BNE      colll|
00001f00  6f 6f 70 31 25 20 20 20  20 20 20 3b 72 65 70 65  |oop1%      ;repe|
00001f10  61 74 20 61 62 6f 76 65  20 34 20 74 69 6d 65 73  |at above 4 times|
00001f20  20 74 6f 20 64 6f 20 61  6c 6c 20 31 36 20 72 6f  | to do all 16 ro|
00001f30  77 73 0d 0a 50 1c 20 41  44 52 20 20 20 20 20 20  |ws..P. ADR      |
00001f40  31 31 2c 20 61 63 6f 6c  6c 72 65 67 73 25 0d 0a  |11, acollregs%..|
00001f50  5a 20 20 4c 44 4d 49 41  20 20 20 20 31 31 2c 20  |Z  LDMIA    11, |
00001f60  7b 30 2d 34 2c 31 32 2c  31 33 2c 31 34 7d 0d 0a  |{0-4,12,13,14}..|
00001f70  64 3d 20 41 44 44 20 20  20 20 20 20 33 2c 20 33  |d= ADD      3, 3|
00001f80  2c 20 23 38 20 20 20 20  20 20 20 20 20 20 20 20  |, #8            |
00001f90  3b 20 61 63 63 65 6c 65  72 61 74 65 20 62 61 6c  |; accelerate bal|
00001fa0  6c 20 64 6f 77 6e 77 61  72 64 73 0d 0a 6e 13 20  |l downwards..n. |
00001fb0  4d 4f 56 20 20 20 20 20  20 34 2c 20 23 30 0d 0a  |MOV      4, #0..|
00001fc0  78 14 20 4d 4f 56 20 20  20 20 20 20 50 43 2c 20  |x. MOV      PC, |
00001fd0  31 34 0d 0a 82 25 20 2e  63 6f 6c 6c 61 64 64 72  |14...% .colladdr|
00001fe0  62 75 66 25 20 20 20 20  20 20 45 51 55 44 20 30  |buf%      EQUD 0|
00001ff0  3a 45 51 55 44 20 30 0d  0a 8c 0e 20 2e 67 6f 74  |:EQUD 0.... .got|
00002000  63 6f 6c 6c 25 0d 0a 96  1c 20 41 44 52 20 20 20  |coll%.... ADR   |
00002010  20 20 20 31 31 2c 20 61  63 6f 6c 6c 72 65 67 73  |   11, acollregs|
00002020  25 0d 0a a0 17 20 4c 44  4d 49 41 20 20 20 20 31  |%.... LDMIA    1|
00002030  31 2c 20 7b 30 2d 33 7d  0d 0a aa 43 20 53 55 42  |1, {0-3}...C SUB|
00002040  20 20 20 20 20 20 30 2c  20 30 2c 20 32 20 20 20  |      0, 0, 2   |
00002050  20 20 20 20 20 20 20 20  20 20 3b 72 65 73 65 74  |          ;reset|
00002060  20 70 6f 73 69 74 69 6f  6e 2c 20 6d 6f 76 69 6e  | position, movin|
00002070  67 20 69 74 20 6f 75 74  20 6f 66 0d 0a b4 2c 20  |g it out of..., |
00002080  53 55 42 20 20 20 20 20  20 31 2c 20 31 2c 20 33  |SUB      1, 1, 3|
00002090  20 20 20 20 20 20 20 20  20 20 20 20 20 3b 63 6f  |             ;co|
000020a0  6c 6c 69 73 69 6f 6e 0d  0a be 17 20 53 54 4d 49  |llision.... STMI|
000020b0  41 20 20 20 20 31 31 2c  20 7b 30 2c 31 7d 0d 0a  |A    11, {0,1}..|
000020c0  c8 39 20 4d 4f 56 20 20  20 20 20 20 36 2c 20 23  |.9 MOV      6, #|
000020d0  30 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |0               |
000020e0  3b 69 6e 20 6d 79 20 6c  69 6e 20 72 65 67 20 6e  |;in my lin reg n|
000020f0  6f 74 65 73 2c 20 6e 0d  0a d2 39 20 4d 4f 56 20  |otes, n...9 MOV |
00002100  20 20 20 20 20 37 2c 20  23 30 20 20 20 20 20 20  |     7, #0      |
00002110  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00002120  20 20 20 20 20 20 20 20  20 20 20 20 20 3b 20 75  |             ; u|
00002130  0d 0a dc 39 20 4d 4f 56  20 20 20 20 20 20 38 2c  |...9 MOV      8,|
00002140  20 23 30 20 20 20 20 20  20 20 20 20 20 20 20 20  | #0             |
00002150  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00002160  20 20 20 20 20 20 3b 20  76 0d 0a e6 39 20 4d 4f  |      ; v...9 MO|
00002170  56 20 20 20 20 20 20 39  2c 20 23 30 20 20 20 20  |V      9, #0    |
00002180  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
00002190  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 3b  |               ;|
000021a0  20 70 0d 0a f0 39 20 4d  4f 56 20 20 20 20 20 20  | p...9 MOV      |
000021b0  31 30 2c 20 23 30 20 20  20 20 20 20 20 20 20 20  |10, #0          |
000021c0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
000021d0  20 20 20 20 20 20 20 20  3b 20 71 0d 0a fa 1d 20  |        ; q.... |
000021e0  41 44 52 20 20 20 20 20  20 32 2c 20 63 6f 6c 6c  |ADR      2, coll|
000021f0  61 64 64 72 62 75 66 25  0d 0b 04 43 20 4c 44 4d  |addrbuf%...C LDM|
00002200  49 41 20 20 20 20 32 2c  20 7b 30 2c 31 7d 20 20  |IA    2, {0,1}  |
00002210  20 20 20 20 20 20 20 20  20 20 3b 72 65 63 61 6c  |          ;recal|
00002220  6c 20 73 63 72 65 65 6e  2f 64 61 74 61 20 61 64  |l screen/data ad|
00002230  64 72 73 20 66 6f 72 20  74 6f 70 0d 0b 0e 31 20  |drs for top...1 |
00002240  4d 4f 56 20 20 20 20 20  20 33 2c 20 23 30 20 20  |MOV      3, #0  |
00002250  20 20 20 3b 72 6f 77 20  30 20 20 20 20 3b 6c 65  |   ;row 0    ;le|
00002260  66 74 20 6f 66 20 73 70  72 69 74 65 0d 0b 18 10  |ft of sprite....|
00002270  20 2e 73 74 61 74 6c 6f  6f 70 31 25 0d 0b 22 1e  | .statloop1%..".|
00002280  20 4d 4f 56 20 20 20 20  20 20 32 2c 20 23 30 20  | MOV      2, #0 |
00002290  20 20 20 20 3b 63 6f 6c  20 30 0d 0b 2c 10 20 2e  |    ;col 0..,. .|
000022a0  73 74 61 74 6c 6f 6f 70  32 25 0d 0b 36 46 20 4c  |statloop2%..6F L|
000022b0  44 52 20 20 20 20 20 20  34 2c 20 5b 30 5d 2c 20  |DR      4, [0], |
000022c0  23 34 20 20 20 20 20 20  20 20 20 20 3b 72 65 73  |#4          ;res|
000022d0  63 61 6e 20 65 61 63 68  20 70 69 78 65 6c 20 69  |can each pixel i|
000022e0  6e 20 63 6f 6c 6c 69 73  69 6f 6e 20 61 72 65 61  |n collision area|
000022f0  0d 0b 40 46 20 4c 44 52  20 20 20 20 20 20 35 2c  |..@F LDR      5,|
00002300  20 5b 31 5d 2c 20 23 34  20 20 20 20 20 20 20 20  | [1], #4        |
00002310  20 20 3b 61 6e 64 20 66  6f 72 20 65 61 63 68 20  |  ;and for each |
00002320  63 6f 6c 6c 69 64 65 64  20 70 69 78 65 6c 20 61  |collided pixel a|
00002330  64 64 20 69 74 73 0d 0b  4a 44 20 80 20 20 20 20  |dd its..JD .    |
00002340  20 20 34 2c 20 34 2c 20  35 20 20 20 20 20 20 20  |  4, 4, 5       |
00002350  20 20 20 20 20 20 3b 63  6f 6f 72 64 73 20 28 72  |      ;coords (r|
00002360  65 6c 61 74 69 76 65 20  74 6f 20 74 6f 70 6c 65  |elative to tople|
00002370  66 74 20 73 70 72 69 74  65 29 0d 0b 54 40 20 a4  |ft sprite)..T@ .|
00002380  73 74 61 74 66 72 61 67  28 70 61 73 73 25 2c 20  |statfrag(pass%, |
00002390  32 35 35 29 20 20 20 20  20 20 20 3b 6f 6e 74 6f  |255)       ;onto|
000023a0  20 74 68 65 20 72 65 67  72 65 73 73 69 6f 6e 20  | the regression |
000023b0  73 74 61 74 69 73 74 69  63 73 0d 0b 5e 16 20 41  |statistics..^. A|
000023c0  44 44 20 20 20 20 20 20  32 2c 20 32 2c 20 23 31  |DD      2, 2, #1|
000023d0  0d 0b 68 1d 20 a4 73 74  61 74 66 72 61 67 28 70  |..h. .statfrag(p|
000023e0  61 73 73 25 2c 20 32 35  35 3c 3c 38 29 0d 0b 72  |ass%, 255<<8)..r|
000023f0  16 20 41 44 44 20 20 20  20 20 20 32 2c 20 32 2c  |. ADD      2, 2,|
00002400  20 23 31 0d 0b 7c 1e 20  a4 73 74 61 74 66 72 61  | #1..|. .statfra|
00002410  67 28 70 61 73 73 25 2c  20 32 35 35 3c 3c 31 36  |g(pass%, 255<<16|
00002420  29 0d 0b 86 16 20 41 44  44 20 20 20 20 20 20 32  |).... ADD      2|
00002430  2c 20 32 2c 20 23 31 0d  0b 90 1e 20 a4 73 74 61  |, 2, #1.... .sta|
00002440  74 66 72 61 67 28 70 61  73 73 25 2c 20 32 35 35  |tfrag(pass%, 255|
00002450  3c 3c 32 34 29 0d 0b 9a  16 20 41 44 44 20 20 20  |<<24).... ADD   |
00002460  20 20 20 32 2c 20 32 2c  20 23 31 0d 0b a4 14 20  |   2, 2, #1.... |
00002470  43 4d 50 20 20 20 20 20  20 32 2c 20 23 32 30 0d  |CMP      2, #20.|
00002480  0b ae 18 20 42 4c 54 20  20 20 20 20 20 73 74 61  |... BLT      sta|
00002490  74 6c 6f 6f 70 32 25 0d  0b b8 1d 20 41 44 44 20  |tloop2%.... ADD |
000024a0  20 20 20 20 20 30 2c 20  30 2c 20 23 68 61 64 64  |     0, 0, #hadd|
000024b0  25 2d 32 30 0d 0b c2 16  20 41 44 44 20 20 20 20  |%-20.... ADD    |
000024c0  20 20 33 2c 20 33 2c 20  23 31 0d 0b cc 14 20 43  |  3, 3, #1.... C|
000024d0  4d 50 20 20 20 20 20 20  33 2c 20 23 31 36 0d 0b  |MP      3, #16..|
000024e0  d6 3f 20 42 4c 54 20 20  20 20 20 20 73 74 61 74  |.? BLT      stat|
000024f0  6c 6f 6f 70 31 25 20 20  20 20 20 20 20 20 20 20  |loop1%          |
00002500  3b 77 68 65 6e 20 64 6f  6e 65 2c 20 6e 2c 20 75  |;when done, n, u|
00002510  20 26 20 76 20 63 6f 6d  70 75 74 65 64 0d 0b e0  | & v computed...|
00002520  15 20 4d 55 4c 20 20 20  20 20 20 39 2c 20 36 2c  |. MUL      9, 6,|
00002530  20 39 0d 0b ea 15 20 41  44 44 20 20 20 20 20 20  | 9.... ADD      |
00002540  35 2c 20 37 2c 20 38 0d  0b f4 16 20 53 55 42 20  |5, 7, 8.... SUB |
00002550  20 20 20 20 20 31 34 2c  20 37 2c 20 38 0d 0b fe  |     14, 7, 8...|
00002560  2d 20 4d 4c 41 20 20 20  20 20 20 39 2c 20 35 2c  |- MLA      9, 5,|
00002570  20 31 34 2c 20 39 20 20  20 20 20 20 20 20 20 3b  | 14, 9         ;|
00002580  70 20 63 6f 6d 70 75 74  65 64 0d 0c 08 17 20 4d  |p computed.... M|
00002590  55 4c 20 20 20 20 20 20  31 30 2c 20 36 2c 20 31  |UL      10, 6, 1|
000025a0  30 0d 0c 12 16 20 4d 55  4c 20 20 20 20 20 20 31  |0.... MUL      1|
000025b0  34 2c 20 37 2c 20 38 0d  0c 1c 18 20 53 55 42 20  |4, 7, 8.... SUB |
000025c0  20 20 20 20 20 31 30 2c  20 31 30 2c 20 31 34 0d  |     10, 10, 14.|
000025d0  0c 26 2d 20 41 44 44 20  20 20 20 20 20 31 30 2c  |.&- ADD      10,|
000025e0  20 31 30 2c 20 31 30 20  20 20 20 20 20 20 20 20  | 10, 10         |
000025f0  20 3b 71 20 63 6f 6d 70  75 74 65 64 0d 0c 30 12  | ;q computed..0.|
00002600  20 4d 4f 56 53 20 20 20  20 20 36 2c 20 39 0d 0c  | MOVS     6, 9..|
00002610  3a 2d 20 52 53 42 4d 49  20 20 20 20 36 2c 20 36  |:- RSBMI    6, 6|
00002620  2c 20 23 30 20 20 20 20  20 20 20 20 20 20 20 20  |, #0            |
00002630  3b 61 70 20 3d 20 61 62  73 20 70 0d 0c 44 13 20  |;ap = abs p..D. |
00002640  4d 4f 56 53 20 20 20 20  20 37 2c 20 31 30 0d 0c  |MOVS     7, 10..|
00002650  4e 2d 20 52 53 42 4d 49  20 20 20 20 37 2c 20 37  |N- RSBMI    7, 7|
00002660  2c 20 23 30 20 20 20 20  20 20 20 20 20 20 20 20  |, #0            |
00002670  3b 61 71 20 3d 20 61 62  73 20 71 0d 0c 58 12 20  |;aq = abs q..X. |
00002680  43 4d 50 20 20 20 20 20  20 36 2c 20 37 0d 0c 62  |CMP      6, 7..b|
00002690  12 20 4d 4f 56 20 20 20  20 20 20 38 2c 20 36 0d  |. MOV      8, 6.|
000026a0  0c 6c 33 20 4d 4f 56 4c  54 20 20 20 20 38 2c 20  |.l3 MOVLT    8, |
000026b0  37 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |7               |
000026c0  20 3b 20 6d 20 3d 20 6d  61 78 20 7b 61 70 2c 61  | ; m = max {ap,a|
000026d0  71 7d 0d 0c 76 3f 20 43  4d 50 20 20 20 20 20 20  |q}..v? CMP      |
000026e0  38 2c 20 23 30 20 20 20  20 20 20 20 20 20 20 20  |8, #0           |
000026f0  20 20 20 20 3b 69 66 20  68 61 76 65 20 64 65 67  |    ;if have deg|
00002700  65 6e 65 72 61 74 65 20  63 6f 6c 6c 69 73 69 6f  |enerate collisio|
00002710  6e 0d 0c 80 45 20 42 45  51 20 20 20 20 20 20 70  |n...E BEQ      p|
00002720  61 74 63 68 31 25 20 20  20 20 20 20 20 20 20 20  |atch1%          |
00002730  20 20 20 3b 28 65 67 20  77 69 74 68 20 73 69 6e  |   ;(eg with sin|
00002740  67 6c 65 20 70 69 78 65  6c 29 2c 20 63 61 6e 27  |gle pixel), can'|
00002750  74 20 63 61 6c 63 0d 0c  8a 45 20 2e 73 74 61 74  |t calc...E .stat|
00002760  6c 6f 6f 70 33 25 20 20  20 20 20 20 20 20 20 20  |loop3%          |
00002770  20 20 20 20 20 20 20 20  3b 61 20 6c 69 6e 65 61  |        ;a linea|
00002780  72 20 72 65 67 72 65 73  73 69 6f 6e 2c 20 73 6f  |r regression, so|
00002790  20 67 6f 20 70 61 74 63  68 31 25 0d 0c 94 44 20  | go patch1%...D |
000027a0  43 4d 50 20 20 20 20 20  20 38 2c 20 23 31 3c 3c  |CMP      8, #1<<|
000027b0  31 32 20 20 20 20 20 20  20 20 20 20 20 3b 77 68  |12           ;wh|
000027c0  69 63 68 20 73 69 6d 70  6c 79 20 72 65 76 65 72  |ich simply rever|
000027d0  73 65 73 20 76 65 6c 6f  63 69 74 69 65 73 21 0d  |ses velocities!.|
000027e0  0c 9e 1a 20 4d 4f 56 47  45 20 20 20 20 38 2c 20  |... MOVGE    8, |
000027f0  38 2c 20 41 53 52 20 23  31 0d 0c a8 46 20 4d 4f  |8, ASR #1...F MO|
00002800  56 47 45 20 20 20 20 36  2c 20 36 2c 20 41 53 52  |VGE    6, 6, ASR|
00002810  20 23 31 20 20 20 20 20  20 20 20 3b 70 72 6f 70  | #1        ;prop|
00002820  6f 72 74 69 6f 6e 61 74  65 6c 79 20 72 65 64 75  |ortionately redu|
00002830  63 65 20 61 70 20 61 6e  64 20 61 71 20 69 6e 0d  |ce ap and aq in.|
00002840  0c b2 46 20 4d 4f 56 47  45 20 20 20 20 37 2c 20  |..F MOVGE    7, |
00002850  37 2c 20 41 53 52 20 23  31 20 20 20 20 20 20 20  |7, ASR #1       |
00002860  20 3b 6d 61 67 6e 69 74  75 64 65 2c 20 75 6e 74  | ;magnitude, unt|
00002870  69 6c 20 69 6e 20 6e 65  63 65 73 73 61 72 79 20  |il in necessary |
00002880  72 61 6e 67 65 0d 0c bc  18 20 42 47 45 20 20 20  |range.... BGE   |
00002890  20 20 20 73 74 61 74 6c  6f 6f 70 33 25 0d 0c c6  |   statloop3%...|
000028a0  34 20 4d 55 4c 20 20 20  20 20 20 31 31 2c 20 36  |4 MUL      11, 6|
000028b0  2c 20 36 20 20 20 20 20  20 20 20 20 20 20 20 3b  |, 6            ;|
000028c0  61 70 5e 32 20 69 6e 20  6c 6f 77 20 72 61 6e 67  |ap^2 in low rang|
000028d0  65 0d 0c d0 34 20 4d 55  4c 20 20 20 20 20 20 31  |e...4 MUL      1|
000028e0  32 2c 20 37 2c 20 37 20  20 20 20 20 20 20 20 20  |2, 7, 7         |
000028f0  20 20 20 3b 61 71 5e 32  20 69 6e 20 6c 6f 77 20  |   ;aq^2 in low |
00002900  72 61 6e 67 65 0d 0c da  34 20 41 44 44 20 20 20  |range...4 ADD   |
00002910  20 20 20 31 33 2c 20 31  31 2c 20 31 32 20 20 20  |   13, 11, 12   |
00002920  20 20 20 20 20 20 20 3b  64 69 76 69 73 6f 72 20  |       ;divisor |
00002930  61 70 5e 32 2b 61 71 5e  32 0d 0c e4 1b 20 4d 4f  |ap^2+aq^2.... MO|
00002940  56 20 20 20 20 20 20 30  2c 20 31 31 2c 20 41 53  |V      0, 11, AS|
00002950  4c 20 23 38 0d 0c ee 41  20 a4 64 69 76 28 70 61  |L #8...A .div(pa|
00002960  73 73 25 2c 20 30 2c 20  31 33 2c 20 31 31 2c 20  |ss%, 0, 13, 11, |
00002970  31 29 20 20 20 3b 74 20  20 69 6e 20 72 31 31 20  |1)   ;t  in r11 |
00002980  3d 20 32 35 36 61 70 5e  32 2f 28 61 70 5e 32 2b  |= 256ap^2/(ap^2+|
00002990  61 71 5e 32 29 0d 0c f8  1b 20 4d 4f 56 20 20 20  |aq^2).... MOV   |
000029a0  20 20 20 30 2c 20 31 32  2c 20 41 53 4c 20 23 38  |   0, 12, ASL #8|
000029b0  0d 0d 02 41 20 a4 64 69  76 28 70 61 73 73 25 2c  |...A .div(pass%,|
000029c0  20 30 2c 20 31 33 2c 20  31 32 2c 20 31 29 20 20  | 0, 13, 12, 1)  |
000029d0  20 3b 74 62 20 69 6e 20  72 31 32 20 3d 20 32 35  | ;tb in r12 = 25|
000029e0  36 61 71 5e 32 2f 28 61  70 5e 32 2b 61 71 5e 32  |6aq^2/(ap^2+aq^2|
000029f0  29 0d 0d 0c 18 20 4c 44  52 20 20 20 20 20 20 31  |).... LDR      1|
00002a00  33 2c 20 61 73 71 72 74  25 0d 0d 16 30 20 4c 44  |3, asqrt%...0 LD|
00002a10  52 20 20 20 20 20 20 37  2c 20 5b 31 33 2c 20 31  |R      7, [13, 1|
00002a20  31 2c 20 4c 53 4c 20 23  32 5d 20 3b 73 71 75 61  |1, LSL #2] ;squa|
00002a30  72 65 20 72 6f 6f 74 20  74 0d 0d 20 3c 20 4c 44  |re root t.. < LD|
00002a40  52 20 20 20 20 20 20 38  2c 20 5b 31 33 2c 20 31  |R      8, [13, 1|
00002a50  32 2c 20 4c 53 4c 20 23  32 5d 20 3b 61 6e 64 20  |2, LSL #2] ;and |
00002a60  74 62 2c 20 76 69 61 20  6c 6f 6f 6b 2d 75 70 2d  |tb, via look-up-|
00002a70  74 61 62 6c 65 0d 0d 2a  13 20 43 4d 50 20 20 20  |table..*. CMP   |
00002a80  20 20 20 39 2c 20 23 30  0d 0d 34 31 20 52 53 42  |   9, #0..41 RSB|
00002a90  4c 54 20 20 20 20 37 2c  20 37 2c 20 23 30 20 20  |LT    7, 7, #0  |
00002aa0  20 20 20 20 20 20 20 20  20 20 3b 66 69 6e 61 6c  |          ;final|
00002ab0  20 74 20 20 69 6e 20 72  37 0d 0d 3e 14 20 43 4d  | t  in r7..>. CM|
00002ac0  50 20 20 20 20 20 20 31  30 2c 20 23 30 0d 0d 48  |P      10, #0..H|
00002ad0  31 20 52 53 42 50 4c 20  20 20 20 38 2c 20 38 2c  |1 RSBPL    8, 8,|
00002ae0  20 23 30 20 20 20 20 20  20 20 20 20 20 20 20 3b  | #0            ;|
00002af0  66 69 6e 61 6c 20 74 62  20 69 6e 20 72 38 0d 0d  |final tb in r8..|
00002b00  52 1c 20 41 44 52 20 20  20 20 20 20 31 31 2c 20  |R. ADR      11, |
00002b10  61 63 6f 6c 6c 72 65 67  73 25 0d 0d 5c 20 20 4c  |acollregs%..\  L|
00002b20  44 4d 49 41 20 20 20 20  31 31 2c 20 7b 30 2d 34  |DMIA    11, {0-4|
00002b30  2c 31 32 2c 31 33 2c 31  34 7d 0d 0d 66 39 20 4d  |,12,13,14}..f9 M|
00002b40  55 4c 20 20 20 20 20 20  35 2c 20 37 2c 20 32 20  |UL      5, 7, 2 |
00002b50  20 20 20 20 20 20 20 20  20 20 20 20 3b 6e 6f 77  |            ;now|
00002b60  20 6d 6f 64 69 66 79 20  76 65 6c 6f 63 69 74 79  | modify velocity|
00002b70  20 62 79 0d 0d 70 37 20  4d 4c 41 20 20 20 20 20  | by..p7 MLA     |
00002b80  20 35 2c 20 38 2c 20 33  2c 20 35 20 20 20 20 20  | 5, 8, 3, 5     |
00002b90  20 20 20 20 20 3b 72 65  66 6c 65 63 74 69 6e 67  |     ;reflecting|
00002ba0  20 69 74 20 69 6e 20 74  68 65 0d 0d 7a 3f 20 52  | it in the..z? R|
00002bb0  53 42 20 20 20 20 20 20  35 2c 20 35 2c 20 23 30  |SB      5, 5, #0|
00002bc0  20 20 20 20 20 20 20 20  20 20 20 20 3b 6c 69 6e  |            ;lin|
00002bd0  65 20 67 65 6e 65 72 61  74 65 64 20 62 79 20 74  |e generated by t|
00002be0  68 65 20 6c 69 6e 65 61  72 0d 0d 84 39 20 4d 55  |he linear...9 MU|
00002bf0  4c 20 20 20 20 20 20 36  2c 20 37 2c 20 33 20 20  |L      6, 7, 3  |
00002c00  20 20 20 20 20 20 20 20  20 20 20 3b 72 65 67 72  |           ;regr|
00002c10  65 73 73 69 6f 6e 20 63  61 6c 63 75 6c 61 74 69  |ession calculati|
00002c20  6f 6e 0d 0d 8e 43 20 4d  55 4c 20 20 20 20 20 20  |on...C MUL      |
00002c30  39 2c 20 38 2c 20 32 20  20 20 20 20 20 20 20 20  |9, 8, 2         |
00002c40  20 20 20 20 3b 28 77 68  69 63 68 20 77 65 20 75  |    ;(which we u|
00002c50  73 65 20 74 6f 20 61 70  70 72 6f 78 69 6d 61 74  |se to approximat|
00002c60  65 20 74 68 65 0d 0d 98  45 20 53 55 42 20 20 20  |e the...E SUB   |
00002c70  20 20 20 36 2c 20 36 2c  20 39 20 20 20 20 20 20  |   6, 6, 9      |
00002c80  20 20 20 20 20 20 20 3b  20 74 61 6e 67 65 6e 74  |       ; tangent|
00002c90  20 61 74 20 74 68 65 20  63 6f 6c 6c 69 73 69 6f  | at the collisio|
00002ca0  6e 20 73 75 72 66 61 63  65 29 0d 0d a2 1d 20 52  |n surface).... R|
00002cb0  53 42 20 20 20 20 20 20  35 2c 20 35 2c 20 35 2c  |SB      5, 5, 5,|
00002cc0  20 41 53 4c 20 23 38 0d  0d ac 45 20 52 53 42 20  | ASL #8...E RSB |
00002cd0  20 20 20 20 20 36 2c 20  36 2c 20 36 2c 20 41 53  |     6, 6, 6, AS|
00002ce0  4c 20 23 38 20 20 20 20  20 3b 26 20 74 68 65 6e  |L #8     ;& then|
00002cf0  20 61 74 74 65 6e 75 61  74 65 20 62 79 20 66 61  | attenuate by fa|
00002d00  63 74 6f 72 20 32 35 35  2f 32 35 36 0d 0d b6 41  |ctor 255/256...A|
00002d10  20 4d 4f 56 20 20 20 20  20 20 32 2c 20 35 2c 20  | MOV      2, 5, |
00002d20  41 53 52 20 23 31 36 20  20 20 20 20 20 20 3b 28  |ASR #16       ;(|
00002d30  73 69 6d 75 6c 61 74 65  20 65 6e 65 72 67 79 20  |simulate energy |
00002d40  6c 6f 73 73 20 6f 6e 20  63 6f 6c 6c 29 0d 0d c0  |loss on coll)...|
00002d50  1b 20 4d 4f 56 20 20 20  20 20 20 33 2c 20 36 2c  |. MOV      3, 6,|
00002d60  20 41 53 52 20 23 31 36  0d 0d ca 44 20 41 44 44  | ASR #16...D ADD|
00002d70  20 20 20 20 20 20 34 2c  20 34 2c 20 23 31 20 20  |      4, 4, #1  |
00002d80  20 20 20 20 20 20 20 20  20 20 3b 74 72 61 63 6b  |          ;track|
00002d90  20 68 6f 77 20 6d 61 6e  79 20 63 6f 6e 73 65 63  | how many consec|
00002da0  75 74 69 76 65 20 66 72  61 6d 65 73 0d 0d d4 40  |utive frames...@|
00002db0  20 3a 20 20 20 20 20 20  20 20 20 20 20 20 20 20  | :              |
00002dc0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 3b 74  |              ;t|
00002dd0  68 69 73 20 62 61 6c 6c  20 68 61 73 20 62 65 65  |his ball has bee|
00002de0  6e 20 73 74 75 63 6b 20  69 6e 20 61 0d 0d de 45  |n stuck in a...E|
00002df0  20 43 4d 50 20 20 20 20  20 20 34 2c 23 32 20 20  | CMP      4,#2  |
00002e00  20 20 20 20 20 20 20 20  20 20 20 20 20 20 3b 63  |              ;c|
00002e10  6f 6c 6c 69 73 69 6f 6e  20 61 6e 64 20 69 66 20  |ollision and if |
00002e20  32 20 6f 72 20 6d 6f 72  65 2c 20 74 72 79 20 74  |2 or more, try t|
00002e30  6f 0d 0d e8 39 20 42 4c  54 20 20 20 20 20 20 6d  |o...9 BLT      m|
00002e40  6f 76 65 6e 63 68 65 63  6b 25 20 20 20 20 20 20  |ovencheck%      |
00002e50  20 20 20 3b 65 73 63 61  70 65 20 69 74 20 76 69  |   ;escape it vi|
00002e60  61 20 61 20 62 6f 64 67  65 3a 0d 0d f2 32 20 2e  |a a bodge:...2 .|
00002e70  62 6f 64 67 65 31 25 20  20 20 20 20 20 20 20 20  |bodge1%         |
00002e80  20 20 20 20 20 20 20 20  20 20 20 20 3b 62 6f 64  |            ;bod|
00002e90  67 65 20 62 65 67 69 6e  20 2e 2e 2e 0d 0d fc 16  |ge begin .......|
00002ea0  20 41 44 52 20 20 20 20  20 20 37 2c 20 73 65 65  | ADR      7, see|
00002eb0  64 25 0d 0e 06 17 20 4c  44 4d 49 41 20 20 20 20  |d%.... LDMIA    |
00002ec0  37 2c 20 7b 35 2c 20 36  7d 0d 0e 10 40 20 4d 4f  |7, {5, 6}...@ MO|
00002ed0  56 53 20 20 20 20 20 36  2c 20 36 2c 20 4c 53 52  |VS     6, 6, LSR|
00002ee0  20 23 31 20 20 20 20 20  20 20 20 3b 67 65 6e 65  | #1        ;gene|
00002ef0  72 61 74 65 20 72 61 6e  64 6f 6d 20 33 32 2d 62  |rate random 32-b|
00002f00  69 74 20 6e 75 6d 62 65  72 0d 0e 1a 17 20 4d 4f  |it number.... MO|
00002f10  56 53 20 20 20 20 20 38  2c 20 35 2c 20 52 52 58  |VS     8, 5, RRX|
00002f20  0d 0e 24 15 20 41 44 43  20 20 20 20 20 20 36 2c  |..$. ADC      6,|
00002f30  20 36 2c 20 36 0d 0e 2e  1c 20 82 20 20 20 20 20  | 6, 6.... .     |
00002f40  20 38 2c 20 38 2c 20 35  2c 20 4c 53 4c 20 23 31  | 8, 8, 5, LSL #1|
00002f50  32 0d 0e 38 1c 20 82 20  20 20 20 20 20 35 2c 20  |2..8. .      5, |
00002f60  38 2c 20 38 2c 20 4c 53  52 20 23 32 30 0d 0e 42  |8, 8, LSR #20..B|
00002f70  17 20 53 54 4d 49 41 20  20 20 20 37 2c 20 7b 35  |. STMIA    7, {5|
00002f80  2c 20 36 7d 0d 0e 4c 37  20 4c 44 52 20 20 20 20  |, 6}..L7 LDR    |
00002f90  20 20 37 2c 20 61 73 69  6e 63 6f 73 25 20 20 20  |  7, asincos%   |
00002fa0  20 20 20 20 20 20 3b 77  68 65 6e 20 62 61 6c 6c  |      ;when ball|
00002fb0  73 20 67 65 74 20 73 74  75 63 6b 0d 0e 56 40 20  |s get stuck..V@ |
00002fc0  80 20 20 20 20 20 20 35  2c 20 35 2c 20 23 32 35  |.      5, 5, #25|
00002fd0  35 20 20 20 20 20 20 20  20 20 20 3b 64 75 65 20  |5          ;due |
00002fe0  74 6f 20 63 6f 6e 66 6c  69 63 74 20 62 65 74 77  |to conflict betw|
00002ff0  65 65 6e 20 63 6f 72 72  65 63 74 0d 0e 60 41 20  |een correct..`A |
00003000  41 44 44 20 20 20 20 20  20 37 2c 20 37 2c 20 35  |ADD      7, 7, 5|
00003010  2c 20 41 53 4c 20 23 33  20 20 20 20 20 3b 72 65  |, ASL #3     ;re|
00003020  66 6c 65 63 74 69 6f 6e  20 26 20 73 6d 61 6c 6c  |flection & small|
00003030  20 76 65 6c 6f 63 69 74  79 20 6f 72 0d 0e 6a 3e  | velocity or..j>|
00003040  20 4c 44 4d 49 41 20 20  20 20 37 2c 20 7b 35 2c  | LDMIA    7, {5,|
00003050  20 36 7d 20 20 20 20 20  20 20 20 20 20 20 3b 6a  | 6}           ;j|
00003060  61 67 67 65 64 20 6f 76  65 72 6c 61 70 20 70 72  |agged overlap pr|
00003070  6f 62 6c 65 6d 73 20 2e  2e 2e 0d 0e 74 15 20 4d  |oblems .....t. M|
00003080  55 4c 20 20 20 20 20 20  37 2c 20 32 2c 20 35 0d  |UL      7, 2, 5.|
00003090  0e 7e 43 20 4d 4c 41 20  20 20 20 20 20 37 2c 20  |.~C MLA      7, |
000030a0  33 2c 20 36 2c 20 37 20  20 20 20 20 20 20 20 20  |3, 6, 7         |
000030b0  20 3b 74 72 79 20 61 20  27 66 69 78 27 20 2d 20  | ;try a 'fix' - |
000030c0  72 6f 74 61 74 65 20 76  65 6c 6f 63 69 74 79 20  |rotate velocity |
000030d0  62 79 0d 0e 88 40 20 4d  55 4c 20 20 20 20 20 20  |by...@ MUL      |
000030e0  38 2c 20 32 2c 20 36 20  20 20 20 20 20 20 20 20  |8, 2, 6         |
000030f0  20 20 20 20 3b 61 20 72  61 6e 64 6f 6d 20 61 6e  |    ;a random an|
00003100  67 6c 65 2c 20 73 6f 20  65 76 65 6e 74 75 61 6c  |gle, so eventual|
00003110  6c 79 0d 0e 92 41 20 4d  55 4c 20 20 20 20 20 20  |ly...A MUL      |
00003120  39 2c 20 33 2c 20 35 20  20 20 20 20 20 20 20 20  |9, 3, 5         |
00003130  20 20 20 20 3b 73 68 6f  75 6c 64 20 70 69 63 6b  |    ;should pick|
00003140  20 73 6f 6d 65 20 76 65  6c 6f 63 69 74 79 20 74  | some velocity t|
00003150  68 61 74 0d 0e 9c 46 20  53 55 42 20 20 20 20 20  |hat...F SUB     |
00003160  20 38 2c 20 38 2c 20 39  20 20 20 20 20 20 20 20  | 8, 8, 9        |
00003170  20 20 20 20 20 3b 65 78  74 72 69 63 61 74 65 73  |     ;extricates|
00003180  20 62 61 6c 6c 20 66 72  6f 6d 20 73 74 75 63 6b  | ball from stuck|
00003190  20 70 6f 73 69 74 69 6f  6e 0d 0e a6 1a 20 4d 4f  | position.... MO|
000031a0  56 20 20 20 20 20 20 32  2c 20 37 2c 20 41 53 52  |V      2, 7, ASR|
000031b0  20 23 38 0d 0e b0 30 20  4d 4f 56 20 20 20 20 20  | #8...0 MOV     |
000031c0  20 33 2c 20 38 2c 20 41  53 52 20 23 38 20 20 20  | 3, 8, ASR #8   |
000031d0  20 20 20 20 20 3b 2e 2e  2e 20 62 6f 64 67 65 20  |     ;... bodge |
000031e0  65 6e 64 0d 0e ba 14 20  43 4d 50 20 20 20 20 20  |end.... CMP     |
000031f0  20 34 2c 20 23 31 36 0d  0e c4 19 20 42 4c 54 20  | 4, #16.... BLT |
00003200  20 20 20 20 20 6d 6f 76  65 6e 63 68 65 63 6b 25  |     movencheck%|
00003210  0d 0e ce 14 20 4d 4f 56  20 20 20 20 20 20 50 43  |.... MOV      PC|
00003220  2c 20 31 34 0d 0e d8 06  20 3a 0d 0e e2 24 20 2e  |, 14.... :...$ .|
00003230  61 73 69 6e 63 6f 73 25  20 20 20 20 20 20 20 20  |asincos%        |
00003240  20 20 45 51 55 44 20 73  69 6e 63 6f 73 25 0d 0e  |  EQUD sincos%..|
00003250  ec 1d 20 2e 73 65 65 64  25 20 20 20 45 51 55 44  |.. .seed%   EQUD|
00003260  20 2d 31 3a 45 51 55 44  20 2d 31 0d 0e f6 46 20  | -1:EQUD -1...F |
00003270  2e 70 61 74 63 68 31 25  20 20 20 20 20 20 20 20  |.patch1%        |
00003280  20 20 20 20 20 20 20 20  20 20 20 20 20 3b 61 20  |             ;a |
00003290  70 61 74 63 68 20 74 6f  20 64 65 61 6c 20 77 69  |patch to deal wi|
000032a0  74 68 20 63 6f 6c 6c 69  73 69 6f 6e 20 63 61 73  |th collision cas|
000032b0  65 0d 0f 00 44 20 41 44  52 20 20 20 20 20 20 31  |e...D ADR      1|
000032c0  31 2c 20 61 63 6f 6c 6c  72 65 67 73 25 20 20 20  |1, acollregs%   |
000032d0  20 20 20 3b 77 68 65 72  65 20 6e 6f 20 6c 69 6e  |   ;where no lin|
000032e0  65 61 72 20 72 65 67 72  65 73 73 69 6f 6e 20 65  |ear regression e|
000032f0  78 69 73 74 73 0d 0f 0a  44 20 4c 44 4d 49 41 20  |xists...D LDMIA |
00003300  20 20 20 31 31 2c 20 7b  30 2d 34 2c 31 32 2c 31  |   11, {0-4,12,1|
00003310  33 2c 31 34 7d 20 20 3b  28 65 67 20 77 68 65 72  |3,14}  ;(eg wher|
00003320  65 20 63 6f 6c 6c 69 73  69 6f 6e 20 69 6e 76 6f  |e collision invo|
00003330  6c 76 65 73 20 6f 6e 6c  79 0d 0f 14 2e 20 53 55  |lves only.... SU|
00003340  42 20 20 20 20 20 20 32  2c 20 32 2c 20 32 2c 20  |B      2, 2, 2, |
00003350  41 53 4c 20 23 38 20 20  20 20 20 3b 20 6f 6e 65  |ASL #8     ; one|
00003360  20 70 69 78 65 6c 29 0d  0f 1e 3d 20 53 55 42 20  | pixel)...= SUB |
00003370  20 20 20 20 20 33 2c 20  33 2c 20 33 2c 20 41 53  |     3, 3, 3, AS|
00003380  4c 20 23 38 20 20 20 20  20 3b 2d 20 73 69 6d 70  |L #8     ;- simp|
00003390  6c 79 20 72 65 76 65 72  73 65 20 76 65 6c 6f 63  |ly reverse veloc|
000033a0  69 74 79 21 0d 0f 28 1a  20 4d 4f 56 20 20 20 20  |ity!..(. MOV    |
000033b0  20 20 32 2c 20 32 2c 20  41 53 52 20 23 38 0d 0f  |  2, 2, ASR #8..|
000033c0  32 46 20 4d 4f 56 20 20  20 20 20 20 33 2c 20 33  |2F MOV      3, 3|
000033d0  2c 20 41 53 52 20 23 38  20 20 20 20 20 20 20 20  |, ASR #8        |
000033e0  3b 6e 62 20 61 6c 73 6f  20 61 74 74 65 6e 75 61  |;nb also attenua|
000033f0  74 65 20 62 79 20 66 61  63 74 6f 72 20 32 35 35  |te by factor 255|
00003400  2f 32 35 36 0d 0f 3c 41  20 41 44 44 20 20 20 20  |/256..<A ADD    |
00003410  20 20 34 2c 20 34 2c 20  23 31 20 20 20 20 20 20  |  4, 4, #1      |
00003420  20 20 20 20 20 20 3b 28  73 69 6d 75 6c 61 74 65  |      ;(simulate|
00003430  20 65 6e 65 72 67 79 20  6c 6f 73 73 20 6f 6e 20  | energy loss on |
00003440  63 6f 6c 6c 29 0d 0f 46  12 20 43 4d 50 20 20 20  |coll)..F. CMP   |
00003450  20 20 20 34 2c 23 32 0d  0f 50 19 20 42 4c 54 20  |   4,#2..P. BLT |
00003460  20 20 20 20 20 6d 6f 76  65 6e 63 68 65 63 6b 25  |     movencheck%|
00003470  0d 0f 5a 46 20 42 20 20  20 20 20 20 20 20 62 6f  |..ZF B        bo|
00003480  64 67 65 31 25 20 20 20  20 20 20 20 20 20 20 20  |dge1%           |
00003490  20 20 3b 69 66 20 62 65  65 6e 20 73 74 75 63 6b  |  ;if been stuck|
000034a0  20 69 6e 20 63 6f 6c 6c  69 73 69 6f 6e 20 66 6f  | in collision fo|
000034b0  72 20 3e 3d 20 32 0d 0f  64 46 20 3a 20 20 20 20  |r >= 2..dF :    |
000034c0  20 20 20 20 20 20 20 20  20 20 20 20 20 20 20 20  |                |
000034d0  20 20 20 20 20 20 20 20  3b 66 72 61 6d 65 73 20  |        ;frames |
000034e0  67 6f 20 61 6e 64 20 61  70 70 6c 79 20 62 6f 64  |go and apply bod|
000034f0  67 65 64 20 27 65 73 63  61 70 65 27 0d 0f 6e 18  |ged 'escape'..n.|
00003500  20 2e 61 73 71 72 74 25  20 20 45 51 55 44 20 73  | .asqrt%  EQUD s|
00003510  71 72 74 25 0d 0f 78 14  20 2e 61 6c 72 63 6c 73  |qrt%..x. .alrcls|
00003520  25 20 45 51 55 44 20 30  0d 0f 82 14 20 2e 61 73  |% EQUD 0.... .as|
00003530  70 63 6c 73 25 20 45 51  55 44 20 30 0d 0f 8c 44  |pcls% EQUD 0...D|
00003540  20 2e 63 6f 70 79 62 61  63 6b 25 20 20 20 20 20  | .copyback%     |
00003550  20 20 20 20 20 20 20 20  20 20 20 20 20 20 3b 73  |              ;s|
00003560  69 6d 70 6c 65 20 72 6f  75 74 69 6e 65 20 74 6f  |imple routine to|
00003570  20 63 6c 65 61 72 20 73  63 72 65 65 6e 20 74 6f  | clear screen to|
00003580  0d 0f 96 46 20 53 54 52  20 20 20 20 20 20 31 34  |...F STR      14|
00003590  2c 20 61 6c 72 63 6c 73  25 20 20 20 20 20 20 20  |, alrcls%       |
000035a0  20 20 3b 62 61 63 6b 67  72 6f 75 6e 64 20 61 73  |  ;background as|
000035b0  20 72 61 70 69 64 6c 79  20 61 73 20 70 6f 73 73  | rapidly as poss|
000035c0  69 62 6c 65 20 2d 0d 0f  a0 41 20 53 54 52 20 20  |ible -...A STR  |
000035d0  20 20 20 20 31 33 2c 20  61 73 70 63 6c 73 25 20  |    13, aspcls% |
000035e0  20 20 20 20 20 20 20 20  3b 6e 6f 74 65 20 74 68  |        ;note th|
000035f0  65 20 68 65 61 76 79 20  75 73 65 20 6f 66 20 4c  |e heavy use of L|
00003600  44 4d 2f 53 54 4d 2e 0d  0f aa 18 20 4c 44 52 20  |DM/STM..... LDR |
00003610  20 20 20 20 20 30 2c 20  61 73 63 72 73 74 25 0d  |     0, ascrst%.|
00003620  0f b4 1b 20 4c 44 52 20  20 20 20 20 20 31 2c 20  |... LDR      1, |
00003630  61 62 61 63 6b 64 61 74  61 25 0d 0f be 17 20 41  |abackdata%.... A|
00003640  44 44 20 20 20 20 20 20  31 2c 20 31 2c 20 23 35  |DD      1, 1, #5|
00003650  36 0d 0f c8 15 20 4d 4f  56 20 20 20 20 20 20 32  |6.... MOV      2|
00003660  2c 20 23 32 30 30 0d 0f  d2 0e 20 2e 63 6c 73 6c  |, #200.... .clsl|
00003670  6f 6f 70 25 0d 0f dc 18  20 4c 44 4d 49 41 20 20  |oop%.... LDMIA  |
00003680  20 20 31 21 2c 20 7b 33  2d 31 34 7d 0d 0f e6 18  |  1!, {3-14}....|
00003690  20 53 54 4d 49 41 20 20  20 20 30 21 2c 20 7b 33  | STMIA    0!, {3|
000036a0  2d 31 34 7d 0d 0f f0 18  20 4c 44 4d 49 41 20 20  |-14}.... LDMIA  |
000036b0  20 20 31 21 2c 20 7b 33  2d 31 34 7d 0d 0f fa 18  |  1!, {3-14}....|
000036c0  20 53 54 4d 49 41 20 20  20 20 30 21 2c 20 7b 33  | STMIA    0!, {3|
000036d0  2d 31 34 7d 0d 10 04 18  20 4c 44 4d 49 41 20 20  |-14}.... LDMIA  |
000036e0  20 20 31 21 2c 20 7b 33  2d 31 34 7d 0d 10 0e 18  |  1!, {3-14}....|
000036f0  20 53 54 4d 49 41 20 20  20 20 30 21 2c 20 7b 33  | STMIA    0!, {3|
00003700  2d 31 34 7d 0d 10 18 18  20 4c 44 4d 49 41 20 20  |-14}.... LDMIA  |
00003710  20 20 31 21 2c 20 7b 33  2d 31 34 7d 0d 10 22 18  |  1!, {3-14}..".|
00003720  20 53 54 4d 49 41 20 20  20 20 30 21 2c 20 7b 33  | STMIA    0!, {3|
00003730  2d 31 34 7d 0d 10 2c 18  20 4c 44 4d 49 41 20 20  |-14}..,. LDMIA  |
00003740  20 20 31 21 2c 20 7b 33  2d 31 34 7d 0d 10 36 18  |  1!, {3-14}..6.|
00003750  20 53 54 4d 49 41 20 20  20 20 30 21 2c 20 7b 33  | STMIA    0!, {3|
00003760  2d 31 34 7d 0d 10 40 18  20 4c 44 4d 49 41 20 20  |-14}..@. LDMIA  |
00003770  20 20 31 21 2c 20 7b 33  2d 31 34 7d 0d 10 4a 18  |  1!, {3-14}..J.|
00003780  20 53 54 4d 49 41 20 20  20 20 30 21 2c 20 7b 33  | STMIA    0!, {3|
00003790  2d 31 34 7d 0d 10 54 06  20 5d 0d 10 5e 0d 20 e7  |-14}..T. ]..^. .|
000037a0  20 56 47 41 25 20 8c 0d  10 68 0f 20 5b 4f 50 54  | VGA% ...h. [OPT|
000037b0  20 70 61 73 73 25 0d 10  72 20 20 41 44 44 20 20  | pass%..r  ADD  |
000037c0  20 20 20 20 30 2c 20 30  2c 20 23 68 61 64 64 25  |    0, 0, #hadd%|
000037d0  2d 68 70 69 78 25 0d 10  7c 06 20 5d 0d 10 86 06  |-hpix%..|. ]....|
000037e0  20 cd 0d 10 90 0f 20 5b  4f 50 54 20 70 61 73 73  | ..... [OPT pass|
000037f0  25 0d 10 9a 16 20 53 55  42 53 20 20 20 20 20 32  |%.... SUBS     2|
00003800  2c 20 32 2c 20 23 31 0d  10 a4 16 20 42 4e 45 20  |, 2, #1.... BNE |
00003810  20 20 20 20 20 63 6c 73  6c 6f 6f 70 25 0d 10 ae  |     clsloop%...|
00003820  19 20 4c 44 52 20 20 20  20 20 20 31 33 2c 20 61  |. LDR      13, a|
00003830  73 70 63 6c 73 25 0d 10  b8 19 20 4c 44 52 20 20  |spcls%.... LDR  |
00003840  20 20 20 20 50 43 2c 20  61 6c 72 63 6c 73 25 0d  |    PC, alrcls%.|
00003850  10 c2 06 20 5d 0d 10 cc  05 ed 0d 10 d6 05 e1 0d  |... ]...........|
00003860  10 e0 05 3a 0d 10 ea 3c  dd 20 a4 70 6c 6f 74 66  |...:...<. .plotf|
00003870  72 61 67 28 70 61 73 73  25 29 20 20 20 20 3a f4  |rag(pass%)    :.|
00003880  20 6d 61 63 72 6f 20 74  6f 20 70 6c 6f 74 20 61  | macro to plot a|
00003890  20 72 6f 77 20 28 32 30  20 70 69 78 65 6c 73 29  | row (20 pixels)|
000038a0  0d 10 f4 2d 5b 4f 50 54  20 70 61 73 73 25 20 20  |...-[OPT pass%  |
000038b0  20 20 20 20 20 20 20 20  20 20 20 20 20 3a f4 20  |             :. |
000038c0  6f 66 20 6f 75 72 20 73  70 72 69 74 65 0d 10 fe  |of our sprite...|
000038d0  45 4c 44 4d 49 41 20 20  20 20 30 2c 20 7b 34 2d  |ELDMIA    0, {4-|
000038e0  36 7d 20 20 20 20 20 20  20 20 20 20 20 20 20 3b  |6}             ;|
000038f0  72 65 61 64 20 33 20 77  6f 72 64 73 20 6f 66 20  |read 3 words of |
00003900  73 63 72 65 65 6e 20 28  31 32 20 70 69 78 65 6c  |screen (12 pixel|
00003910  73 29 0d 11 08 38 4c 44  4d 49 41 20 20 20 20 31  |s)...8LDMIA    1|
00003920  21 2c 20 7b 37 2d 39 7d  20 20 20 20 20 20 20 20  |!, {7-9}        |
00003930  20 20 20 20 3b 72 65 61  64 20 31 32 20 73 70 72  |    ;read 12 spr|
00003940  69 74 65 20 70 69 78 65  6c 73 0d 11 12 2d 4c 44  |ite pixels...-LD|
00003950  4d 49 41 20 20 20 20 33  21 2c 20 7b 31 30 2d 31  |MIA    3!, {10-1|
00003960  32 7d 20 20 20 20 20 20  20 20 20 20 3b 26 20 31  |2}          ;& 1|
00003970  32 20 6d 61 73 6b 73 0d  11 1c 40 42 49 43 20 20  |2 masks...@BIC  |
00003980  20 20 20 20 34 2c 20 34  2c 20 31 30 20 20 20 20  |    4, 4, 10    |
00003990  20 20 20 20 20 20 20 20  20 3b 61 70 70 6c 79 20  |         ;apply |
000039a0  6d 61 73 6b 20 74 6f 20  73 63 72 65 65 6e 2c 20  |mask to screen, |
000039b0  7a 65 72 6f 69 6e 67 0d  11 26 3f 42 49 43 20 20  |zeroing..&?BIC  |
000039c0  20 20 20 20 35 2c 20 35  2c 20 31 31 20 20 20 20  |    5, 5, 11    |
000039d0  20 20 20 20 20 20 20 20  20 3b 20 74 68 6f 73 65  |         ; those|
000039e0  20 62 69 74 73 20 77 68  65 72 65 20 77 69 6c 6c  | bits where will|
000039f0  20 77 72 69 74 65 0d 11  30 3c 42 49 43 20 20 20  | write..0<BIC   |
00003a00  20 20 20 36 2c 20 36 2c  20 31 32 20 20 20 20 20  |   6, 6, 12     |
00003a10  20 20 20 20 20 20 20 20  3b 20 73 70 72 69 74 65  |        ; sprite|
00003a20  20 69 6d 61 67 65 20 69  6e 20 61 20 6d 6f 6d 65  | image in a mome|
00003a30  6e 74 0d 11 3a 3b 84 52  20 20 20 20 20 20 34 2c  |nt..:;.R      4,|
00003a40  20 34 2c 20 37 20 20 20  20 20 20 20 20 20 20 20  | 4, 7           |
00003a50  20 20 20 3b 77 72 69 74  65 20 69 6e 20 74 68 65  |   ;write in the|
00003a60  20 73 70 72 69 74 65 20  69 6d 61 67 65 0d 11 44  | sprite image..D|
00003a70  13 84 52 20 20 20 20 20  20 35 2c 20 35 2c 20 38  |..R      5, 5, 8|
00003a80  0d 11 4e 13 84 52 20 20  20 20 20 20 36 2c 20 36  |..N..R      6, 6|
00003a90  2c 20 39 0d 11 58 42 53  54 4d 49 41 20 20 20 20  |, 9..XBSTMIA    |
00003aa0  30 21 2c 20 7b 34 2d 36  7d 20 20 20 20 20 20 20  |0!, {4-6}       |
00003ab0  20 20 20 20 20 3b 72 65  73 74 6f 72 65 20 74 68  |     ;restore th|
00003ac0  65 20 64 61 74 61 20 62  61 63 6b 20 74 6f 20 73  |e data back to s|
00003ad0  63 72 65 65 6e 0d 11 62  44 4c 44 4d 49 41 20 20  |creen..bDLDMIA  |
00003ae0  20 20 30 2c 20 7b 34 2d  35 7d 20 20 20 20 20 20  |  0, {4-5}      |
00003af0  20 20 20 20 20 20 20 3b  72 65 61 64 20 32 20 77  |       ;read 2 w|
00003b00  6f 72 64 73 20 6f 66 20  73 63 72 65 65 6e 20 28  |ords of screen (|
00003b10  38 20 70 69 78 65 6c 73  29 0d 11 6c 37 4c 44 4d  |8 pixels)..l7LDM|
00003b20  49 41 20 20 20 20 31 21  2c 20 7b 37 2d 38 7d 20  |IA    1!, {7-8} |
00003b30  20 20 20 20 20 20 20 20  20 20 20 3b 72 65 61 64  |           ;read|
00003b40  20 38 20 73 70 72 69 74  65 20 70 69 78 65 6c 73  | 8 sprite pixels|
00003b50  0d 11 76 2c 4c 44 4d 49  41 20 20 20 20 33 21 2c  |..v,LDMIA    3!,|
00003b60  20 7b 31 30 2d 31 31 7d  20 20 20 20 20 20 20 20  | {10-11}        |
00003b70  20 20 3b 26 20 38 20 6d  61 73 6b 73 0d 11 80 15  |  ;& 8 masks....|
00003b80  42 49 43 20 20 20 20 20  20 34 2c 20 34 2c 20 31  |BIC      4, 4, 1|
00003b90  30 0d 11 8a 15 42 49 43  20 20 20 20 20 20 35 2c  |0....BIC      5,|
00003ba0  20 35 2c 20 31 31 0d 11  94 13 84 52 20 20 20 20  | 5, 11.....R    |
00003bb0  20 20 34 2c 20 34 2c 20  37 0d 11 9e 13 84 52 20  |  4, 4, 7.....R |
00003bc0  20 20 20 20 20 35 2c 20  35 2c 20 38 0d 11 a8 42  |     5, 5, 8...B|
00003bd0  53 54 4d 49 41 20 20 20  20 30 21 2c 20 7b 34 2d  |STMIA    0!, {4-|
00003be0  35 7d 20 20 20 20 20 20  20 20 20 20 20 20 3b 72  |5}            ;r|
00003bf0  65 73 74 6f 72 65 20 74  68 65 20 64 61 74 61 20  |estore the data |
00003c00  62 61 63 6b 20 74 6f 20  73 63 72 65 65 6e 0d 11  |back to screen..|
00003c10  b2 05 5d 0d 11 bc 0a 3d  70 61 73 73 25 0d 11 c6  |..]....=pass%...|
00003c20  05 3a 0d 11 d0 36 dd 20  a4 63 6f 6c 6c 66 72 61  |.:...6. .collfra|
00003c30  67 28 70 61 73 73 25 29  20 20 20 20 3a f4 20 6d  |g(pass%)    :. m|
00003c40  61 63 72 6f 20 74 6f 20  63 6f 6c 6c 20 63 68 65  |acro to coll che|
00003c50  63 6b 20 61 20 72 6f 77  0d 11 da 39 5b 4f 50 54  |ck a row...9[OPT|
00003c60  20 70 61 73 73 25 20 20  20 20 20 20 20 20 20 20  | pass%          |
00003c70  20 20 20 20 20 3a f4 20  28 32 30 20 70 69 78 65  |     :. (20 pixe|
00003c80  6c 73 29 20 6f 66 20 6f  75 72 20 73 70 72 69 74  |ls) of our sprit|
00003c90  65 0d 11 e4 45 4c 44 4d  49 41 20 20 20 20 30 21  |e...ELDMIA    0!|
00003ca0  2c 20 7b 33 2d 37 7d 20  20 20 20 20 20 20 20 20  |, {3-7}         |
00003cb0  20 20 20 3b 72 65 61 64  20 35 20 77 6f 72 64 73  |   ;read 5 words|
00003cc0  20 6f 66 20 73 63 72 65  65 6e 20 28 32 30 20 70  | of screen (20 p|
00003cd0  69 78 65 6c 73 29 0d 11  ee 3d 4c 44 4d 49 41 20  |ixels)...=LDMIA |
00003ce0  20 20 20 31 21 2c 20 7b  38 2d 31 32 7d 20 20 20  |   1!, {8-12}   |
00003cf0  20 20 20 20 20 20 20 20  3b 72 65 61 64 20 32 30  |        ;read 20|
00003d00  20 73 70 72 69 74 65 20  70 69 78 65 6c 20 6d 61  | sprite pixel ma|
00003d10  73 6b 73 0d 11 f8 11 54  53 54 20 20 20 20 20 20  |sks....TST      |
00003d20  33 2c 20 38 0d 12 02 11  54 53 54 45 51 20 20 20  |3, 8....TSTEQ   |
00003d30  20 34 2c 20 39 0d 12 0c  12 54 53 54 45 51 20 20  | 4, 9....TSTEQ  |
00003d40  20 20 35 2c 20 31 30 0d  12 16 12 54 53 54 45 51  |  5, 10....TSTEQ|
00003d50  20 20 20 20 36 2c 20 31  31 0d 12 20 12 54 53 54  |    6, 11.. .TST|
00003d60  45 51 20 20 20 20 37 2c  20 31 32 0d 12 2a 44 42  |EQ    7, 12..*DB|
00003d70  4e 45 20 20 20 20 20 20  67 6f 74 63 6f 6c 6c 25  |NE      gotcoll%|
00003d80  20 20 20 20 20 20 20 20  20 20 20 20 20 3b 62 72  |             ;br|
00003d90  61 6e 63 68 20 74 6f 20  67 6f 74 63 6f 6c 6c 25  |anch to gotcoll%|
00003da0  20 69 66 20 61 6e 79 20  6f 76 65 72 6c 61 70 0d  | if any overlap.|
00003db0  12 34 44 5d 20 20 20 20  20 20 20 20 20 20 20 20  |.4D]            |
00003dc0  20 20 20 20 20 20 20 20  20 20 20 20 3a f4 20 20  |            :.  |
00003dd0  65 6c 73 65 20 63 6f 6e  74 69 6e 75 65 20 77 69  |else continue wi|
00003de0  74 68 20 63 6f 64 65 20  61 66 74 65 72 20 6d 61  |th code after ma|
00003df0  63 72 6f 0d 12 3e 0a 3d  70 61 73 73 25 0d 12 48  |cro..>.=pass%..H|
00003e00  05 3a 0d 12 52 3d dd 20  a4 73 74 61 74 66 72 61  |.:..R=. .statfra|
00003e10  67 28 70 61 73 73 25 2c  20 6d 25 29 3a f4 20 6d  |g(pass%, m%):. m|
00003e20  61 63 72 6f 20 74 6f 20  61 64 64 20 69 6e 20 72  |acro to add in r|
00003e30  65 67 72 65 73 73 69 6f  6e 20 73 74 61 74 73 0d  |egression stats.|
00003e40  12 5c 40 5b 4f 50 54 20  70 61 73 73 25 20 20 20  |.\@[OPT pass%   |
00003e50  20 20 20 20 20 20 20 20  20 20 20 20 3a f4 20 66  |            :. f|
00003e60  6f 72 20 6f 6e 65 20 70  69 78 65 6c 20 28 63 6f  |or one pixel (co|
00003e70  6f 72 64 73 20 75 28 69  29 2c 76 28 69 29 29 0d  |ords u(i),v(i)).|
00003e80  12 66 14 54 53 54 20 20  20 20 20 20 20 34 2c 20  |.f.TST       4, |
00003e90  23 6d 25 0d 12 70 14 42  45 51 20 20 20 20 20 20  |#m%..p.BEQ      |
00003ea0  20 50 25 2b 38 2a 34 0d  12 7a 2d 41 44 44 4e 45  | P%+8*4..z-ADDNE|
00003eb0  20 20 20 20 20 36 2c 20  36 2c 20 23 31 20 20 20  |     6, 6, #1   |
00003ec0  20 20 20 20 20 20 20 20  20 3b 20 6e 20 3d 20 6e  |         ; n = n|
00003ed0  20 2b 20 31 0d 12 84 30  41 44 44 4e 45 20 20 20  | + 1...0ADDNE   |
00003ee0  20 20 37 2c 20 37 2c 20  32 20 20 20 20 20 20 20  |  7, 7, 2       |
00003ef0  20 20 20 20 20 20 3b 20  75 20 3d 20 75 20 2b 20  |      ; u = u + |
00003f00  75 28 69 29 0d 12 8e 30  41 44 44 4e 45 20 20 20  |u(i)...0ADDNE   |
00003f10  20 20 38 2c 20 38 2c 20  33 20 20 20 20 20 20 20  |  8, 8, 3       |
00003f20  20 20 20 20 20 20 3b 20  76 20 3d 20 76 20 2b 20  |      ; v = v + |
00003f30  76 28 69 29 0d 12 98 15  41 44 44 4e 45 20 20 20  |v(i)....ADDNE   |
00003f40  20 20 35 2c 20 32 2c 20  33 0d 12 a2 16 53 55 42  |  5, 2, 3....SUB|
00003f50  4e 45 20 20 20 20 20 31  34 2c 20 33 2c 20 32 0d  |NE     14, 3, 2.|
00003f60  12 ac 39 4d 4c 41 4e 45  20 20 20 20 20 39 2c 20  |..9MLANE     9, |
00003f70  35 2c 20 31 34 2c 20 39  20 20 20 20 20 20 20 20  |5, 14, 9        |
00003f80  20 3b 20 70 20 3d 20 70  20 2b 20 76 28 69 29 5e  | ; p = p + v(i)^|
00003f90  32 2d 75 28 69 29 5e 32  0d 12 b6 35 4d 4c 41 4e  |2-u(i)^2...5MLAN|
00003fa0  45 20 20 20 20 20 31 30  2c 20 32 2c 20 33 2c 20  |E     10, 2, 3, |
00003fb0  31 30 20 20 20 20 20 20  20 20 3b 20 71 20 3d 20  |10        ; q = |
00003fc0  71 20 2b 20 75 28 69 29  2a 76 28 69 29 0d 12 c0  |q + u(i)*v(i)...|
00003fd0  05 5d 0d 12 ca 0a 3d 70  61 73 73 25 0d 12 d4 05  |.]....=pass%....|
00003fe0  3a 0d 12 de 3c dd 20 a4  64 69 76 28 70 61 73 73  |:...<. .div(pass|
00003ff0  25 2c 20 72 61 2c 20 72  62 2c 20 72 63 2c 20 72  |%, ra, rb, rc, r|
00004000  64 29 20 3a f4 20 6d 61  63 72 6f 20 74 6f 20 73  |d) :. macro to s|
00004010  65 74 20 72 63 3d 72 61  44 49 56 72 62 0d 12 e8  |et rc=raDIVrb...|
00004020  0e 5b 4f 50 54 20 70 61  73 73 25 0d 12 f2 14 4d  |.[OPT pass%....M|
00004030  4f 56 20 20 20 20 20 20  20 72 64 2c 20 72 62 0d  |OV       rd, rb.|
00004040  12 fc 1c 43 4d 50 20 20  20 20 20 20 20 72 64 2c  |...CMP       rd,|
00004050  20 72 61 2c 20 4c 53 52  20 23 31 0d 13 06 1c 4d  | ra, LSR #1....M|
00004060  4f 56 4c 53 20 20 20 20  20 72 64 2c 20 72 64 2c  |OVLS     rd, rd,|
00004070  20 4c 53 4c 20 23 31 0d  13 10 1c 43 4d 50 20 20  | LSL #1....CMP  |
00004080  20 20 20 20 20 72 64 2c  20 72 61 2c 20 4c 53 52  |     rd, ra, LSR|
00004090  20 23 31 0d 13 1a 14 42  4c 53 20 20 20 20 20 20  | #1....BLS      |
000040a0  20 50 25 2d 32 2a 34 0d  13 24 14 4d 4f 56 20 20  | P%-2*4..$.MOV  |
000040b0  20 20 20 20 20 72 63 2c  20 23 30 0d 13 2e 14 43  |     rc, #0....C|
000040c0  4d 50 20 20 20 20 20 20  20 72 61 2c 20 72 64 0d  |MP       ra, rd.|
000040d0  13 38 18 53 55 42 43 53  20 20 20 20 20 72 61 2c  |.8.SUBCS     ra,|
000040e0  20 72 61 2c 20 72 64 0d  13 42 18 41 44 43 20 20  | ra, rd..B.ADC  |
000040f0  20 20 20 20 20 72 63 2c  20 72 63 2c 20 72 63 0d  |     rc, rc, rc.|
00004100  13 4c 1c 4d 4f 56 20 20  20 20 20 20 20 72 64 2c  |.L.MOV       rd,|
00004110  20 72 64 2c 20 4c 53 52  20 23 31 0d 13 56 14 43  | rd, LSR #1..V.C|
00004120  4d 50 20 20 20 20 20 20  20 72 64 2c 20 72 62 0d  |MP       rd, rb.|
00004130  13 60 14 42 48 53 20 20  20 20 20 20 20 50 25 2d  |.`.BHS       P%-|
00004140  35 2a 34 0d 13 6a 05 5d  0d 13 74 0a 3d 70 61 73  |5*4..j.]..t.=pas|
00004150  73 25 0d ff                                       |s%..|
00004154