Home » Archimedes archive » Archimedes World » AW-1996-03-Disc 2.adf » !AcornAns_AcornAns » September/FastDiv/FastDiv

September/FastDiv/FastDiv

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-03-Disc 2.adf » !AcornAns_AcornAns
Filename: September/FastDiv/FastDiv
Read OK:
File size: 34D7 bytes
Load address: 0000
Exec address: 0000
Duplicates

There is 1 duplicate copy of this file in the archive:

File contents
   10REM >FASTDIVbsc
   20REM Fast DIV/MOD  with a constant number
   30REM code fragment  to test fastdiv/mod code generation
   40REM Author: Samuel K.R. Smith
   50REM Heavily MODIFIED by Michael Rozdoba, February '95
   60REM (fixes & additional modifications)
   70
   80ONERROR:PROCerr:END
   90MODE 0
  100
  110spoolpath$ = "FDdemo"
  120spool%=FALSE
  130IF spool% OSCLI("Spool "+spoolpath$)
  140
  150PRINT '"Fast Integer Division Code for arbitrary CONSTANT Divisor -"
  160PRINT "Compilation & testing:"'
  170PRINT "This program lists the divisors it is testing & disassembles each routine,"
  180PRINT "each of which calculates R0 = R2 DIV divisor, R1 = R2 MOD divisor."
  190PRINT "If it finds an error it prints the details and waits for a key press."''
  200
  210DIM code% &400
  220r0=0:r1=1:r2=2:r3=3
  230
  240Q%=1000
  250R%=&7FFFFFFF-Q%
  260S%=&80000000+Q%
  270maxc%=0: nmaxc%=0: totc%=0: cnt%=0
  280
  290Zbase%=1
  300Zrange%=100000
  310
  320Z%=Zbase%
  330REPEAT
  340  PROCcheck( Z%,-Q%,Q%, 1)
  350  PROCcheck(-Z%,-Q%,Q%, 2)
  360  PROCcheck( Z%,R%,&7FFFFFFF, 0)
  370  PROCcheck(-Z%,R%,&7FFFFFFF, 0)
  380  PROCcheck( Z%,&80000000,S%, 0)
  390  PROCcheck(-Z%,&80000000,S%, 0)
  400  PROCcheck( Z%,-Q%,Q%, 100+0)
  410  PROCcheck(-Z%,-Q%,Q%, 100-1)
  420  cnt% += 1
  430  l% =(aft%-fore%)/4
  440  totc% += l%
  450  IF l%>maxc% THEN
  460    maxc% = l%
  470    nmaxc%= Z%
  480  ENDIF
  490  PRINT"Current max code length ";maxc%;" instructions for divisor ";FNnstr(nmaxc%)
  500  PRINT"Average code length ";totc%/cnt%;" instructions"''
  510Z%+=1
  520UNTIL Z%=Zbase%+Zrange%
  530ERROR 1, "All done"
  540
  550END
  560
  570DEFPROCcheck(N%,START%,FINISH%, report%)
  580LOCAL l%, rnd%
  590PROCasstst(N%):REM produce the code then test it!
  600
  610IF report%>50 rnd%=TRUE:report%-=100 ELSE rnd%=FALSE
  620IF report% < 1 PRINT ;", ";FNnstr(N%);
  630IF report% =-1 PRINT
  640IF report%=1 THEN
  650  PRINT"Checking division by &";~N%;" = ";N%
  660  l% =(aft%-fore%)/4
  670  PRINT"Using code, length ";l%;" instructions:"
  680  PROCdis(fore%, aft%)
  690ENDIF
  700IF report%=2 PRINT"Further checks for ";FNnstr(N%);
  710
  720IF rnd% A%=RND(-1)
  730FOR F%=START% TO FINISH% STEP 1
  740  IF rnd% THEN
  750    IF RND(2)=1 C%=RND(&7FFFFFFF)-&40000000 ELSE C%=RND(&0007FFFF)-&00040000
  760  ELSE
  770    C%=F%
  780  ENDIF
  790  A%=USR(code%):B%=!r%
  800  D%=C% DIV N%:E%=C% MOD N%
  810  IF (A%<>D%)OR(B%<>E%) THEN
  820     PRINT"Error Found: ";~C%;" DIV ";~N%;"=";~A%;" ";
  830     PRINT;~C%;" MOD ";~N%;"=";~B%;" should be ";~D%;" and ";~E%
  840     IF spool%=FALSE G=GET
  850  ENDIF
  860NEXT
  870ENDPROC
  880
  890DEFPROCasstst(n%)
  900r0=0:r1=1:r2=2:r3=3:r4=4:r5=5:lr=14
  910
  920REM require workReg if n% can't be expressed as a valid immediate const
  930workR=r4
  940
  950signpresR=r3
  960
  970FOR pass%=0 TO 2 STEP 2
  980P%=code%
  990[          OPT pass%
 1000.fore%     OPT FNFastDiv(r0,r1,r2,n%,signpresR,workR,pass%)
 1010.aft%      STR r1,r%
 1020           MOV pc,lr
 1030.r%        EQUD 0
 1040]
 1050NEXT
 1060ENDPROC
 1070
 1080REMFast Divide
 1090REM-----------
 1100DEFFNFastDiv(outq%,outr%,num%,const%,signpres%,work%,pass%)
 1110LOCAL n%
 1120REM To not pass, signpres, use -1 instead of valid register const.
 1130
 1140IF const%=0 THEN PRINT"FastDiv:Attempt to code division by ZERO !":STOP
 1150
 1160REM Preserve the sign of const%
 1170IF const%<0 THEN nsignpres=-1:const%=-const% ELSE nsignpres=+1
 1180power_of_2 =FNpowerof2(const%)
 1190IF FNimop2(const%)<>-1 THEN work%=-1 :REM if can be represented as an immediate constant, no need for work% register
 1200
 1210IF FNInvReg(outq%) OR FNInvReg(outr%) OR FNInvReg(num%) THEN
 1220  PRINT "FastDiv:Invalid Register":STOP
 1230ENDIF
 1240IF outq%=outr% OR outq%=num% OR num%=outr% THEN
 1250  PRINT"FastDiv:q,r,num registers Must be different":STOP
 1260ENDIF
 1270IF outq%=signpres% OR outr%=signpres% OR num%=signpres% THEN
 1280  IF signpres%<>-1 THEN PRINT"FastDiv:Invalid signpres register":STOP
 1290ENDIF
 1300IF outq%=work% OR outr%=work% OR num%=work% OR signpres%=work% THEN
 1310  IF work%<>-1 THEN PRINT"FastDiv:Invalid work register":STOP
 1320ENDIF
 1330
 1340IF const%=1 THEN
 1350  IF nsignpres=+1 THEN
 1360   [OPT pass%
 1370    MOV outr%, #0
 1380    MOV outq%, num%
 1390   ]
 1400  ELSE
 1410   [OPT pass%
 1420    MOV outr%, #0
 1430    RSB outq%, num%, #0
 1440   ]
 1450  ENDIF
 1460=pass%
 1470ENDIF
 1480
 1490REM set bit31 of this reg to NOT(sign of num%)
 1500IF NOT FNInvReg(signpres%) THEN
 1510    [OPT pass%
 1520     ANDS signpres%,num%,#&80000000 ; save sign of num
 1530     RSBNE num%,num%,#0; make num positive
 1540    ]
 1550ENDIF
 1560
 1570REM Carry out Fast Integer Division
 1580IF const%=(1<<power_of_2) THEN
 1590  REM division by a power of 2
 1600  [OPT pass%
 1610   MOV outq%,num%,lsr #power_of_2
 1620   SUB outr%,num%,outq%,lsl #power_of_2
 1630  ]
 1640ELSE
 1650
 1660  subflag%=FALSE
 1670
 1680  IF NOT FNInvReg(work%) THEN
 1690    [OPT FNmegamov(work%, const%, pass%)
 1700    ]
 1710  ENDIF
 1720
 1730  npower_of_2=power_of_2
 1740  const%=const%>>npower_of_2
 1750
 1760  t1%=1:s%=0:m%=0
 1770  WHILE (t1%<>0) AND (m%<=32)
 1780    IF (t1%>=const%) THEN t1%=t1%-const%:s%+=1
 1790    IF (t1%<>0) THEN t1%=(t1%<<1)+1:s%=s%<<1:m%=m%+1
 1800  ENDWHILE
 1810  t1%=FNpowerof2(s%)
 1820  power_of_2=power_of_2 - t1%
 1830  s%=s% >> t1%
 1840  IF s%=1 THEN
 1850    REM MOV outq%,num% (done by joining with next instruction!)
 1860  ELSE
 1870    [OPT FNFastDivAid(outq%,num%,s%,pass%)
 1880    ]
 1890  ENDIF
 1900  ls%=FNbitpatlen(s%):REM calc:ls (len:s):2^(ls-1)<= s <2^(ls),ls<=m
 1910  t1%=m%+1:REM generate code for sssss.... to 32 bits
 1920  WHILE t1%<32
 1930    IF s%=1 THEN
 1940      s%=0
 1950      [OPT pass%
 1960       ADD outq%,num%,num%,LSR #t1%
 1970      ]
 1980    ELSE
 1990      [OPT pass%
 2000       ADD outq%,outq%,outq%,LSR #t1%
 2010      ]
 2020    ENDIF
 2030    t1%=t1%*2
 2040  ENDWHILE
 2050  IF s%=1 THEN
 2060    REM Used by some large divisors (eg &7ffffff1)
 2070    [OPT pass%
 2080     MOV outq%, num%
 2090    ]
 2100  ENDIF
 2110  power_of_2=power_of_2+m%-ls%+2
 2120  IF power_of_2 <>0 THEN
 2130    [OPT pass%
 2140     MOV outq%,outq%,LSR #power_of_2 ;gen final shift
 2150    ]
 2160  ENDIF
 2170  IF const%=1 THEN PRINT"FastDiv:Sorry Program Error 1, please report":STOP
 2180  [OPT FNFastMul(outr%,outq%,const%,pass%)
 2190  ]
 2200  const%=const% << npower_of_2
 2210  IF npower_of_2 <>0 THEN
 2220    [OPT pass%
 2230     SUBS outr%,num%,outr%,LSL# npower_of_2
 2240    ]
 2250  ELSE
 2260    [OPT pass%
 2270     SUBS outr%,num%,outr%
 2280    ]
 2290  ENDIF
 2300  IF FNInvReg(work%) THEN
 2310    IF subflag% THEN
 2320      [OPT pass%
 2330       SUBMI outq%,outq%,#1
 2340       ADDMI outr%,outr%,#const%
 2350      ]
 2360    ENDIF
 2370    [OPT pass%
 2380     CMP outr%,#const%
 2390     ADDGE outq%,outq%,#1
 2400     SUBGE outr%,outr%,#const%
 2410    ]
 2420  ELSE
 2430    IF subflag% THEN
 2440      [OPT pass%
 2450       SUBMI outq%,outq%,#1
 2460       ADDMI outr%,outr%,work%
 2470      ]
 2480    ENDIF
 2490    [OPT pass%
 2500     CMP outr%,work%
 2510     ADDGE outq%,outq%,#1
 2520     SUBGE outr%,outr%,work%
 2530    ]
 2540  ENDIF
 2550ENDIF
 2560
 2570REM change sign of answer if const%<0 at start
 2580IF FNInvReg(signpres%) THEN
 2590  IF (nsignpres=-1) THEN
 2600    [OPT pass%
 2610     RSB outq%,outq%,#0
 2620    ]
 2630  ENDIF
 2640ELSE
 2650  [OPT pass%
 2660   TEQS signpres%,#&80000000 ; get stored sign
 2670   RSBEQ num%,num%,#0; remove if don't want to preserve original no.
 2680   RSBEQ outr%,outr%,#0
 2690  ]
 2700  IF (nsignpres=-1) THEN
 2710    [OPT pass%
 2720     RSBNE outq%,outq%,#0
 2730    ]
 2740  ELSE
 2750    [OPT pass%
 2760     RSBEQ outq%,outq%,#0
 2770    ]
 2780  ENDIF
 2790ENDIF
 2800
 2810=pass%
 2820
 2830REMFast Divide Aider:- For Working details see h.FastDiv
 2840REM-----------------
 2850DEFFNFastDivAid(Rb,Ra,const%,pass%)
 2860REM
 2870LOCAL n%,ls%
 2880LOCAL divinst$
 2890IF const% = 1 OR const%=0:PRINT"FastDivAid:Logic error 1, can't by 1 or 0":STOP
 2900IF const%<0 THEN ERROR 0,"FastDivAid:Logic error 2 found"
 2910IF Rb=Ra THEN PRINT"FastDivAid:Registers Must be different":STOP
 2920IF FNInvReg(Rb) OR FNInvReg(Ra) THEN PRINT "FastDivAid:Invalid Register":STOP
 2930
 2940REM Find the length of bit pattern s, from the first 1
 2950ls%=FNbitpatlen(const%)
 2960
 2970CASE (const% AND 3) OF
 2980WHEN 0,2:REM ie sb of form s = s1 * 2^n, n>1
 2990  PRINT "FastDivAid:Program logic error 3":STOP
 3000WHEN 1:  REM ie s of form s = s1 * 2^n +1, s1 odd, n>1
 3010  const%-=1
 3020  divinst$="ADD"
 3030WHEN 3:REM ie s of form s = s1 * 2^n -1, s1 odd, n>1
 3040  const%+=1
 3050  divinst$="SUB"
 3060  subflag%=TRUE
 3070ENDCASE
 3080const%=const% >>> FNpowerof2(const%)
 3090IF const%=1 THEN
 3100  IF (divinst$="SUB") THEN
 3110    IF ls%<=1 THEN PRINT"FastDivAid:Logic Error 4":STOP
 3120    [OPT pass%
 3130     ADD Rb,Ra,Ra            ;<---FASTDIVaid Gen
 3140     SUB Rb,Rb,Ra,LSR#ls% -1 ;<---FASTDIVaid Gen
 3150    ]
 3160  ELSE
 3170    [OPT pass%
 3180     ADD Rb,Ra,Ra, LSR #ls%-1 ;<---FASTDIVaid Gen
 3190    ]
 3200  ENDIF
 3210ELSE
 3220  IF (divinst$="SUB") THEN
 3230    [OPT FNFastDivAid(Rb,Ra,const%,pass%)
 3240     SUB Rb,Rb,Ra, LSR #ls%-1 ;<---FASTDIVaid Gen
 3250    ]
 3260  ELSE
 3270    [OPT FNFastDivAid(Rb,Ra,const%,pass%)
 3280     ADD Rb,Rb,Ra, LSR #ls%-1 ;<---FASTDIVaid Gen
 3290    ]
 3300  ENDIF
 3310ENDIF
 3320
 3330=pass%
 3340
 3350REMFast Multiply
 3360REM--------------
 3370REM//initialise macro with
 3380REM//registers: result ,number to be multiplied by constant
 3390REM//followed by: the constant you wish to fast multiply by
 3400REM// generates code to solve to get Rb=Ra * s
 3410REM//when Ra,Rb are registers and  s=constant to multiply by
 3420REM//if s=0 or s=1 macro aborts !!!! (Try MOV Rb,Ra or MOV Rb,#0 !!)
 3430REM//Comment: Ra is preserved after the code
 3440REM//Order of components to use just like a standard instruction !
 3450
 3460DEFFNFastMul(Rb,Ra,const%,pass%)
 3470REM Generate instructions for fast multiply Rb=Ra * const%
 3480LOCAL n%
 3490IF const%=1 OR const%=0:PRINT"FastMul:Silly FastMul by 1 or 0":STOP
 3500IF Rb=Ra THEN PRINT"FastMul:Registers Must be different":STOP
 3510IF FNInvReg(Rb) OR FNInvReg(Ra) THEN PRINT "FastMul:Invalid Register":STOP
 3520CASE (const% AND 3) OF
 3530WHEN 0,2:REM const% of form s1 * 2^n, n>1
 3540  n%=FNpowerof2(const%)
 3550  const%=const%/(1<<n%)
 3560  IF const%=1 THEN
 3570    [OPT pass%
 3580    MOV Rb,Ra, LSL #n%;<------FAST MUL generated
 3590    ]
 3600  ELSE
 3610    [OPT FNFastMul(Rb,Ra,const%,pass%)
 3620    MOV Rb,Rb, LSL #n%;<------FAST MUL generated
 3630    ]
 3640  ENDIF
 3650WHEN 1:REM const% of form s1 * 2^n +1, s1 odd, n>1
 3660  const%=const%-1
 3670  n%=FNpowerof2(const%)
 3680  const%=const%/(1<<n%)
 3690  IF const%=1 THEN
 3700    [OPT pass%
 3710    ADD Rb,Ra,Ra, LSL #n%;<------FAST MUL generated
 3720    ]
 3730  ELSE
 3740    [OPT FNFastMul(Rb,Ra,const%,pass%)
 3750    ADD Rb,Ra,Rb, LSL #n%;<------FAST MUL generated
 3760    ]
 3770  ENDIF
 3780WHEN 3:REM const% of form s1 * 2^n -1, s1 odd, n>1
 3790  const%=const%+1
 3800  n%=FNpowerof2(const%)
 3810  const%=const%/(1<<n%)
 3820  IF const%=1 THEN
 3830    [OPT pass%
 3840    RSB Rb,Ra,Ra, LSL #n%;<------FAST MUL generated
 3850    ]
 3860  ELSE
 3870    [OPT FNFastMul(Rb,Ra,const%,pass%)
 3880    RSB Rb,Ra,Rb, LSL #n%;<------FAST MUL generated
 3890    ]
 3900  ENDIF
 3910ENDCASE
 3920=pass%
 3930
 3940REM Find length of bit pattern from first 1 to bit 0 position
 3950DEFFNbitpatlen(S%)
 3960LOCAL Scopy%,ls%
 3970Scopy%=S%
 3980ls%=0
 3990WHILE Scopy%<>0
 4000  Scopy%=Scopy%>>>1
 4010  ls%+=1
 4020ENDWHILE
 4030=ls%
 4040
 4050
 4060REM Find highest power of 2 which divides n
 4070DEFFNpowerof2(N%)
 4080LOCAL n%
 4090IF N%=0 THEN =0:REM possible error
 4100n%=0
 4110WHILE (N% AND 1)=0:n%+=1:N%=N%>>>1:ENDWHILE
 4120=n%
 4130
 4140REM Check out registers
 4150DEFFNInvReg(reg)
 4160=(reg<0 OR reg>12) :REM Unsensible registers
 4170
 4180REM Decompose argument into machine code immediate value operand 2
 4190REM if possible, else return -1.
 4200REM IE into an 8 bit chunk 'Imm' & a 4 bit rotation 'Rotate', st
 4210REM 12 bit          operand = Rotate<<8 + Imm,
 4220REM where original argument = Imm rotated right by (2*Rotate).
 4230DEF FNimop2(a%)
 4240LOCAL i%, r%
 4250r%=0
 4260FOR i%=0 TO 30 STEP 2
 4270IF (a% AND NOT 255)=0 THEN = r%ORa%
 4280a% = (a%>>>30) OR (a%<<2) :REM ie rot left 2
 4290r%+= 256
 4300NEXT
 4310= -1
 4320
 4330REM Recall in MOV Rn, #v%, there is a restriction on permitted v%.
 4340REM Following function assembles a multi-instruction mov capable
 4350REM of taking any 32-bit v%.
 4360REM Aim is to achieve this using as few instructions as possible
 4370REM for each value of v% (never need more than 4, of course).
 4380REM
 4390REM - Well, actually following isn't quite optimal:
 4400REM It looks for the longest sequence of zero bits, & then splits
 4410REM rest into 8 bit chunks assigning first using MOV & each
 4420REM subsequent non-zero one using ORR.
 4430REM If you were to repeat algo below, but looking for long seq
 4440REM of 1's instead of zeros, & used a  similar process to below to
 4450REM build mov using MVN & BIC to specify 0's (instead of MOV & ORR
 4460REM to specify 1's), this would in some cases yield better soln.
 4470REM So, ideally do both & pick best.
 4480REM NB That still wouldn't be optimal, but it might be close.
 4490REM
 4500REM Anyone know of a better way?
 4510REM
 4520DEF FNmegamov(a%, v%, pass%)
 4530LOCAL i%, m%, r%, mi%, ml%, li%
 4540IF v%=0 THEN
 4550 [OPT pass%
 4560  MOV a%, #0
 4570 ]
 4580 = pass%
 4590ENDIF
 4600r%=0 :REM Now need to find the longest span of zeros, allowing bit wrap from b0 to b31
 4610WHILE (v%AND1)=0 :REM rotate to get a 1 into b0
 4620 v% = (v%>>>31) OR (v%<<1)
 4630 r%+= 1
 4640ENDWHILE
 4650i%=0
 4660m%=1
 4670ml%=0 :REM Length of longest sequence of zeros
 4680REPEAT
 4690 REPEAT :REM scan till get zero or all bits checked
 4700  i%+= 1
 4710  m% = m%<<1
 4720 UNTIL (i%>31) OR ((v%ANDm%)=0)
 4730 IF (i%<32) THEN
 4740  li% = i% :REM start of a zero sequence
 4750  REPEAT
 4760   i%+= 1
 4770   m% = m%<<1
 4780  UNTIL (i%>31) OR ((v%ANDm%)<>0)
 4790  IF (i%-li%)>ml% THEN mi%=li%:ml%=i%-li% :REM start of longest zero sequence so far
 4800 ENDIF
 4810UNTIL i%>31
 4820IF ml%>0 THEN
 4830 REM shift to get zero sequence in most significant bits of v%
 4840 i% = 32-(mi%+ml%)
 4850 v% = (v%>>>(32-i%)) OR (v%<<i%)
 4860 r%+= i%
 4870ENDIF
 4880IF r%AND1 THEN
 4890 REM r% must be even
 4900 v% = (v%>>>31) OR (v%<<1)
 4910 r%+= 1
 4920ENDIF
 4930
 4940REM now do the move, at last!
 4950i% = v%AND255
 4960[OPT pass%
 4970 MOV a%, #(i%>>>r%) OR (i%<<(32-r%)) :REM ie i% ror r%
 4980]
 4990REPEAT
 5000 v% = v%>>>8
 5010 IF (v%=0) THEN = pass%
 5020 r% = 31 AND (r%-8)
 5030 i% = v%AND255
 5040 IF i% THEN
 5050  [OPT pass%
 5060   ORR a%, a%, #(i%>>>r%) OR (i%<<(32-r%))
 5070  ]
 5080 ENDIF
 5090UNTIL FALSE
 5100= pass%
 5110
 5120DEF PROCdis(a%, b%)
 5130LOCAL q%, w%, q$, i%
 5140FOR q%=a% TO b%-1 STEP 4
 5150 SYS &40380, !q%, q% TO ,x%,y%
 5160 q$=""
 5170 FOR w%=x% TO x%+y%-1
 5180  q$+=CHR$(?w%)
 5190 NEXT
 5200 i% = INSTR(q$, ";")
 5210 IF i%>1 THEN
 5220  FOR w%=i%-1 TO 1 STEP -1
 5230   IF MID$(q$, w%, 1) <> " " THEN
 5240    q$ = LEFT$(q$, w%)
 5250    w%=0
 5260   ENDIF
 5270  NEXT
 5280 ENDIF
 5290 PRINT q$
 5300NEXT
 5310ENDPROC
 5320
 5330DEF FNnstr(n%)
 5340IF ABS(n%)<65536 THEN
 5350 = STR$(n%)
 5360ELSE
 5370 = "&"+STR$~(n%)
 5380ENDIF
 5390
 5400DEF PROCerr
 5410ON ERROR OFF
 5420REPORT:PRINT" with code: ";ERL/10
 5430IF spool% THEN
 5440 *Spool
 5450 spool%=FALSE
 5460 OSCLI("SetType "+spoolpath$+" Text")
 5470ENDIF
 5480ENDPROC

� >FASTDIVbsc
*� Fast DIV/MOD  with a constant number
8� code fragment  to test fastdiv/mod code generation
(� Author: Samuel K.R. Smith
27� Heavily MODIFIED by Michael Rozdoba, February '95
<(� (fixes & additional modifications)
F
P
�:�err:�
Z� 0
d
nspoolpath$ = "FDdemo"
xspool%=�
�#� spool% �("Spool "+spoolpath$)
�
�D� '"Fast Integer Division Code for arbitrary CONSTANT Divisor -"
�� "Compilation & testing:"'
�R� "This program lists the divisors it is testing & disassembles each routine,"
�J� "each of which calculates R0 = R2 DIV divisor, R1 = R2 MOD divisor."
�O� "If it finds an error it prints the details and waits for a key press."''
�
�� code% &400
�r0=0:r1=1:r2=2:r3=3
�
�Q%=1000
�R%=&7FFFFFFF-Q%
S%=&80000000+Q%
&maxc%=0: nmaxc%=0: totc%=0: cnt%=0

"Zbase%=1
,Zrange%=100000
6
@
Z%=Zbase%
J�
T  �check( Z%,-Q%,Q%, 1)
^  �check(-Z%,-Q%,Q%, 2)
h!  �check( Z%,R%,&7FFFFFFF, 0)
r!  �check(-Z%,R%,&7FFFFFFF, 0)
|!  �check( Z%,&80000000,S%, 0)
�!  �check(-Z%,&80000000,S%, 0)
�  �check( Z%,-Q%,Q%, 100+0)
�  �check(-Z%,-Q%,Q%, 100-1)
�  cnt% += 1
�  l% =(aft%-fore%)/4
�  totc% += l%
�  � l%>maxc% �
�    maxc% = l%
�    nmaxc%= Z%
�  �
�R  �"Current max code length ";maxc%;" instructions for divisor ";�nstr(nmaxc%)
�:  �"Average code length ";totc%/cnt%;" instructions"''
�	Z%+=1
� Z%=Zbase%+Zrange%
� 1, "All done"

&�
0
:'��check(N%,START%,FINISH%, report%)
D� l%, rnd%
N0�asstst(N%):� produce the code then test it!
X
b-� report%>50 rnd%=�:report%-=100 � rnd%=�
l$� report% < 1 � ;", ";�nstr(N%);
v� report% =-1 �
�� report%=1 �
�,  �"Checking division by &";~N%;" = ";N%
�  l% =(aft%-fore%)/4
�0  �"Using code, length ";l%;" instructions:"
�  �dis(fore%, aft%)
��
�1� report%=2 �"Further checks for ";�nstr(N%);
�
�� rnd% A%=�(-1)
�� F%=START% � FINISH% � 1
�  � rnd% �
�F    � �(2)=1 C%=�(&7FFFFFFF)-&40000000 � C%=�(&0007FFFF)-&00040000
�  �

    C%=F%
  �
  A%=�(code%):B%=!r%
   D%=C% � N%:E%=C% � N%
*  � (A%<>D%)�(B%<>E%) �
46     �"Error Found: ";~C%;" DIV ";~N%;"=";~A%;" ";
>@     �;~C%;" MOD ";~N%;"=";~B%;" should be ";~D%;" and ";~E%
H     � spool%=� G=�
R  �
\�
f�
p
z��asstst(n%)
�'r0=0:r1=1:r2=2:r3=3:r4=4:r5=5:lr=14
�
�I� require workReg if n% can't be expressed as a valid immediate const
�workR=r4
�
�signpresR=r3
�
�� pass%=0 � 2 � 2
�P%=code%
�[          OPT pass%
�>.fore%     OPT �FastDiv(r0,r1,r2,n%,signpresR,workR,pass%)
�.aft%      STR r1,r%
�           MOV pc,lr
.r%        EQUD 0
]
�
$�
.
8�Fast Divide
B�-----------
L<ݤFastDiv(outq%,outr%,num%,const%,signpres%,work%,pass%)
V� n%
`D� To not pass, signpres, use -1 instead of valid register const.
j
t@� const%=0 � �"FastDiv:Attempt to code division by ZERO !":�
~
�!� Preserve the sign of const%
�;� const%<0 � nsignpres=-1:const%=-const% � nsignpres=+1
�!power_of_2 =�powerof2(const%)
�q� �imop2(const%)<>-1 � work%=-1 :� if can be represented as an immediate constant, no need for work% register
�
�7� �InvReg(outq%) � �InvReg(outr%) � �InvReg(num%) �
�$  � "FastDiv:Invalid Register":�
��
�-� outq%=outr% � outq%=num% � num%=outr% �
�6  �"FastDiv:q,r,num registers Must be different":�
��
�:� outq%=signpres% � outr%=signpres% � num%=signpres% �
>  � signpres%<>-1 � �"FastDiv:Invalid signpres register":�

�
@� outq%=work% � outr%=work% � num%=work% � signpres%=work% �
6  � work%<>-1 � �"FastDiv:Invalid work register":�
(�
2
<� const%=1 �
F  � nsignpres=+1 �
P   [OPT pass%
Z    MOV outr%, #0
d    MOV outq%, num%
n   ]
x  �
�   [OPT pass%
�    MOV outr%, #0
�    RSB outq%, num%, #0
�   ]
�  �
�
=pass%
��
�
�0� set bit31 of this reg to NOT(sign of num%)
�� � �InvReg(signpres%) �
�    [OPT pass%
�8     �S signpres%,num%,#&80000000 ; save sign of num
�.     RSBNE num%,num%,#0; make num positive
	    ]
�

"%� Carry out Fast Integer Division
,� const%=(1<<power_of_2) �
6   � division by a power of 2
@  [OPT pass%
J%   MOV outq%,num%,lsr #power_of_2
T+   SUB outr%,num%,outq%,lsl #power_of_2
^  ]
h�
r
|  subflag%=�
�
�  � � �InvReg(work%) �
�+    [OPT �megamov(work%, const%, pass%)
�	    ]
�  �
�
�  npower_of_2=power_of_2
�   const%=const%>>npower_of_2
�
�  t1%=1:s%=0:m%=0
�  ȕ (t1%<>0) � (m%<=32)
�.    � (t1%>=const%) � t1%=t1%-const%:s%+=1
�4    � (t1%<>0) � t1%=(t1%<<1)+1:s%=s%<<1:m%=m%+1
  �
  t1%=�powerof2(s%)
!  power_of_2=power_of_2 - t1%
&  s%=s% >> t1%
0  � s%=1 �
:A    � MOV outq%,num% (done by joining with next instruction!)
D  �
N-    [OPT �FastDivAid(outq%,num%,s%,pass%)
X	    ]
b  �
lE  ls%=�bitpatlen(s%):� calc:ls (len:s):2^(ls-1)<= s <2^(ls),ls<=m
v7  t1%=m%+1:� generate code for sssss.... to 32 bits
�  ȕ t1%<32
�    � s%=1 �
�      s%=0
�      [OPT pass%
�'       ADD outq%,num%,num%,LSR #t1%
�      ]
�	    �
�      [OPT pass%
�)       ADD outq%,outq%,outq%,LSR #t1%
�      ]
�	    �
�    t1%=t1%*2
�  �
  � s%=1 �
4    � Used by some large divisors (eg &7ffffff1)
    [OPT pass%
      MOV outq%, num%
*	    ]
4  �
>$  power_of_2=power_of_2+m%-ls%+2
H  � power_of_2 <>0 �
R    [OPT pass%
\9     MOV outq%,outq%,LSR #power_of_2 ;gen final shift
f	    ]
p  �
zD  � const%=1 � �"FastDiv:Sorry Program Error 1, please report":�
�-  [OPT �FastMul(outr%,outq%,const%,pass%)
�  ]
�"  const%=const% << npower_of_2
�  � npower_of_2 <>0 �
�    [OPT pass%
�/     SUBS outr%,num%,outr%,LSL# npower_of_2
�	    ]
�  �
�    [OPT pass%
�     SUBS outr%,num%,outr%
�	    ]
�  �
�  � �InvReg(work%) �
	    � subflag% �
	      [OPT pass%
	       SUBMI outq%,outq%,#1
	$$       ADDMI outr%,outr%,#const%
	.      ]
	8	    �
	B    [OPT pass%
	L     CMP outr%,#const%
	V     ADDGE outq%,outq%,#1
	`"     SUBGE outr%,outr%,#const%
	j	    ]
	t  �
	~    � subflag% �
	�      [OPT pass%
	�       SUBMI outq%,outq%,#1
	�"       ADDMI outr%,outr%,work%
	�      ]
	�	    �
	�    [OPT pass%
	�     CMP outr%,work%
	�     ADDGE outq%,outq%,#1
	�      SUBGE outr%,outr%,work%
	�	    ]
	�  �
	��


0� change sign of answer if const%<0 at start
� �InvReg(signpres%) �
  � (nsignpres=-1) �
(    [OPT pass%
2     RSB outq%,outq%,#0
<	    ]
F  �
P�
Z  [OPT pass%
d2   TEQS signpres%,#&80000000 ; get stored sign
nH   RSBEQ num%,num%,#0; remove if don't want to preserve original no.
x   RSBEQ outr%,outr%,#0
�  ]
�  � (nsignpres=-1) �
�    [OPT pass%
�     RSBNE outq%,outq%,#0
�	    ]
�  �
�    [OPT pass%
�     RSBEQ outq%,outq%,#0
�	    ]
�  �
��
�
�
=pass%

:�Fast Divide Aider:- For Working details see h.FastDiv
�-----------------
"$ݤFastDivAid(Rb,Ra,const%,pass%)
,�
6� n%,ls%
@� divinst$
JJ� const% = 1 � const%=0:�"FastDivAid:Logic error 1, can't by 1 or 0":�
T5� const%<0 � � 0,"FastDivAid:Logic error 2 found"
^9� Rb=Ra � �"FastDivAid:Registers Must be different":�
hC� �InvReg(Rb) � �InvReg(Ra) � � "FastDivAid:Invalid Register":�
r
|8� Find the length of bit pattern s, from the first 1
�ls%=�bitpatlen(const%)
�
�Ȏ (const% � 3) �
�+� 0,2:� ie sb of form s = s1 * 2^n, n>1
�,  � "FastDivAid:Program logic error 3":�
�5� 1:  � ie s of form s = s1 * 2^n +1, s1 odd, n>1
�  const%-=1
�  divinst$="ADD"
�3� 3:� ie s of form s = s1 * 2^n -1, s1 odd, n>1
�  const%+=1
�  divinst$="SUB"
�  subflag%=�
��
'const%=const% >>> �powerof2(const%)
� const%=1 �
  � (divinst$="SUB") �
&0    � ls%<=1 � �"FastDivAid:Logic Error 4":�
0    [OPT pass%
:4     ADD Rb,Ra,Ra            ;<---FASTDIVaid Gen
D4     SUB Rb,Rb,Ra,LSR#ls% -1 ;<---FASTDIVaid Gen
N	    ]
X  �
b    [OPT pass%
l5     ADD Rb,Ra,Ra, LSR #ls%-1 ;<---FASTDIVaid Gen
v	    ]
�  �
��
�  � (divinst$="SUB") �
�,    [OPT �FastDivAid(Rb,Ra,const%,pass%)
�5     SUB Rb,Rb,Ra, LSR #ls%-1 ;<---FASTDIVaid Gen
�	    ]
�  �
�,    [OPT �FastDivAid(Rb,Ra,const%,pass%)
�5     ADD Rb,Rb,Ra, LSR #ls%-1 ;<---FASTDIVaid Gen
�	    ]
�  �
��
�


=pass%



�Fast Multiply

 �--------------

*�//initialise macro with

4=�//registers: result ,number to be multiplied by constant

>=�//followed by: the constant you wish to fast multiply by

H0�// generates code to solve to get Rb=Ra * s

R>�//when Ra,Rb are registers and  s=constant to multiply by

\F�//if s=0 or s=1 macro aborts !!!! (Try MOV Rb,Ra or MOV Rb,#0 !!)

f.�//Comment: Ra is preserved after the code

pD�//Order of components to use just like a standard instruction !

z

�!ݤFastMul(Rb,Ra,const%,pass%)

�<� Generate instructions for fast multiply Rb=Ra * const%

�� n%

�>� const%=1 � const%=0:�"FastMul:Silly FastMul by 1 or 0":�

�6� Rb=Ra � �"FastMul:Registers Must be different":�

�@� �InvReg(Rb) � �InvReg(Ra) � � "FastMul:Invalid Register":�

�Ȏ (const% � 3) �

�(� 0,2:� const% of form s1 * 2^n, n>1

�  n%=�powerof2(const%)

�  const%=const%/(1<<n%)

�  � const%=1 �

�    [OPT pass%

�4    MOV Rb,Ra, LSL #n%;<------FAST MUL generated
	    ]
  �
)    [OPT �FastMul(Rb,Ra,const%,pass%)
$4    MOV Rb,Rb, LSL #n%;<------FAST MUL generated
.	    ]
8  �
B1� 1:� const% of form s1 * 2^n +1, s1 odd, n>1
L  const%=const%-1
V  n%=�powerof2(const%)
`  const%=const%/(1<<n%)
j  � const%=1 �
t    [OPT pass%
~7    ADD Rb,Ra,Ra, LSL #n%;<------FAST MUL generated
�	    ]
�  �
�)    [OPT �FastMul(Rb,Ra,const%,pass%)
�7    ADD Rb,Ra,Rb, LSL #n%;<------FAST MUL generated
�	    ]
�  �
�1� 3:� const% of form s1 * 2^n -1, s1 odd, n>1
�  const%=const%+1
�  n%=�powerof2(const%)
�  const%=const%/(1<<n%)
�  � const%=1 �
�    [OPT pass%
7    RSB Rb,Ra,Ra, LSL #n%;<------FAST MUL generated

	    ]
  �
)    [OPT �FastMul(Rb,Ra,const%,pass%)
(7    RSB Rb,Ra,Rb, LSL #n%;<------FAST MUL generated
2	    ]
<  �
F�
P
=pass%
Z
d?� Find length of bit pattern from first 1 to bit 0 position
nݤbitpatlen(S%)
x� Scopy%,ls%
�
Scopy%=S%
�	ls%=0
�ȕ Scopy%<>0
�  Scopy%=Scopy%>>>1
�  ls%+=1
��
�=ls%
�
�
�-� Find highest power of 2 which divides n
�ݤpowerof2(N%)
�� n%
� � N%=0 � =0:� possible error
n%=0
#ȕ (N% � 1)=0:n%+=1:N%=N%>>>1:�
=n%
"
,� Check out registers
6ݤInvReg(reg)
@-=(reg<0 � reg>12) :� Unsensible registers
J
TD� Decompose argument into machine code immediate value operand 2
^"� if possible, else return -1.
hB� IE into an 8 bit chunk 'Imm' & a 4 bit rotation 'Rotate', st
r0� 12 bit          operand = Rotate<<8 + Imm,
|@� where original argument = Imm rotated right by (2*Rotate).
�� �imop2(a%)
�� i%, r%
�r%=0
�� i%=0 � 30 � 2
�� (a% � � 255)=0 � = r%�a%
�-a% = (a%>>>30) � (a%<<2) :� ie rot left 2
�r%+= 256
��
�= -1
�
�D� Recall in MOV Rn, #v%, there is a restriction on permitted v%.
�B� Following function assembles a multi-instruction mov capable
�� of taking any 32-bit v%.
B� Aim is to achieve this using as few instructions as possible
?� for each value of v% (never need more than 4, of course).
�
&5� - Well, actually following isn't quite optimal:
0C� It looks for the longest sequence of zero bits, & then splits
:=� rest into 8 bit chunks assigning first using MOV & each
D(� subsequent non-zero one using ORR.
N@� If you were to repeat algo below, but looking for long seq
XD� of 1's instead of zeros, & used a  similar process to below to
bD� build mov using MVN & BIC to specify 0's (instead of MOV & ORR
lB� to specify 1's), this would in some cases yield better soln.
v&� So, ideally do both & pick best.
�?� NB That still wouldn't be optimal, but it might be close.
��
�"� Anyone know of a better way?
��
�� �megamov(a%, v%, pass%)
�� i%, m%, r%, mi%, ml%, li%
�� v%=0 �
� [OPT pass%
�  MOV a%, #0
� ]
� = pass%
��
�Xr%=0 :� Now need to find the longest span of zeros, allowing bit wrap from b0 to b31
,ȕ (v%�1)=0 :� rotate to get a 1 into b0
 v% = (v%>>>31) � (v%<<1)
 r%+= 1
 �
*i%=0
4m%=1
>0ml%=0 :� Length of longest sequence of zeros
H�
R0 � :� scan till get zero or all bits checked
\  i%+= 1
f  m% = m%<<1
p � (i%>31) � ((v%�m%)=0)
z � (i%<32) �
�*  li% = i% :� start of a zero sequence
�  �
�
   i%+= 1
�   m% = m%<<1
�  � (i%>31) � ((v%�m%)<>0)
�R  � (i%-li%)>ml% � mi%=li%:ml%=i%-li% :� start of longest zero sequence so far
� �
�� i%>31
�
� ml%>0 �
�@ � shift to get zero sequence in most significant bits of v%
� i% = 32-(mi%+ml%)
�# v% = (v%>>>(32-i%)) � (v%<<i%)
� r%+= i%
�
� r%�1 �
 � r% must be even
$ v% = (v%>>>31) � (v%<<1)
. r%+= 1
8�
B
L� now do the move, at last!
Vi% = v%�255
`[OPT pass%
j7 MOV a%, #(i%>>>r%) � (i%<<(32-r%)) :� ie i% ror r%
t]
~�
� v% = v%>>>8
� � (v%=0) � = pass%
� r% = 31 � (r%-8)
� i% = v%�255
� � i% �
�  [OPT pass%
�,   �R a%, a%, #(i%>>>r%) � (i%<<(32-r%))
�  ]
� �
�� �
�= pass%
�
� �dis(a%, b%)

� q%, w%, q$, i%
� q%=a% � b%-1 � 4
  ș &40380, !q%, q% � ,x%,y%
(
 q$=""
2 � w%=x% � x%+y%-1
<  q$+=�(?w%)
F �
P i% = �q$, ";")
Z
 � i%>1 �
d  � w%=i%-1 � 1 � -1
n   � �q$, w%, 1) <> " " �
x    q$ = �q$, w%)
�    w%=0
�   �
�  �
� �
�	 � q$
��
��
�
�� �nstr(n%)
�� �(n%)<65536 �
� = �(n%)
��
� = "&"+�~(n%)
�


� �err
"	� � �
,�:�" with code: ";�/10
6� spool% �
@ *Spool
J
 spool%=�
T% �("SetType "+spoolpath$+" Text")
^�
h�
�
00000000  0d 00 0a 11 f4 20 3e 46  41 53 54 44 49 56 62 73  |..... >FASTDIVbs|
00000010  63 0d 00 14 2a f4 20 46  61 73 74 20 44 49 56 2f  |c...*. Fast DIV/|
00000020  4d 4f 44 20 20 77 69 74  68 20 61 20 63 6f 6e 73  |MOD  with a cons|
00000030  74 61 6e 74 20 6e 75 6d  62 65 72 0d 00 1e 38 f4  |tant number...8.|
00000040  20 63 6f 64 65 20 66 72  61 67 6d 65 6e 74 20 20  | code fragment  |
00000050  74 6f 20 74 65 73 74 20  66 61 73 74 64 69 76 2f  |to test fastdiv/|
00000060  6d 6f 64 20 63 6f 64 65  20 67 65 6e 65 72 61 74  |mod code generat|
00000070  69 6f 6e 0d 00 28 1f f4  20 41 75 74 68 6f 72 3a  |ion..(.. Author:|
00000080  20 53 61 6d 75 65 6c 20  4b 2e 52 2e 20 53 6d 69  | Samuel K.R. Smi|
00000090  74 68 0d 00 32 37 f4 20  48 65 61 76 69 6c 79 20  |th..27. Heavily |
000000a0  4d 4f 44 49 46 49 45 44  20 62 79 20 4d 69 63 68  |MODIFIED by Mich|
000000b0  61 65 6c 20 52 6f 7a 64  6f 62 61 2c 20 46 65 62  |ael Rozdoba, Feb|
000000c0  72 75 61 72 79 20 27 39  35 0d 00 3c 28 f4 20 28  |ruary '95..<(. (|
000000d0  66 69 78 65 73 20 26 20  61 64 64 69 74 69 6f 6e  |fixes & addition|
000000e0  61 6c 20 6d 6f 64 69 66  69 63 61 74 69 6f 6e 73  |al modifications|
000000f0  29 0d 00 46 04 0d 00 50  0d ee 85 3a f2 65 72 72  |)..F...P...:.err|
00000100  3a e0 0d 00 5a 07 eb 20  30 0d 00 64 04 0d 00 6e  |:...Z.. 0..d...n|
00000110  19 73 70 6f 6f 6c 70 61  74 68 24 20 3d 20 22 46  |.spoolpath$ = "F|
00000120  44 64 65 6d 6f 22 0d 00  78 0c 73 70 6f 6f 6c 25  |Ddemo"..x.spool%|
00000130  3d a3 0d 00 82 23 e7 20  73 70 6f 6f 6c 25 20 ff  |=....#. spool% .|
00000140  28 22 53 70 6f 6f 6c 20  22 2b 73 70 6f 6f 6c 70  |("Spool "+spoolp|
00000150  61 74 68 24 29 0d 00 8c  04 0d 00 96 44 f1 20 27  |ath$).......D. '|
00000160  22 46 61 73 74 20 49 6e  74 65 67 65 72 20 44 69  |"Fast Integer Di|
00000170  76 69 73 69 6f 6e 20 43  6f 64 65 20 66 6f 72 20  |vision Code for |
00000180  61 72 62 69 74 72 61 72  79 20 43 4f 4e 53 54 41  |arbitrary CONSTA|
00000190  4e 54 20 44 69 76 69 73  6f 72 20 2d 22 0d 00 a0  |NT Divisor -"...|
000001a0  1f f1 20 22 43 6f 6d 70  69 6c 61 74 69 6f 6e 20  |.. "Compilation |
000001b0  26 20 74 65 73 74 69 6e  67 3a 22 27 0d 00 aa 52  |& testing:"'...R|
000001c0  f1 20 22 54 68 69 73 20  70 72 6f 67 72 61 6d 20  |. "This program |
000001d0  6c 69 73 74 73 20 74 68  65 20 64 69 76 69 73 6f  |lists the diviso|
000001e0  72 73 20 69 74 20 69 73  20 74 65 73 74 69 6e 67  |rs it is testing|
000001f0  20 26 20 64 69 73 61 73  73 65 6d 62 6c 65 73 20  | & disassembles |
00000200  65 61 63 68 20 72 6f 75  74 69 6e 65 2c 22 0d 00  |each routine,"..|
00000210  b4 4a f1 20 22 65 61 63  68 20 6f 66 20 77 68 69  |.J. "each of whi|
00000220  63 68 20 63 61 6c 63 75  6c 61 74 65 73 20 52 30  |ch calculates R0|
00000230  20 3d 20 52 32 20 44 49  56 20 64 69 76 69 73 6f  | = R2 DIV diviso|
00000240  72 2c 20 52 31 20 3d 20  52 32 20 4d 4f 44 20 64  |r, R1 = R2 MOD d|
00000250  69 76 69 73 6f 72 2e 22  0d 00 be 4f f1 20 22 49  |ivisor."...O. "I|
00000260  66 20 69 74 20 66 69 6e  64 73 20 61 6e 20 65 72  |f it finds an er|
00000270  72 6f 72 20 69 74 20 70  72 69 6e 74 73 20 74 68  |ror it prints th|
00000280  65 20 64 65 74 61 69 6c  73 20 61 6e 64 20 77 61  |e details and wa|
00000290  69 74 73 20 66 6f 72 20  61 20 6b 65 79 20 70 72  |its for a key pr|
000002a0  65 73 73 2e 22 27 27 0d  00 c8 04 0d 00 d2 10 de  |ess."''.........|
000002b0  20 63 6f 64 65 25 20 26  34 30 30 0d 00 dc 17 72  | code% &400....r|
000002c0  30 3d 30 3a 72 31 3d 31  3a 72 32 3d 32 3a 72 33  |0=0:r1=1:r2=2:r3|
000002d0  3d 33 0d 00 e6 04 0d 00  f0 0b 51 25 3d 31 30 30  |=3........Q%=100|
000002e0  30 0d 00 fa 13 52 25 3d  26 37 46 46 46 46 46 46  |0....R%=&7FFFFFF|
000002f0  46 2d 51 25 0d 01 04 13  53 25 3d 26 38 30 30 30  |F-Q%....S%=&8000|
00000300  30 30 30 30 2b 51 25 0d  01 0e 26 6d 61 78 63 25  |0000+Q%...&maxc%|
00000310  3d 30 3a 20 6e 6d 61 78  63 25 3d 30 3a 20 74 6f  |=0: nmaxc%=0: to|
00000320  74 63 25 3d 30 3a 20 63  6e 74 25 3d 30 0d 01 18  |tc%=0: cnt%=0...|
00000330  04 0d 01 22 0c 5a 62 61  73 65 25 3d 31 0d 01 2c  |...".Zbase%=1..,|
00000340  12 5a 72 61 6e 67 65 25  3d 31 30 30 30 30 30 0d  |.Zrange%=100000.|
00000350  01 36 04 0d 01 40 0d 5a  25 3d 5a 62 61 73 65 25  |.6...@.Z%=Zbase%|
00000360  0d 01 4a 05 f5 0d 01 54  1b 20 20 f2 63 68 65 63  |..J....T.  .chec|
00000370  6b 28 20 5a 25 2c 2d 51  25 2c 51 25 2c 20 31 29  |k( Z%,-Q%,Q%, 1)|
00000380  0d 01 5e 1b 20 20 f2 63  68 65 63 6b 28 2d 5a 25  |..^.  .check(-Z%|
00000390  2c 2d 51 25 2c 51 25 2c  20 32 29 0d 01 68 21 20  |,-Q%,Q%, 2)..h! |
000003a0  20 f2 63 68 65 63 6b 28  20 5a 25 2c 52 25 2c 26  | .check( Z%,R%,&|
000003b0  37 46 46 46 46 46 46 46  2c 20 30 29 0d 01 72 21  |7FFFFFFF, 0)..r!|
000003c0  20 20 f2 63 68 65 63 6b  28 2d 5a 25 2c 52 25 2c  |  .check(-Z%,R%,|
000003d0  26 37 46 46 46 46 46 46  46 2c 20 30 29 0d 01 7c  |&7FFFFFFF, 0)..||
000003e0  21 20 20 f2 63 68 65 63  6b 28 20 5a 25 2c 26 38  |!  .check( Z%,&8|
000003f0  30 30 30 30 30 30 30 2c  53 25 2c 20 30 29 0d 01  |0000000,S%, 0)..|
00000400  86 21 20 20 f2 63 68 65  63 6b 28 2d 5a 25 2c 26  |.!  .check(-Z%,&|
00000410  38 30 30 30 30 30 30 30  2c 53 25 2c 20 30 29 0d  |80000000,S%, 0).|
00000420  01 90 1f 20 20 f2 63 68  65 63 6b 28 20 5a 25 2c  |...  .check( Z%,|
00000430  2d 51 25 2c 51 25 2c 20  31 30 30 2b 30 29 0d 01  |-Q%,Q%, 100+0)..|
00000440  9a 1f 20 20 f2 63 68 65  63 6b 28 2d 5a 25 2c 2d  |..  .check(-Z%,-|
00000450  51 25 2c 51 25 2c 20 31  30 30 2d 31 29 0d 01 a4  |Q%,Q%, 100-1)...|
00000460  0f 20 20 63 6e 74 25 20  2b 3d 20 31 0d 01 ae 18  |.  cnt% += 1....|
00000470  20 20 6c 25 20 3d 28 61  66 74 25 2d 66 6f 72 65  |  l% =(aft%-fore|
00000480  25 29 2f 34 0d 01 b8 11  20 20 74 6f 74 63 25 20  |%)/4....  totc% |
00000490  2b 3d 20 6c 25 0d 01 c2  12 20 20 e7 20 6c 25 3e  |+= l%....  . l%>|
000004a0  6d 61 78 63 25 20 8c 0d  01 cc 12 20 20 20 20 6d  |maxc% .....    m|
000004b0  61 78 63 25 20 3d 20 6c  25 0d 01 d6 12 20 20 20  |axc% = l%....   |
000004c0  20 6e 6d 61 78 63 25 3d  20 5a 25 0d 01 e0 07 20  | nmaxc%= Z%.... |
000004d0  20 cd 0d 01 ea 52 20 20  f1 22 43 75 72 72 65 6e  | ....R  ."Curren|
000004e0  74 20 6d 61 78 20 63 6f  64 65 20 6c 65 6e 67 74  |t max code lengt|
000004f0  68 20 22 3b 6d 61 78 63  25 3b 22 20 69 6e 73 74  |h ";maxc%;" inst|
00000500  72 75 63 74 69 6f 6e 73  20 66 6f 72 20 64 69 76  |ructions for div|
00000510  69 73 6f 72 20 22 3b a4  6e 73 74 72 28 6e 6d 61  |isor ";.nstr(nma|
00000520  78 63 25 29 0d 01 f4 3a  20 20 f1 22 41 76 65 72  |xc%)...:  ."Aver|
00000530  61 67 65 20 63 6f 64 65  20 6c 65 6e 67 74 68 20  |age code length |
00000540  22 3b 74 6f 74 63 25 2f  63 6e 74 25 3b 22 20 69  |";totc%/cnt%;" i|
00000550  6e 73 74 72 75 63 74 69  6f 6e 73 22 27 27 0d 01  |nstructions"''..|
00000560  fe 09 5a 25 2b 3d 31 0d  02 08 17 fd 20 5a 25 3d  |..Z%+=1..... Z%=|
00000570  5a 62 61 73 65 25 2b 5a  72 61 6e 67 65 25 0d 02  |Zbase%+Zrange%..|
00000580  12 13 85 20 31 2c 20 22  41 6c 6c 20 64 6f 6e 65  |... 1, "All done|
00000590  22 0d 02 1c 04 0d 02 26  05 e0 0d 02 30 04 0d 02  |"......&....0...|
000005a0  3a 27 dd f2 63 68 65 63  6b 28 4e 25 2c 53 54 41  |:'..check(N%,STA|
000005b0  52 54 25 2c 46 49 4e 49  53 48 25 2c 20 72 65 70  |RT%,FINISH%, rep|
000005c0  6f 72 74 25 29 0d 02 44  0e ea 20 6c 25 2c 20 72  |ort%)..D.. l%, r|
000005d0  6e 64 25 0d 02 4e 30 f2  61 73 73 74 73 74 28 4e  |nd%..N0.asstst(N|
000005e0  25 29 3a f4 20 70 72 6f  64 75 63 65 20 74 68 65  |%):. produce the|
000005f0  20 63 6f 64 65 20 74 68  65 6e 20 74 65 73 74 20  | code then test |
00000600  69 74 21 0d 02 58 04 0d  02 62 2d e7 20 72 65 70  |it!..X...b-. rep|
00000610  6f 72 74 25 3e 35 30 20  72 6e 64 25 3d b9 3a 72  |ort%>50 rnd%=.:r|
00000620  65 70 6f 72 74 25 2d 3d  31 30 30 20 8b 20 72 6e  |eport%-=100 . rn|
00000630  64 25 3d a3 0d 02 6c 24  e7 20 72 65 70 6f 72 74  |d%=...l$. report|
00000640  25 20 3c 20 31 20 f1 20  3b 22 2c 20 22 3b a4 6e  |% < 1 . ;", ";.n|
00000650  73 74 72 28 4e 25 29 3b  0d 02 76 13 e7 20 72 65  |str(N%);..v.. re|
00000660  70 6f 72 74 25 20 3d 2d  31 20 f1 0d 02 80 11 e7  |port% =-1 ......|
00000670  20 72 65 70 6f 72 74 25  3d 31 20 8c 0d 02 8a 2c  | report%=1 ....,|
00000680  20 20 f1 22 43 68 65 63  6b 69 6e 67 20 64 69 76  |  ."Checking div|
00000690  69 73 69 6f 6e 20 62 79  20 26 22 3b 7e 4e 25 3b  |ision by &";~N%;|
000006a0  22 20 3d 20 22 3b 4e 25  0d 02 94 18 20 20 6c 25  |" = ";N%....  l%|
000006b0  20 3d 28 61 66 74 25 2d  66 6f 72 65 25 29 2f 34  | =(aft%-fore%)/4|
000006c0  0d 02 9e 30 20 20 f1 22  55 73 69 6e 67 20 63 6f  |...0  ."Using co|
000006d0  64 65 2c 20 6c 65 6e 67  74 68 20 22 3b 6c 25 3b  |de, length ";l%;|
000006e0  22 20 69 6e 73 74 72 75  63 74 69 6f 6e 73 3a 22  |" instructions:"|
000006f0  0d 02 a8 17 20 20 f2 64  69 73 28 66 6f 72 65 25  |....  .dis(fore%|
00000700  2c 20 61 66 74 25 29 0d  02 b2 05 cd 0d 02 bc 31  |, aft%)........1|
00000710  e7 20 72 65 70 6f 72 74  25 3d 32 20 f1 22 46 75  |. report%=2 ."Fu|
00000720  72 74 68 65 72 20 63 68  65 63 6b 73 20 66 6f 72  |rther checks for|
00000730  20 22 3b a4 6e 73 74 72  28 4e 25 29 3b 0d 02 c6  | ";.nstr(N%);...|
00000740  04 0d 02 d0 13 e7 20 72  6e 64 25 20 41 25 3d b3  |...... rnd% A%=.|
00000750  28 2d 31 29 0d 02 da 1d  e3 20 46 25 3d 53 54 41  |(-1)..... F%=STA|
00000760  52 54 25 20 b8 20 46 49  4e 49 53 48 25 20 88 20  |RT% . FINISH% . |
00000770  31 0d 02 e4 0e 20 20 e7  20 72 6e 64 25 20 8c 0d  |1....  . rnd% ..|
00000780  02 ee 46 20 20 20 20 e7  20 b3 28 32 29 3d 31 20  |..F    . .(2)=1 |
00000790  43 25 3d b3 28 26 37 46  46 46 46 46 46 46 29 2d  |C%=.(&7FFFFFFF)-|
000007a0  26 34 30 30 30 30 30 30  30 20 8b 20 43 25 3d b3  |&40000000 . C%=.|
000007b0  28 26 30 30 30 37 46 46  46 46 29 2d 26 30 30 30  |(&0007FFFF)-&000|
000007c0  34 30 30 30 30 0d 02 f8  07 20 20 cc 0d 03 02 0d  |40000....  .....|
000007d0  20 20 20 20 43 25 3d 46  25 0d 03 0c 07 20 20 cd  |    C%=F%....  .|
000007e0  0d 03 16 18 20 20 41 25  3d ba 28 63 6f 64 65 25  |....  A%=.(code%|
000007f0  29 3a 42 25 3d 21 72 25  0d 03 20 1b 20 20 44 25  |):B%=!r%.. .  D%|
00000800  3d 43 25 20 81 20 4e 25  3a 45 25 3d 43 25 20 83  |=C% . N%:E%=C% .|
00000810  20 4e 25 0d 03 2a 1b 20  20 e7 20 28 41 25 3c 3e  | N%..*.  . (A%<>|
00000820  44 25 29 84 28 42 25 3c  3e 45 25 29 20 8c 0d 03  |D%).(B%<>E%) ...|
00000830  34 36 20 20 20 20 20 f1  22 45 72 72 6f 72 20 46  |46     ."Error F|
00000840  6f 75 6e 64 3a 20 22 3b  7e 43 25 3b 22 20 44 49  |ound: ";~C%;" DI|
00000850  56 20 22 3b 7e 4e 25 3b  22 3d 22 3b 7e 41 25 3b  |V ";~N%;"=";~A%;|
00000860  22 20 22 3b 0d 03 3e 40  20 20 20 20 20 f1 3b 7e  |" ";..>@     .;~|
00000870  43 25 3b 22 20 4d 4f 44  20 22 3b 7e 4e 25 3b 22  |C%;" MOD ";~N%;"|
00000880  3d 22 3b 7e 42 25 3b 22  20 73 68 6f 75 6c 64 20  |=";~B%;" should |
00000890  62 65 20 22 3b 7e 44 25  3b 22 20 61 6e 64 20 22  |be ";~D%;" and "|
000008a0  3b 7e 45 25 0d 03 48 17  20 20 20 20 20 e7 20 73  |;~E%..H.     . s|
000008b0  70 6f 6f 6c 25 3d a3 20  47 3d a5 0d 03 52 07 20  |pool%=. G=...R. |
000008c0  20 cd 0d 03 5c 05 ed 0d  03 66 05 e1 0d 03 70 04  | ...\....f....p.|
000008d0  0d 03 7a 10 dd f2 61 73  73 74 73 74 28 6e 25 29  |..z...asstst(n%)|
000008e0  0d 03 84 27 72 30 3d 30  3a 72 31 3d 31 3a 72 32  |...'r0=0:r1=1:r2|
000008f0  3d 32 3a 72 33 3d 33 3a  72 34 3d 34 3a 72 35 3d  |=2:r3=3:r4=4:r5=|
00000900  35 3a 6c 72 3d 31 34 0d  03 8e 04 0d 03 98 49 f4  |5:lr=14.......I.|
00000910  20 72 65 71 75 69 72 65  20 77 6f 72 6b 52 65 67  | require workReg|
00000920  20 69 66 20 6e 25 20 63  61 6e 27 74 20 62 65 20  | if n% can't be |
00000930  65 78 70 72 65 73 73 65  64 20 61 73 20 61 20 76  |expressed as a v|
00000940  61 6c 69 64 20 69 6d 6d  65 64 69 61 74 65 20 63  |alid immediate c|
00000950  6f 6e 73 74 0d 03 a2 0c  77 6f 72 6b 52 3d 72 34  |onst....workR=r4|
00000960  0d 03 ac 04 0d 03 b6 10  73 69 67 6e 70 72 65 73  |........signpres|
00000970  52 3d 72 33 0d 03 c0 04  0d 03 ca 15 e3 20 70 61  |R=r3......... pa|
00000980  73 73 25 3d 30 20 b8 20  32 20 88 20 32 0d 03 d4  |ss%=0 . 2 . 2...|
00000990  0c 50 25 3d 63 6f 64 65  25 0d 03 de 18 5b 20 20  |.P%=code%....[  |
000009a0  20 20 20 20 20 20 20 20  4f 50 54 20 70 61 73 73  |        OPT pass|
000009b0  25 0d 03 e8 3e 2e 66 6f  72 65 25 20 20 20 20 20  |%...>.fore%     |
000009c0  4f 50 54 20 a4 46 61 73  74 44 69 76 28 72 30 2c  |OPT .FastDiv(r0,|
000009d0  72 31 2c 72 32 2c 6e 25  2c 73 69 67 6e 70 72 65  |r1,r2,n%,signpre|
000009e0  73 52 2c 77 6f 72 6b 52  2c 70 61 73 73 25 29 0d  |sR,workR,pass%).|
000009f0  03 f2 18 2e 61 66 74 25  20 20 20 20 20 20 53 54  |....aft%      ST|
00000a00  52 20 72 31 2c 72 25 0d  03 fc 18 20 20 20 20 20  |R r1,r%....     |
00000a10  20 20 20 20 20 20 4d 4f  56 20 70 63 2c 6c 72 0d  |      MOV pc,lr.|
00000a20  04 06 15 2e 72 25 20 20  20 20 20 20 20 20 45 51  |....r%        EQ|
00000a30  55 44 20 30 0d 04 10 05  5d 0d 04 1a 05 ed 0d 04  |UD 0....].......|
00000a40  24 05 e1 0d 04 2e 04 0d  04 38 10 f4 46 61 73 74  |$........8..Fast|
00000a50  20 44 69 76 69 64 65 0d  04 42 10 f4 2d 2d 2d 2d  | Divide..B..----|
00000a60  2d 2d 2d 2d 2d 2d 2d 0d  04 4c 3c dd a4 46 61 73  |-------..L<..Fas|
00000a70  74 44 69 76 28 6f 75 74  71 25 2c 6f 75 74 72 25  |tDiv(outq%,outr%|
00000a80  2c 6e 75 6d 25 2c 63 6f  6e 73 74 25 2c 73 69 67  |,num%,const%,sig|
00000a90  6e 70 72 65 73 25 2c 77  6f 72 6b 25 2c 70 61 73  |npres%,work%,pas|
00000aa0  73 25 29 0d 04 56 08 ea  20 6e 25 0d 04 60 44 f4  |s%)..V.. n%..`D.|
00000ab0  20 54 6f 20 6e 6f 74 20  70 61 73 73 2c 20 73 69  | To not pass, si|
00000ac0  67 6e 70 72 65 73 2c 20  75 73 65 20 2d 31 20 69  |gnpres, use -1 i|
00000ad0  6e 73 74 65 61 64 20 6f  66 20 76 61 6c 69 64 20  |nstead of valid |
00000ae0  72 65 67 69 73 74 65 72  20 63 6f 6e 73 74 2e 0d  |register const..|
00000af0  04 6a 04 0d 04 74 40 e7  20 63 6f 6e 73 74 25 3d  |.j...t@. const%=|
00000b00  30 20 8c 20 f1 22 46 61  73 74 44 69 76 3a 41 74  |0 . ."FastDiv:At|
00000b10  74 65 6d 70 74 20 74 6f  20 63 6f 64 65 20 64 69  |tempt to code di|
00000b20  76 69 73 69 6f 6e 20 62  79 20 5a 45 52 4f 20 21  |vision by ZERO !|
00000b30  22 3a fa 0d 04 7e 04 0d  04 88 21 f4 20 50 72 65  |":...~....!. Pre|
00000b40  73 65 72 76 65 20 74 68  65 20 73 69 67 6e 20 6f  |serve the sign o|
00000b50  66 20 63 6f 6e 73 74 25  0d 04 92 3b e7 20 63 6f  |f const%...;. co|
00000b60  6e 73 74 25 3c 30 20 8c  20 6e 73 69 67 6e 70 72  |nst%<0 . nsignpr|
00000b70  65 73 3d 2d 31 3a 63 6f  6e 73 74 25 3d 2d 63 6f  |es=-1:const%=-co|
00000b80  6e 73 74 25 20 8b 20 6e  73 69 67 6e 70 72 65 73  |nst% . nsignpres|
00000b90  3d 2b 31 0d 04 9c 21 70  6f 77 65 72 5f 6f 66 5f  |=+1...!power_of_|
00000ba0  32 20 3d a4 70 6f 77 65  72 6f 66 32 28 63 6f 6e  |2 =.powerof2(con|
00000bb0  73 74 25 29 0d 04 a6 71  e7 20 a4 69 6d 6f 70 32  |st%)...q. .imop2|
00000bc0  28 63 6f 6e 73 74 25 29  3c 3e 2d 31 20 8c 20 77  |(const%)<>-1 . w|
00000bd0  6f 72 6b 25 3d 2d 31 20  3a f4 20 69 66 20 63 61  |ork%=-1 :. if ca|
00000be0  6e 20 62 65 20 72 65 70  72 65 73 65 6e 74 65 64  |n be represented|
00000bf0  20 61 73 20 61 6e 20 69  6d 6d 65 64 69 61 74 65  | as an immediate|
00000c00  20 63 6f 6e 73 74 61 6e  74 2c 20 6e 6f 20 6e 65  | constant, no ne|
00000c10  65 64 20 66 6f 72 20 77  6f 72 6b 25 20 72 65 67  |ed for work% reg|
00000c20  69 73 74 65 72 0d 04 b0  04 0d 04 ba 37 e7 20 a4  |ister.......7. .|
00000c30  49 6e 76 52 65 67 28 6f  75 74 71 25 29 20 84 20  |InvReg(outq%) . |
00000c40  a4 49 6e 76 52 65 67 28  6f 75 74 72 25 29 20 84  |.InvReg(outr%) .|
00000c50  20 a4 49 6e 76 52 65 67  28 6e 75 6d 25 29 20 8c  | .InvReg(num%) .|
00000c60  0d 04 c4 24 20 20 f1 20  22 46 61 73 74 44 69 76  |...$  . "FastDiv|
00000c70  3a 49 6e 76 61 6c 69 64  20 52 65 67 69 73 74 65  |:Invalid Registe|
00000c80  72 22 3a fa 0d 04 ce 05  cd 0d 04 d8 2d e7 20 6f  |r":.........-. o|
00000c90  75 74 71 25 3d 6f 75 74  72 25 20 84 20 6f 75 74  |utq%=outr% . out|
00000ca0  71 25 3d 6e 75 6d 25 20  84 20 6e 75 6d 25 3d 6f  |q%=num% . num%=o|
00000cb0  75 74 72 25 20 8c 0d 04  e2 36 20 20 f1 22 46 61  |utr% ....6  ."Fa|
00000cc0  73 74 44 69 76 3a 71 2c  72 2c 6e 75 6d 20 72 65  |stDiv:q,r,num re|
00000cd0  67 69 73 74 65 72 73 20  4d 75 73 74 20 62 65 20  |gisters Must be |
00000ce0  64 69 66 66 65 72 65 6e  74 22 3a fa 0d 04 ec 05  |different":.....|
00000cf0  cd 0d 04 f6 3a e7 20 6f  75 74 71 25 3d 73 69 67  |....:. outq%=sig|
00000d00  6e 70 72 65 73 25 20 84  20 6f 75 74 72 25 3d 73  |npres% . outr%=s|
00000d10  69 67 6e 70 72 65 73 25  20 84 20 6e 75 6d 25 3d  |ignpres% . num%=|
00000d20  73 69 67 6e 70 72 65 73  25 20 8c 0d 05 00 3e 20  |signpres% ....> |
00000d30  20 e7 20 73 69 67 6e 70  72 65 73 25 3c 3e 2d 31  | . signpres%<>-1|
00000d40  20 8c 20 f1 22 46 61 73  74 44 69 76 3a 49 6e 76  | . ."FastDiv:Inv|
00000d50  61 6c 69 64 20 73 69 67  6e 70 72 65 73 20 72 65  |alid signpres re|
00000d60  67 69 73 74 65 72 22 3a  fa 0d 05 0a 05 cd 0d 05  |gister":........|
00000d70  14 40 e7 20 6f 75 74 71  25 3d 77 6f 72 6b 25 20  |.@. outq%=work% |
00000d80  84 20 6f 75 74 72 25 3d  77 6f 72 6b 25 20 84 20  |. outr%=work% . |
00000d90  6e 75 6d 25 3d 77 6f 72  6b 25 20 84 20 73 69 67  |num%=work% . sig|
00000da0  6e 70 72 65 73 25 3d 77  6f 72 6b 25 20 8c 0d 05  |npres%=work% ...|
00000db0  1e 36 20 20 e7 20 77 6f  72 6b 25 3c 3e 2d 31 20  |.6  . work%<>-1 |
00000dc0  8c 20 f1 22 46 61 73 74  44 69 76 3a 49 6e 76 61  |. ."FastDiv:Inva|
00000dd0  6c 69 64 20 77 6f 72 6b  20 72 65 67 69 73 74 65  |lid work registe|
00000de0  72 22 3a fa 0d 05 28 05  cd 0d 05 32 04 0d 05 3c  |r":...(....2...<|
00000df0  10 e7 20 63 6f 6e 73 74  25 3d 31 20 8c 0d 05 46  |.. const%=1 ...F|
00000e00  16 20 20 e7 20 6e 73 69  67 6e 70 72 65 73 3d 2b  |.  . nsignpres=+|
00000e10  31 20 8c 0d 05 50 11 20  20 20 5b 4f 50 54 20 70  |1 ...P.   [OPT p|
00000e20  61 73 73 25 0d 05 5a 15  20 20 20 20 4d 4f 56 20  |ass%..Z.    MOV |
00000e30  6f 75 74 72 25 2c 20 23  30 0d 05 64 17 20 20 20  |outr%, #0..d.   |
00000e40  20 4d 4f 56 20 6f 75 74  71 25 2c 20 6e 75 6d 25  | MOV outq%, num%|
00000e50  0d 05 6e 08 20 20 20 5d  0d 05 78 07 20 20 cc 0d  |..n.   ]..x.  ..|
00000e60  05 82 11 20 20 20 5b 4f  50 54 20 70 61 73 73 25  |...   [OPT pass%|
00000e70  0d 05 8c 15 20 20 20 20  4d 4f 56 20 6f 75 74 72  |....    MOV outr|
00000e80  25 2c 20 23 30 0d 05 96  1b 20 20 20 20 52 53 42  |%, #0....    RSB|
00000e90  20 6f 75 74 71 25 2c 20  6e 75 6d 25 2c 20 23 30  | outq%, num%, #0|
00000ea0  0d 05 a0 08 20 20 20 5d  0d 05 aa 07 20 20 cd 0d  |....   ]....  ..|
00000eb0  05 b4 0a 3d 70 61 73 73  25 0d 05 be 05 cd 0d 05  |...=pass%.......|
00000ec0  c8 04 0d 05 d2 30 f4 20  73 65 74 20 62 69 74 33  |.....0. set bit3|
00000ed0  31 20 6f 66 20 74 68 69  73 20 72 65 67 20 74 6f  |1 of this reg to|
00000ee0  20 4e 4f 54 28 73 69 67  6e 20 6f 66 20 6e 75 6d  | NOT(sign of num|
00000ef0  25 29 0d 05 dc 1c e7 20  ac 20 a4 49 6e 76 52 65  |%)..... . .InvRe|
00000f00  67 28 73 69 67 6e 70 72  65 73 25 29 20 8c 0d 05  |g(signpres%) ...|
00000f10  e6 12 20 20 20 20 5b 4f  50 54 20 70 61 73 73 25  |..    [OPT pass%|
00000f20  0d 05 f0 38 20 20 20 20  20 80 53 20 73 69 67 6e  |...8     .S sign|
00000f30  70 72 65 73 25 2c 6e 75  6d 25 2c 23 26 38 30 30  |pres%,num%,#&800|
00000f40  30 30 30 30 30 20 3b 20  73 61 76 65 20 73 69 67  |00000 ; save sig|
00000f50  6e 20 6f 66 20 6e 75 6d  0d 05 fa 2e 20 20 20 20  |n of num....    |
00000f60  20 52 53 42 4e 45 20 6e  75 6d 25 2c 6e 75 6d 25  | RSBNE num%,num%|
00000f70  2c 23 30 3b 20 6d 61 6b  65 20 6e 75 6d 20 70 6f  |,#0; make num po|
00000f80  73 69 74 69 76 65 0d 06  04 09 20 20 20 20 5d 0d  |sitive....    ].|
00000f90  06 0e 05 cd 0d 06 18 04  0d 06 22 25 f4 20 43 61  |.........."%. Ca|
00000fa0  72 72 79 20 6f 75 74 20  46 61 73 74 20 49 6e 74  |rry out Fast Int|
00000fb0  65 67 65 72 20 44 69 76  69 73 69 6f 6e 0d 06 2c  |eger Division..,|
00000fc0  1e e7 20 63 6f 6e 73 74  25 3d 28 31 3c 3c 70 6f  |.. const%=(1<<po|
00000fd0  77 65 72 5f 6f 66 5f 32  29 20 8c 0d 06 36 20 20  |wer_of_2) ...6  |
00000fe0  20 f4 20 64 69 76 69 73  69 6f 6e 20 62 79 20 61  | . division by a|
00000ff0  20 70 6f 77 65 72 20 6f  66 20 32 0d 06 40 10 20  | power of 2..@. |
00001000  20 5b 4f 50 54 20 70 61  73 73 25 0d 06 4a 25 20  | [OPT pass%..J% |
00001010  20 20 4d 4f 56 20 6f 75  74 71 25 2c 6e 75 6d 25  |  MOV outq%,num%|
00001020  2c 6c 73 72 20 23 70 6f  77 65 72 5f 6f 66 5f 32  |,lsr #power_of_2|
00001030  0d 06 54 2b 20 20 20 53  55 42 20 6f 75 74 72 25  |..T+   SUB outr%|
00001040  2c 6e 75 6d 25 2c 6f 75  74 71 25 2c 6c 73 6c 20  |,num%,outq%,lsl |
00001050  23 70 6f 77 65 72 5f 6f  66 5f 32 0d 06 5e 07 20  |#power_of_2..^. |
00001060  20 5d 0d 06 68 05 cc 0d  06 72 04 0d 06 7c 10 20  | ]..h....r...|. |
00001070  20 73 75 62 66 6c 61 67  25 3d a3 0d 06 86 04 0d  | subflag%=......|
00001080  06 90 1a 20 20 e7 20 ac  20 a4 49 6e 76 52 65 67  |...  . . .InvReg|
00001090  28 77 6f 72 6b 25 29 20  8c 0d 06 9a 2b 20 20 20  |(work%) ....+   |
000010a0  20 5b 4f 50 54 20 a4 6d  65 67 61 6d 6f 76 28 77  | [OPT .megamov(w|
000010b0  6f 72 6b 25 2c 20 63 6f  6e 73 74 25 2c 20 70 61  |ork%, const%, pa|
000010c0  73 73 25 29 0d 06 a4 09  20 20 20 20 5d 0d 06 ae  |ss%)....    ]...|
000010d0  07 20 20 cd 0d 06 b8 04  0d 06 c2 1c 20 20 6e 70  |.  .........  np|
000010e0  6f 77 65 72 5f 6f 66 5f  32 3d 70 6f 77 65 72 5f  |ower_of_2=power_|
000010f0  6f 66 5f 32 0d 06 cc 20  20 20 63 6f 6e 73 74 25  |of_2...   const%|
00001100  3d 63 6f 6e 73 74 25 3e  3e 6e 70 6f 77 65 72 5f  |=const%>>npower_|
00001110  6f 66 5f 32 0d 06 d6 04  0d 06 e0 15 20 20 74 31  |of_2........  t1|
00001120  25 3d 31 3a 73 25 3d 30  3a 6d 25 3d 30 0d 06 ea  |%=1:s%=0:m%=0...|
00001130  1c 20 20 c8 95 20 28 74  31 25 3c 3e 30 29 20 80  |.  .. (t1%<>0) .|
00001140  20 28 6d 25 3c 3d 33 32  29 0d 06 f4 2e 20 20 20  | (m%<=32)....   |
00001150  20 e7 20 28 74 31 25 3e  3d 63 6f 6e 73 74 25 29  | . (t1%>=const%)|
00001160  20 8c 20 74 31 25 3d 74  31 25 2d 63 6f 6e 73 74  | . t1%=t1%-const|
00001170  25 3a 73 25 2b 3d 31 0d  06 fe 34 20 20 20 20 e7  |%:s%+=1...4    .|
00001180  20 28 74 31 25 3c 3e 30  29 20 8c 20 74 31 25 3d  | (t1%<>0) . t1%=|
00001190  28 74 31 25 3c 3c 31 29  2b 31 3a 73 25 3d 73 25  |(t1%<<1)+1:s%=s%|
000011a0  3c 3c 31 3a 6d 25 3d 6d  25 2b 31 0d 07 08 07 20  |<<1:m%=m%+1.... |
000011b0  20 ce 0d 07 12 17 20 20  74 31 25 3d a4 70 6f 77  | .....  t1%=.pow|
000011c0  65 72 6f 66 32 28 73 25  29 0d 07 1c 21 20 20 70  |erof2(s%)...!  p|
000011d0  6f 77 65 72 5f 6f 66 5f  32 3d 70 6f 77 65 72 5f  |ower_of_2=power_|
000011e0  6f 66 5f 32 20 2d 20 74  31 25 0d 07 26 12 20 20  |of_2 - t1%..&.  |
000011f0  73 25 3d 73 25 20 3e 3e  20 74 31 25 0d 07 30 0e  |s%=s% >> t1%..0.|
00001200  20 20 e7 20 73 25 3d 31  20 8c 0d 07 3a 41 20 20  |  . s%=1 ...:A  |
00001210  20 20 f4 20 4d 4f 56 20  6f 75 74 71 25 2c 6e 75  |  . MOV outq%,nu|
00001220  6d 25 20 28 64 6f 6e 65  20 62 79 20 6a 6f 69 6e  |m% (done by join|
00001230  69 6e 67 20 77 69 74 68  20 6e 65 78 74 20 69 6e  |ing with next in|
00001240  73 74 72 75 63 74 69 6f  6e 21 29 0d 07 44 07 20  |struction!)..D. |
00001250  20 cc 0d 07 4e 2d 20 20  20 20 5b 4f 50 54 20 a4  | ...N-    [OPT .|
00001260  46 61 73 74 44 69 76 41  69 64 28 6f 75 74 71 25  |FastDivAid(outq%|
00001270  2c 6e 75 6d 25 2c 73 25  2c 70 61 73 73 25 29 0d  |,num%,s%,pass%).|
00001280  07 58 09 20 20 20 20 5d  0d 07 62 07 20 20 cd 0d  |.X.    ]..b.  ..|
00001290  07 6c 45 20 20 6c 73 25  3d a4 62 69 74 70 61 74  |.lE  ls%=.bitpat|
000012a0  6c 65 6e 28 73 25 29 3a  f4 20 63 61 6c 63 3a 6c  |len(s%):. calc:l|
000012b0  73 20 28 6c 65 6e 3a 73  29 3a 32 5e 28 6c 73 2d  |s (len:s):2^(ls-|
000012c0  31 29 3c 3d 20 73 20 3c  32 5e 28 6c 73 29 2c 6c  |1)<= s <2^(ls),l|
000012d0  73 3c 3d 6d 0d 07 76 37  20 20 74 31 25 3d 6d 25  |s<=m..v7  t1%=m%|
000012e0  2b 31 3a f4 20 67 65 6e  65 72 61 74 65 20 63 6f  |+1:. generate co|
000012f0  64 65 20 66 6f 72 20 73  73 73 73 73 2e 2e 2e 2e  |de for sssss....|
00001300  20 74 6f 20 33 32 20 62  69 74 73 0d 07 80 0f 20  | to 32 bits.... |
00001310  20 c8 95 20 74 31 25 3c  33 32 0d 07 8a 10 20 20  | .. t1%<32....  |
00001320  20 20 e7 20 73 25 3d 31  20 8c 0d 07 94 0e 20 20  |  . s%=1 .....  |
00001330  20 20 20 20 73 25 3d 30  0d 07 9e 14 20 20 20 20  |    s%=0....    |
00001340  20 20 5b 4f 50 54 20 70  61 73 73 25 0d 07 a8 27  |  [OPT pass%...'|
00001350  20 20 20 20 20 20 20 41  44 44 20 6f 75 74 71 25  |       ADD outq%|
00001360  2c 6e 75 6d 25 2c 6e 75  6d 25 2c 4c 53 52 20 23  |,num%,num%,LSR #|
00001370  74 31 25 0d 07 b2 0b 20  20 20 20 20 20 5d 0d 07  |t1%....      ]..|
00001380  bc 09 20 20 20 20 cc 0d  07 c6 14 20 20 20 20 20  |..    .....     |
00001390  20 5b 4f 50 54 20 70 61  73 73 25 0d 07 d0 29 20  | [OPT pass%...) |
000013a0  20 20 20 20 20 20 41 44  44 20 6f 75 74 71 25 2c  |      ADD outq%,|
000013b0  6f 75 74 71 25 2c 6f 75  74 71 25 2c 4c 53 52 20  |outq%,outq%,LSR |
000013c0  23 74 31 25 0d 07 da 0b  20 20 20 20 20 20 5d 0d  |#t1%....      ].|
000013d0  07 e4 09 20 20 20 20 cd  0d 07 ee 11 20 20 20 20  |...    .....    |
000013e0  74 31 25 3d 74 31 25 2a  32 0d 07 f8 07 20 20 ce  |t1%=t1%*2....  .|
000013f0  0d 08 02 0e 20 20 e7 20  73 25 3d 31 20 8c 0d 08  |....  . s%=1 ...|
00001400  0c 34 20 20 20 20 f4 20  55 73 65 64 20 62 79 20  |.4    . Used by |
00001410  73 6f 6d 65 20 6c 61 72  67 65 20 64 69 76 69 73  |some large divis|
00001420  6f 72 73 20 28 65 67 20  26 37 66 66 66 66 66 66  |ors (eg &7ffffff|
00001430  31 29 0d 08 16 12 20 20  20 20 5b 4f 50 54 20 70  |1)....    [OPT p|
00001440  61 73 73 25 0d 08 20 18  20 20 20 20 20 4d 4f 56  |ass%.. .     MOV|
00001450  20 6f 75 74 71 25 2c 20  6e 75 6d 25 0d 08 2a 09  | outq%, num%..*.|
00001460  20 20 20 20 5d 0d 08 34  07 20 20 cd 0d 08 3e 24  |    ]..4.  ...>$|
00001470  20 20 70 6f 77 65 72 5f  6f 66 5f 32 3d 70 6f 77  |  power_of_2=pow|
00001480  65 72 5f 6f 66 5f 32 2b  6d 25 2d 6c 73 25 2b 32  |er_of_2+m%-ls%+2|
00001490  0d 08 48 18 20 20 e7 20  70 6f 77 65 72 5f 6f 66  |..H.  . power_of|
000014a0  5f 32 20 3c 3e 30 20 8c  0d 08 52 12 20 20 20 20  |_2 <>0 ...R.    |
000014b0  5b 4f 50 54 20 70 61 73  73 25 0d 08 5c 39 20 20  |[OPT pass%..\9  |
000014c0  20 20 20 4d 4f 56 20 6f  75 74 71 25 2c 6f 75 74  |   MOV outq%,out|
000014d0  71 25 2c 4c 53 52 20 23  70 6f 77 65 72 5f 6f 66  |q%,LSR #power_of|
000014e0  5f 32 20 3b 67 65 6e 20  66 69 6e 61 6c 20 73 68  |_2 ;gen final sh|
000014f0  69 66 74 0d 08 66 09 20  20 20 20 5d 0d 08 70 07  |ift..f.    ]..p.|
00001500  20 20 cd 0d 08 7a 44 20  20 e7 20 63 6f 6e 73 74  |  ...zD  . const|
00001510  25 3d 31 20 8c 20 f1 22  46 61 73 74 44 69 76 3a  |%=1 . ."FastDiv:|
00001520  53 6f 72 72 79 20 50 72  6f 67 72 61 6d 20 45 72  |Sorry Program Er|
00001530  72 6f 72 20 31 2c 20 70  6c 65 61 73 65 20 72 65  |ror 1, please re|
00001540  70 6f 72 74 22 3a fa 0d  08 84 2d 20 20 5b 4f 50  |port":....-  [OP|
00001550  54 20 a4 46 61 73 74 4d  75 6c 28 6f 75 74 72 25  |T .FastMul(outr%|
00001560  2c 6f 75 74 71 25 2c 63  6f 6e 73 74 25 2c 70 61  |,outq%,const%,pa|
00001570  73 73 25 29 0d 08 8e 07  20 20 5d 0d 08 98 22 20  |ss%)....  ]..." |
00001580  20 63 6f 6e 73 74 25 3d  63 6f 6e 73 74 25 20 3c  | const%=const% <|
00001590  3c 20 6e 70 6f 77 65 72  5f 6f 66 5f 32 0d 08 a2  |< npower_of_2...|
000015a0  19 20 20 e7 20 6e 70 6f  77 65 72 5f 6f 66 5f 32  |.  . npower_of_2|
000015b0  20 3c 3e 30 20 8c 0d 08  ac 12 20 20 20 20 5b 4f  | <>0 .....    [O|
000015c0  50 54 20 70 61 73 73 25  0d 08 b6 2f 20 20 20 20  |PT pass%.../    |
000015d0  20 53 55 42 53 20 6f 75  74 72 25 2c 6e 75 6d 25  | SUBS outr%,num%|
000015e0  2c 6f 75 74 72 25 2c 4c  53 4c 23 20 6e 70 6f 77  |,outr%,LSL# npow|
000015f0  65 72 5f 6f 66 5f 32 0d  08 c0 09 20 20 20 20 5d  |er_of_2....    ]|
00001600  0d 08 ca 07 20 20 cc 0d  08 d4 12 20 20 20 20 5b  |....  .....    [|
00001610  4f 50 54 20 70 61 73 73  25 0d 08 de 1e 20 20 20  |OPT pass%....   |
00001620  20 20 53 55 42 53 20 6f  75 74 72 25 2c 6e 75 6d  |  SUBS outr%,num|
00001630  25 2c 6f 75 74 72 25 0d  08 e8 09 20 20 20 20 5d  |%,outr%....    ]|
00001640  0d 08 f2 07 20 20 cd 0d  08 fc 18 20 20 e7 20 a4  |....  .....  . .|
00001650  49 6e 76 52 65 67 28 77  6f 72 6b 25 29 20 8c 0d  |InvReg(work%) ..|
00001660  09 06 14 20 20 20 20 e7  20 73 75 62 66 6c 61 67  |...    . subflag|
00001670  25 20 8c 0d 09 10 14 20  20 20 20 20 20 5b 4f 50  |% .....      [OP|
00001680  54 20 70 61 73 73 25 0d  09 1a 1f 20 20 20 20 20  |T pass%....     |
00001690  20 20 53 55 42 4d 49 20  6f 75 74 71 25 2c 6f 75  |  SUBMI outq%,ou|
000016a0  74 71 25 2c 23 31 0d 09  24 24 20 20 20 20 20 20  |tq%,#1..$$      |
000016b0  20 41 44 44 4d 49 20 6f  75 74 72 25 2c 6f 75 74  | ADDMI outr%,out|
000016c0  72 25 2c 23 63 6f 6e 73  74 25 0d 09 2e 0b 20 20  |r%,#const%....  |
000016d0  20 20 20 20 5d 0d 09 38  09 20 20 20 20 cd 0d 09  |    ]..8.    ...|
000016e0  42 12 20 20 20 20 5b 4f  50 54 20 70 61 73 73 25  |B.    [OPT pass%|
000016f0  0d 09 4c 1a 20 20 20 20  20 43 4d 50 20 6f 75 74  |..L.     CMP out|
00001700  72 25 2c 23 63 6f 6e 73  74 25 0d 09 56 1d 20 20  |r%,#const%..V.  |
00001710  20 20 20 41 44 44 47 45  20 6f 75 74 71 25 2c 6f  |   ADDGE outq%,o|
00001720  75 74 71 25 2c 23 31 0d  09 60 22 20 20 20 20 20  |utq%,#1..`"     |
00001730  53 55 42 47 45 20 6f 75  74 72 25 2c 6f 75 74 72  |SUBGE outr%,outr|
00001740  25 2c 23 63 6f 6e 73 74  25 0d 09 6a 09 20 20 20  |%,#const%..j.   |
00001750  20 5d 0d 09 74 07 20 20  cc 0d 09 7e 14 20 20 20  | ]..t.  ...~.   |
00001760  20 e7 20 73 75 62 66 6c  61 67 25 20 8c 0d 09 88  | . subflag% ....|
00001770  14 20 20 20 20 20 20 5b  4f 50 54 20 70 61 73 73  |.      [OPT pass|
00001780  25 0d 09 92 1f 20 20 20  20 20 20 20 53 55 42 4d  |%....       SUBM|
00001790  49 20 6f 75 74 71 25 2c  6f 75 74 71 25 2c 23 31  |I outq%,outq%,#1|
000017a0  0d 09 9c 22 20 20 20 20  20 20 20 41 44 44 4d 49  |..."       ADDMI|
000017b0  20 6f 75 74 72 25 2c 6f  75 74 72 25 2c 77 6f 72  | outr%,outr%,wor|
000017c0  6b 25 0d 09 a6 0b 20 20  20 20 20 20 5d 0d 09 b0  |k%....      ]...|
000017d0  09 20 20 20 20 cd 0d 09  ba 12 20 20 20 20 5b 4f  |.    .....    [O|
000017e0  50 54 20 70 61 73 73 25  0d 09 c4 18 20 20 20 20  |PT pass%....    |
000017f0  20 43 4d 50 20 6f 75 74  72 25 2c 77 6f 72 6b 25  | CMP outr%,work%|
00001800  0d 09 ce 1d 20 20 20 20  20 41 44 44 47 45 20 6f  |....     ADDGE o|
00001810  75 74 71 25 2c 6f 75 74  71 25 2c 23 31 0d 09 d8  |utq%,outq%,#1...|
00001820  20 20 20 20 20 20 53 55  42 47 45 20 6f 75 74 72  |      SUBGE outr|
00001830  25 2c 6f 75 74 72 25 2c  77 6f 72 6b 25 0d 09 e2  |%,outr%,work%...|
00001840  09 20 20 20 20 5d 0d 09  ec 07 20 20 cd 0d 09 f6  |.    ]....  ....|
00001850  05 cd 0d 0a 00 04 0d 0a  0a 30 f4 20 63 68 61 6e  |.........0. chan|
00001860  67 65 20 73 69 67 6e 20  6f 66 20 61 6e 73 77 65  |ge sign of answe|
00001870  72 20 69 66 20 63 6f 6e  73 74 25 3c 30 20 61 74  |r if const%<0 at|
00001880  20 73 74 61 72 74 0d 0a  14 1a e7 20 a4 49 6e 76  | start..... .Inv|
00001890  52 65 67 28 73 69 67 6e  70 72 65 73 25 29 20 8c  |Reg(signpres%) .|
000018a0  0d 0a 1e 18 20 20 e7 20  28 6e 73 69 67 6e 70 72  |....  . (nsignpr|
000018b0  65 73 3d 2d 31 29 20 8c  0d 0a 28 12 20 20 20 20  |es=-1) ...(.    |
000018c0  5b 4f 50 54 20 70 61 73  73 25 0d 0a 32 1b 20 20  |[OPT pass%..2.  |
000018d0  20 20 20 52 53 42 20 6f  75 74 71 25 2c 6f 75 74  |   RSB outq%,out|
000018e0  71 25 2c 23 30 0d 0a 3c  09 20 20 20 20 5d 0d 0a  |q%,#0..<.    ]..|
000018f0  46 07 20 20 cd 0d 0a 50  05 cc 0d 0a 5a 10 20 20  |F.  ...P....Z.  |
00001900  5b 4f 50 54 20 70 61 73  73 25 0d 0a 64 32 20 20  |[OPT pass%..d2  |
00001910  20 54 45 51 53 20 73 69  67 6e 70 72 65 73 25 2c  | TEQS signpres%,|
00001920  23 26 38 30 30 30 30 30  30 30 20 3b 20 67 65 74  |#&80000000 ; get|
00001930  20 73 74 6f 72 65 64 20  73 69 67 6e 0d 0a 6e 48  | stored sign..nH|
00001940  20 20 20 52 53 42 45 51  20 6e 75 6d 25 2c 6e 75  |   RSBEQ num%,nu|
00001950  6d 25 2c 23 30 3b 20 72  65 6d 6f 76 65 20 69 66  |m%,#0; remove if|
00001960  20 64 6f 6e 27 74 20 77  61 6e 74 20 74 6f 20 70  | don't want to p|
00001970  72 65 73 65 72 76 65 20  6f 72 69 67 69 6e 61 6c  |reserve original|
00001980  20 6e 6f 2e 0d 0a 78 1b  20 20 20 52 53 42 45 51  | no...x.   RSBEQ|
00001990  20 6f 75 74 72 25 2c 6f  75 74 72 25 2c 23 30 0d  | outr%,outr%,#0.|
000019a0  0a 82 07 20 20 5d 0d 0a  8c 18 20 20 e7 20 28 6e  |...  ]....  . (n|
000019b0  73 69 67 6e 70 72 65 73  3d 2d 31 29 20 8c 0d 0a  |signpres=-1) ...|
000019c0  96 12 20 20 20 20 5b 4f  50 54 20 70 61 73 73 25  |..    [OPT pass%|
000019d0  0d 0a a0 1d 20 20 20 20  20 52 53 42 4e 45 20 6f  |....     RSBNE o|
000019e0  75 74 71 25 2c 6f 75 74  71 25 2c 23 30 0d 0a aa  |utq%,outq%,#0...|
000019f0  09 20 20 20 20 5d 0d 0a  b4 07 20 20 cc 0d 0a be  |.    ]....  ....|
00001a00  12 20 20 20 20 5b 4f 50  54 20 70 61 73 73 25 0d  |.    [OPT pass%.|
00001a10  0a c8 1d 20 20 20 20 20  52 53 42 45 51 20 6f 75  |...     RSBEQ ou|
00001a20  74 71 25 2c 6f 75 74 71  25 2c 23 30 0d 0a d2 09  |tq%,outq%,#0....|
00001a30  20 20 20 20 5d 0d 0a dc  07 20 20 cd 0d 0a e6 05  |    ]....  .....|
00001a40  cd 0d 0a f0 04 0d 0a fa  0a 3d 70 61 73 73 25 0d  |.........=pass%.|
00001a50  0b 04 04 0d 0b 0e 3a f4  46 61 73 74 20 44 69 76  |......:.Fast Div|
00001a60  69 64 65 20 41 69 64 65  72 3a 2d 20 46 6f 72 20  |ide Aider:- For |
00001a70  57 6f 72 6b 69 6e 67 20  64 65 74 61 69 6c 73 20  |Working details |
00001a80  73 65 65 20 68 2e 46 61  73 74 44 69 76 0d 0b 18  |see h.FastDiv...|
00001a90  16 f4 2d 2d 2d 2d 2d 2d  2d 2d 2d 2d 2d 2d 2d 2d  |..--------------|
00001aa0  2d 2d 2d 0d 0b 22 24 dd  a4 46 61 73 74 44 69 76  |---.."$..FastDiv|
00001ab0  41 69 64 28 52 62 2c 52  61 2c 63 6f 6e 73 74 25  |Aid(Rb,Ra,const%|
00001ac0  2c 70 61 73 73 25 29 0d  0b 2c 05 f4 0d 0b 36 0c  |,pass%)..,....6.|
00001ad0  ea 20 6e 25 2c 6c 73 25  0d 0b 40 0e ea 20 64 69  |. n%,ls%..@.. di|
00001ae0  76 69 6e 73 74 24 0d 0b  4a 4a e7 20 63 6f 6e 73  |vinst$..JJ. cons|
00001af0  74 25 20 3d 20 31 20 84  20 63 6f 6e 73 74 25 3d  |t% = 1 . const%=|
00001b00  30 3a f1 22 46 61 73 74  44 69 76 41 69 64 3a 4c  |0:."FastDivAid:L|
00001b10  6f 67 69 63 20 65 72 72  6f 72 20 31 2c 20 63 61  |ogic error 1, ca|
00001b20  6e 27 74 20 62 79 20 31  20 6f 72 20 30 22 3a fa  |n't by 1 or 0":.|
00001b30  0d 0b 54 35 e7 20 63 6f  6e 73 74 25 3c 30 20 8c  |..T5. const%<0 .|
00001b40  20 85 20 30 2c 22 46 61  73 74 44 69 76 41 69 64  | . 0,"FastDivAid|
00001b50  3a 4c 6f 67 69 63 20 65  72 72 6f 72 20 32 20 66  |:Logic error 2 f|
00001b60  6f 75 6e 64 22 0d 0b 5e  39 e7 20 52 62 3d 52 61  |ound"..^9. Rb=Ra|
00001b70  20 8c 20 f1 22 46 61 73  74 44 69 76 41 69 64 3a  | . ."FastDivAid:|
00001b80  52 65 67 69 73 74 65 72  73 20 4d 75 73 74 20 62  |Registers Must b|
00001b90  65 20 64 69 66 66 65 72  65 6e 74 22 3a fa 0d 0b  |e different":...|
00001ba0  68 43 e7 20 a4 49 6e 76  52 65 67 28 52 62 29 20  |hC. .InvReg(Rb) |
00001bb0  84 20 a4 49 6e 76 52 65  67 28 52 61 29 20 8c 20  |. .InvReg(Ra) . |
00001bc0  f1 20 22 46 61 73 74 44  69 76 41 69 64 3a 49 6e  |. "FastDivAid:In|
00001bd0  76 61 6c 69 64 20 52 65  67 69 73 74 65 72 22 3a  |valid Register":|
00001be0  fa 0d 0b 72 04 0d 0b 7c  38 f4 20 46 69 6e 64 20  |...r...|8. Find |
00001bf0  74 68 65 20 6c 65 6e 67  74 68 20 6f 66 20 62 69  |the length of bi|
00001c00  74 20 70 61 74 74 65 72  6e 20 73 2c 20 66 72 6f  |t pattern s, fro|
00001c10  6d 20 74 68 65 20 66 69  72 73 74 20 31 0d 0b 86  |m the first 1...|
00001c20  1a 6c 73 25 3d a4 62 69  74 70 61 74 6c 65 6e 28  |.ls%=.bitpatlen(|
00001c30  63 6f 6e 73 74 25 29 0d  0b 90 04 0d 0b 9a 15 c8  |const%).........|
00001c40  8e 20 28 63 6f 6e 73 74  25 20 80 20 33 29 20 ca  |. (const% . 3) .|
00001c50  0d 0b a4 2b c9 20 30 2c  32 3a f4 20 69 65 20 73  |...+. 0,2:. ie s|
00001c60  62 20 6f 66 20 66 6f 72  6d 20 73 20 3d 20 73 31  |b of form s = s1|
00001c70  20 2a 20 32 5e 6e 2c 20  6e 3e 31 0d 0b ae 2c 20  | * 2^n, n>1..., |
00001c80  20 f1 20 22 46 61 73 74  44 69 76 41 69 64 3a 50  | . "FastDivAid:P|
00001c90  72 6f 67 72 61 6d 20 6c  6f 67 69 63 20 65 72 72  |rogram logic err|
00001ca0  6f 72 20 33 22 3a fa 0d  0b b8 35 c9 20 31 3a 20  |or 3":....5. 1: |
00001cb0  20 f4 20 69 65 20 73 20  6f 66 20 66 6f 72 6d 20  | . ie s of form |
00001cc0  73 20 3d 20 73 31 20 2a  20 32 5e 6e 20 2b 31 2c  |s = s1 * 2^n +1,|
00001cd0  20 73 31 20 6f 64 64 2c  20 6e 3e 31 0d 0b c2 0f  | s1 odd, n>1....|
00001ce0  20 20 63 6f 6e 73 74 25  2d 3d 31 0d 0b cc 14 20  |  const%-=1.... |
00001cf0  20 64 69 76 69 6e 73 74  24 3d 22 41 44 44 22 0d  | divinst$="ADD".|
00001d00  0b d6 33 c9 20 33 3a f4  20 69 65 20 73 20 6f 66  |..3. 3:. ie s of|
00001d10  20 66 6f 72 6d 20 73 20  3d 20 73 31 20 2a 20 32  | form s = s1 * 2|
00001d20  5e 6e 20 2d 31 2c 20 73  31 20 6f 64 64 2c 20 6e  |^n -1, s1 odd, n|
00001d30  3e 31 0d 0b e0 0f 20 20  63 6f 6e 73 74 25 2b 3d  |>1....  const%+=|
00001d40  31 0d 0b ea 14 20 20 64  69 76 69 6e 73 74 24 3d  |1....  divinst$=|
00001d50  22 53 55 42 22 0d 0b f4  10 20 20 73 75 62 66 6c  |"SUB"....  subfl|
00001d60  61 67 25 3d b9 0d 0b fe  05 cb 0d 0c 08 27 63 6f  |ag%=.........'co|
00001d70  6e 73 74 25 3d 63 6f 6e  73 74 25 20 3e 3e 3e 20  |nst%=const% >>> |
00001d80  a4 70 6f 77 65 72 6f 66  32 28 63 6f 6e 73 74 25  |.powerof2(const%|
00001d90  29 0d 0c 12 10 e7 20 63  6f 6e 73 74 25 3d 31 20  |)..... const%=1 |
00001da0  8c 0d 0c 1c 1a 20 20 e7  20 28 64 69 76 69 6e 73  |.....  . (divins|
00001db0  74 24 3d 22 53 55 42 22  29 20 8c 0d 0c 26 30 20  |t$="SUB") ...&0 |
00001dc0  20 20 20 e7 20 6c 73 25  3c 3d 31 20 8c 20 f1 22  |   . ls%<=1 . ."|
00001dd0  46 61 73 74 44 69 76 41  69 64 3a 4c 6f 67 69 63  |FastDivAid:Logic|
00001de0  20 45 72 72 6f 72 20 34  22 3a fa 0d 0c 30 12 20  | Error 4":...0. |
00001df0  20 20 20 5b 4f 50 54 20  70 61 73 73 25 0d 0c 3a  |   [OPT pass%..:|
00001e00  34 20 20 20 20 20 41 44  44 20 52 62 2c 52 61 2c  |4     ADD Rb,Ra,|
00001e10  52 61 20 20 20 20 20 20  20 20 20 20 20 20 3b 3c  |Ra            ;<|
00001e20  2d 2d 2d 46 41 53 54 44  49 56 61 69 64 20 47 65  |---FASTDIVaid Ge|
00001e30  6e 0d 0c 44 34 20 20 20  20 20 53 55 42 20 52 62  |n..D4     SUB Rb|
00001e40  2c 52 62 2c 52 61 2c 4c  53 52 23 6c 73 25 20 2d  |,Rb,Ra,LSR#ls% -|
00001e50  31 20 3b 3c 2d 2d 2d 46  41 53 54 44 49 56 61 69  |1 ;<---FASTDIVai|
00001e60  64 20 47 65 6e 0d 0c 4e  09 20 20 20 20 5d 0d 0c  |d Gen..N.    ]..|
00001e70  58 07 20 20 cc 0d 0c 62  12 20 20 20 20 5b 4f 50  |X.  ...b.    [OP|
00001e80  54 20 70 61 73 73 25 0d  0c 6c 35 20 20 20 20 20  |T pass%..l5     |
00001e90  41 44 44 20 52 62 2c 52  61 2c 52 61 2c 20 4c 53  |ADD Rb,Ra,Ra, LS|
00001ea0  52 20 23 6c 73 25 2d 31  20 3b 3c 2d 2d 2d 46 41  |R #ls%-1 ;<---FA|
00001eb0  53 54 44 49 56 61 69 64  20 47 65 6e 0d 0c 76 09  |STDIVaid Gen..v.|
00001ec0  20 20 20 20 5d 0d 0c 80  07 20 20 cd 0d 0c 8a 05  |    ]....  .....|
00001ed0  cc 0d 0c 94 1a 20 20 e7  20 28 64 69 76 69 6e 73  |.....  . (divins|
00001ee0  74 24 3d 22 53 55 42 22  29 20 8c 0d 0c 9e 2c 20  |t$="SUB") ...., |
00001ef0  20 20 20 5b 4f 50 54 20  a4 46 61 73 74 44 69 76  |   [OPT .FastDiv|
00001f00  41 69 64 28 52 62 2c 52  61 2c 63 6f 6e 73 74 25  |Aid(Rb,Ra,const%|
00001f10  2c 70 61 73 73 25 29 0d  0c a8 35 20 20 20 20 20  |,pass%)...5     |
00001f20  53 55 42 20 52 62 2c 52  62 2c 52 61 2c 20 4c 53  |SUB Rb,Rb,Ra, LS|
00001f30  52 20 23 6c 73 25 2d 31  20 3b 3c 2d 2d 2d 46 41  |R #ls%-1 ;<---FA|
00001f40  53 54 44 49 56 61 69 64  20 47 65 6e 0d 0c b2 09  |STDIVaid Gen....|
00001f50  20 20 20 20 5d 0d 0c bc  07 20 20 cc 0d 0c c6 2c  |    ]....  ....,|
00001f60  20 20 20 20 5b 4f 50 54  20 a4 46 61 73 74 44 69  |    [OPT .FastDi|
00001f70  76 41 69 64 28 52 62 2c  52 61 2c 63 6f 6e 73 74  |vAid(Rb,Ra,const|
00001f80  25 2c 70 61 73 73 25 29  0d 0c d0 35 20 20 20 20  |%,pass%)...5    |
00001f90  20 41 44 44 20 52 62 2c  52 62 2c 52 61 2c 20 4c  | ADD Rb,Rb,Ra, L|
00001fa0  53 52 20 23 6c 73 25 2d  31 20 3b 3c 2d 2d 2d 46  |SR #ls%-1 ;<---F|
00001fb0  41 53 54 44 49 56 61 69  64 20 47 65 6e 0d 0c da  |ASTDIVaid Gen...|
00001fc0  09 20 20 20 20 5d 0d 0c  e4 07 20 20 cd 0d 0c ee  |.    ]....  ....|
00001fd0  05 cd 0d 0c f8 04 0d 0d  02 0a 3d 70 61 73 73 25  |..........=pass%|
00001fe0  0d 0d 0c 04 0d 0d 16 12  f4 46 61 73 74 20 4d 75  |.........Fast Mu|
00001ff0  6c 74 69 70 6c 79 0d 0d  20 13 f4 2d 2d 2d 2d 2d  |ltiply.. ..-----|
00002000  2d 2d 2d 2d 2d 2d 2d 2d  2d 0d 0d 2a 1c f4 2f 2f  |---------..*..//|
00002010  69 6e 69 74 69 61 6c 69  73 65 20 6d 61 63 72 6f  |initialise macro|
00002020  20 77 69 74 68 0d 0d 34  3d f4 2f 2f 72 65 67 69  | with..4=.//regi|
00002030  73 74 65 72 73 3a 20 72  65 73 75 6c 74 20 2c 6e  |sters: result ,n|
00002040  75 6d 62 65 72 20 74 6f  20 62 65 20 6d 75 6c 74  |umber to be mult|
00002050  69 70 6c 69 65 64 20 62  79 20 63 6f 6e 73 74 61  |iplied by consta|
00002060  6e 74 0d 0d 3e 3d f4 2f  2f 66 6f 6c 6c 6f 77 65  |nt..>=.//followe|
00002070  64 20 62 79 3a 20 74 68  65 20 63 6f 6e 73 74 61  |d by: the consta|
00002080  6e 74 20 79 6f 75 20 77  69 73 68 20 74 6f 20 66  |nt you wish to f|
00002090  61 73 74 20 6d 75 6c 74  69 70 6c 79 20 62 79 0d  |ast multiply by.|
000020a0  0d 48 30 f4 2f 2f 20 67  65 6e 65 72 61 74 65 73  |.H0.// generates|
000020b0  20 63 6f 64 65 20 74 6f  20 73 6f 6c 76 65 20 74  | code to solve t|
000020c0  6f 20 67 65 74 20 52 62  3d 52 61 20 2a 20 73 0d  |o get Rb=Ra * s.|
000020d0  0d 52 3e f4 2f 2f 77 68  65 6e 20 52 61 2c 52 62  |.R>.//when Ra,Rb|
000020e0  20 61 72 65 20 72 65 67  69 73 74 65 72 73 20 61  | are registers a|
000020f0  6e 64 20 20 73 3d 63 6f  6e 73 74 61 6e 74 20 74  |nd  s=constant t|
00002100  6f 20 6d 75 6c 74 69 70  6c 79 20 62 79 0d 0d 5c  |o multiply by..\|
00002110  46 f4 2f 2f 69 66 20 73  3d 30 20 6f 72 20 73 3d  |F.//if s=0 or s=|
00002120  31 20 6d 61 63 72 6f 20  61 62 6f 72 74 73 20 21  |1 macro aborts !|
00002130  21 21 21 20 28 54 72 79  20 4d 4f 56 20 52 62 2c  |!!! (Try MOV Rb,|
00002140  52 61 20 6f 72 20 4d 4f  56 20 52 62 2c 23 30 20  |Ra or MOV Rb,#0 |
00002150  21 21 29 0d 0d 66 2e f4  2f 2f 43 6f 6d 6d 65 6e  |!!)..f..//Commen|
00002160  74 3a 20 52 61 20 69 73  20 70 72 65 73 65 72 76  |t: Ra is preserv|
00002170  65 64 20 61 66 74 65 72  20 74 68 65 20 63 6f 64  |ed after the cod|
00002180  65 0d 0d 70 44 f4 2f 2f  4f 72 64 65 72 20 6f 66  |e..pD.//Order of|
00002190  20 63 6f 6d 70 6f 6e 65  6e 74 73 20 74 6f 20 75  | components to u|
000021a0  73 65 20 6a 75 73 74 20  6c 69 6b 65 20 61 20 73  |se just like a s|
000021b0  74 61 6e 64 61 72 64 20  69 6e 73 74 72 75 63 74  |tandard instruct|
000021c0  69 6f 6e 20 21 0d 0d 7a  04 0d 0d 84 21 dd a4 46  |ion !..z....!..F|
000021d0  61 73 74 4d 75 6c 28 52  62 2c 52 61 2c 63 6f 6e  |astMul(Rb,Ra,con|
000021e0  73 74 25 2c 70 61 73 73  25 29 0d 0d 8e 3c f4 20  |st%,pass%)...<. |
000021f0  47 65 6e 65 72 61 74 65  20 69 6e 73 74 72 75 63  |Generate instruc|
00002200  74 69 6f 6e 73 20 66 6f  72 20 66 61 73 74 20 6d  |tions for fast m|
00002210  75 6c 74 69 70 6c 79 20  52 62 3d 52 61 20 2a 20  |ultiply Rb=Ra * |
00002220  63 6f 6e 73 74 25 0d 0d  98 08 ea 20 6e 25 0d 0d  |const%..... n%..|
00002230  a2 3e e7 20 63 6f 6e 73  74 25 3d 31 20 84 20 63  |.>. const%=1 . c|
00002240  6f 6e 73 74 25 3d 30 3a  f1 22 46 61 73 74 4d 75  |onst%=0:."FastMu|
00002250  6c 3a 53 69 6c 6c 79 20  46 61 73 74 4d 75 6c 20  |l:Silly FastMul |
00002260  62 79 20 31 20 6f 72 20  30 22 3a fa 0d 0d ac 36  |by 1 or 0":....6|
00002270  e7 20 52 62 3d 52 61 20  8c 20 f1 22 46 61 73 74  |. Rb=Ra . ."Fast|
00002280  4d 75 6c 3a 52 65 67 69  73 74 65 72 73 20 4d 75  |Mul:Registers Mu|
00002290  73 74 20 62 65 20 64 69  66 66 65 72 65 6e 74 22  |st be different"|
000022a0  3a fa 0d 0d b6 40 e7 20  a4 49 6e 76 52 65 67 28  |:....@. .InvReg(|
000022b0  52 62 29 20 84 20 a4 49  6e 76 52 65 67 28 52 61  |Rb) . .InvReg(Ra|
000022c0  29 20 8c 20 f1 20 22 46  61 73 74 4d 75 6c 3a 49  |) . . "FastMul:I|
000022d0  6e 76 61 6c 69 64 20 52  65 67 69 73 74 65 72 22  |nvalid Register"|
000022e0  3a fa 0d 0d c0 15 c8 8e  20 28 63 6f 6e 73 74 25  |:....... (const%|
000022f0  20 80 20 33 29 20 ca 0d  0d ca 28 c9 20 30 2c 32  | . 3) ....(. 0,2|
00002300  3a f4 20 63 6f 6e 73 74  25 20 6f 66 20 66 6f 72  |:. const% of for|
00002310  6d 20 73 31 20 2a 20 32  5e 6e 2c 20 6e 3e 31 0d  |m s1 * 2^n, n>1.|
00002320  0d d4 1a 20 20 6e 25 3d  a4 70 6f 77 65 72 6f 66  |...  n%=.powerof|
00002330  32 28 63 6f 6e 73 74 25  29 0d 0d de 1b 20 20 63  |2(const%)....  c|
00002340  6f 6e 73 74 25 3d 63 6f  6e 73 74 25 2f 28 31 3c  |onst%=const%/(1<|
00002350  3c 6e 25 29 0d 0d e8 12  20 20 e7 20 63 6f 6e 73  |<n%)....  . cons|
00002360  74 25 3d 31 20 8c 0d 0d  f2 12 20 20 20 20 5b 4f  |t%=1 .....    [O|
00002370  50 54 20 70 61 73 73 25  0d 0d fc 34 20 20 20 20  |PT pass%...4    |
00002380  4d 4f 56 20 52 62 2c 52  61 2c 20 4c 53 4c 20 23  |MOV Rb,Ra, LSL #|
00002390  6e 25 3b 3c 2d 2d 2d 2d  2d 2d 46 41 53 54 20 4d  |n%;<------FAST M|
000023a0  55 4c 20 67 65 6e 65 72  61 74 65 64 0d 0e 06 09  |UL generated....|
000023b0  20 20 20 20 5d 0d 0e 10  07 20 20 cc 0d 0e 1a 29  |    ]....  ....)|
000023c0  20 20 20 20 5b 4f 50 54  20 a4 46 61 73 74 4d 75  |    [OPT .FastMu|
000023d0  6c 28 52 62 2c 52 61 2c  63 6f 6e 73 74 25 2c 70  |l(Rb,Ra,const%,p|
000023e0  61 73 73 25 29 0d 0e 24  34 20 20 20 20 4d 4f 56  |ass%)..$4    MOV|
000023f0  20 52 62 2c 52 62 2c 20  4c 53 4c 20 23 6e 25 3b  | Rb,Rb, LSL #n%;|
00002400  3c 2d 2d 2d 2d 2d 2d 46  41 53 54 20 4d 55 4c 20  |<------FAST MUL |
00002410  67 65 6e 65 72 61 74 65  64 0d 0e 2e 09 20 20 20  |generated....   |
00002420  20 5d 0d 0e 38 07 20 20  cd 0d 0e 42 31 c9 20 31  | ]..8.  ...B1. 1|
00002430  3a f4 20 63 6f 6e 73 74  25 20 6f 66 20 66 6f 72  |:. const% of for|
00002440  6d 20 73 31 20 2a 20 32  5e 6e 20 2b 31 2c 20 73  |m s1 * 2^n +1, s|
00002450  31 20 6f 64 64 2c 20 6e  3e 31 0d 0e 4c 15 20 20  |1 odd, n>1..L.  |
00002460  63 6f 6e 73 74 25 3d 63  6f 6e 73 74 25 2d 31 0d  |const%=const%-1.|
00002470  0e 56 1a 20 20 6e 25 3d  a4 70 6f 77 65 72 6f 66  |.V.  n%=.powerof|
00002480  32 28 63 6f 6e 73 74 25  29 0d 0e 60 1b 20 20 63  |2(const%)..`.  c|
00002490  6f 6e 73 74 25 3d 63 6f  6e 73 74 25 2f 28 31 3c  |onst%=const%/(1<|
000024a0  3c 6e 25 29 0d 0e 6a 12  20 20 e7 20 63 6f 6e 73  |<n%)..j.  . cons|
000024b0  74 25 3d 31 20 8c 0d 0e  74 12 20 20 20 20 5b 4f  |t%=1 ...t.    [O|
000024c0  50 54 20 70 61 73 73 25  0d 0e 7e 37 20 20 20 20  |PT pass%..~7    |
000024d0  41 44 44 20 52 62 2c 52  61 2c 52 61 2c 20 4c 53  |ADD Rb,Ra,Ra, LS|
000024e0  4c 20 23 6e 25 3b 3c 2d  2d 2d 2d 2d 2d 46 41 53  |L #n%;<------FAS|
000024f0  54 20 4d 55 4c 20 67 65  6e 65 72 61 74 65 64 0d  |T MUL generated.|
00002500  0e 88 09 20 20 20 20 5d  0d 0e 92 07 20 20 cc 0d  |...    ]....  ..|
00002510  0e 9c 29 20 20 20 20 5b  4f 50 54 20 a4 46 61 73  |..)    [OPT .Fas|
00002520  74 4d 75 6c 28 52 62 2c  52 61 2c 63 6f 6e 73 74  |tMul(Rb,Ra,const|
00002530  25 2c 70 61 73 73 25 29  0d 0e a6 37 20 20 20 20  |%,pass%)...7    |
00002540  41 44 44 20 52 62 2c 52  61 2c 52 62 2c 20 4c 53  |ADD Rb,Ra,Rb, LS|
00002550  4c 20 23 6e 25 3b 3c 2d  2d 2d 2d 2d 2d 46 41 53  |L #n%;<------FAS|
00002560  54 20 4d 55 4c 20 67 65  6e 65 72 61 74 65 64 0d  |T MUL generated.|
00002570  0e b0 09 20 20 20 20 5d  0d 0e ba 07 20 20 cd 0d  |...    ]....  ..|
00002580  0e c4 31 c9 20 33 3a f4  20 63 6f 6e 73 74 25 20  |..1. 3:. const% |
00002590  6f 66 20 66 6f 72 6d 20  73 31 20 2a 20 32 5e 6e  |of form s1 * 2^n|
000025a0  20 2d 31 2c 20 73 31 20  6f 64 64 2c 20 6e 3e 31  | -1, s1 odd, n>1|
000025b0  0d 0e ce 15 20 20 63 6f  6e 73 74 25 3d 63 6f 6e  |....  const%=con|
000025c0  73 74 25 2b 31 0d 0e d8  1a 20 20 6e 25 3d a4 70  |st%+1....  n%=.p|
000025d0  6f 77 65 72 6f 66 32 28  63 6f 6e 73 74 25 29 0d  |owerof2(const%).|
000025e0  0e e2 1b 20 20 63 6f 6e  73 74 25 3d 63 6f 6e 73  |...  const%=cons|
000025f0  74 25 2f 28 31 3c 3c 6e  25 29 0d 0e ec 12 20 20  |t%/(1<<n%)....  |
00002600  e7 20 63 6f 6e 73 74 25  3d 31 20 8c 0d 0e f6 12  |. const%=1 .....|
00002610  20 20 20 20 5b 4f 50 54  20 70 61 73 73 25 0d 0f  |    [OPT pass%..|
00002620  00 37 20 20 20 20 52 53  42 20 52 62 2c 52 61 2c  |.7    RSB Rb,Ra,|
00002630  52 61 2c 20 4c 53 4c 20  23 6e 25 3b 3c 2d 2d 2d  |Ra, LSL #n%;<---|
00002640  2d 2d 2d 46 41 53 54 20  4d 55 4c 20 67 65 6e 65  |---FAST MUL gene|
00002650  72 61 74 65 64 0d 0f 0a  09 20 20 20 20 5d 0d 0f  |rated....    ]..|
00002660  14 07 20 20 cc 0d 0f 1e  29 20 20 20 20 5b 4f 50  |..  ....)    [OP|
00002670  54 20 a4 46 61 73 74 4d  75 6c 28 52 62 2c 52 61  |T .FastMul(Rb,Ra|
00002680  2c 63 6f 6e 73 74 25 2c  70 61 73 73 25 29 0d 0f  |,const%,pass%)..|
00002690  28 37 20 20 20 20 52 53  42 20 52 62 2c 52 61 2c  |(7    RSB Rb,Ra,|
000026a0  52 62 2c 20 4c 53 4c 20  23 6e 25 3b 3c 2d 2d 2d  |Rb, LSL #n%;<---|
000026b0  2d 2d 2d 46 41 53 54 20  4d 55 4c 20 67 65 6e 65  |---FAST MUL gene|
000026c0  72 61 74 65 64 0d 0f 32  09 20 20 20 20 5d 0d 0f  |rated..2.    ]..|
000026d0  3c 07 20 20 cd 0d 0f 46  05 cb 0d 0f 50 0a 3d 70  |<.  ...F....P.=p|
000026e0  61 73 73 25 0d 0f 5a 04  0d 0f 64 3f f4 20 46 69  |ass%..Z...d?. Fi|
000026f0  6e 64 20 6c 65 6e 67 74  68 20 6f 66 20 62 69 74  |nd length of bit|
00002700  20 70 61 74 74 65 72 6e  20 66 72 6f 6d 20 66 69  | pattern from fi|
00002710  72 73 74 20 31 20 74 6f  20 62 69 74 20 30 20 70  |rst 1 to bit 0 p|
00002720  6f 73 69 74 69 6f 6e 0d  0f 6e 13 dd a4 62 69 74  |osition..n...bit|
00002730  70 61 74 6c 65 6e 28 53  25 29 0d 0f 78 10 ea 20  |patlen(S%)..x.. |
00002740  53 63 6f 70 79 25 2c 6c  73 25 0d 0f 82 0d 53 63  |Scopy%,ls%....Sc|
00002750  6f 70 79 25 3d 53 25 0d  0f 8c 09 6c 73 25 3d 30  |opy%=S%....ls%=0|
00002760  0d 0f 96 10 c8 95 20 53  63 6f 70 79 25 3c 3e 30  |...... Scopy%<>0|
00002770  0d 0f a0 17 20 20 53 63  6f 70 79 25 3d 53 63 6f  |....  Scopy%=Sco|
00002780  70 79 25 3e 3e 3e 31 0d  0f aa 0c 20 20 6c 73 25  |py%>>>1....  ls%|
00002790  2b 3d 31 0d 0f b4 05 ce  0d 0f be 08 3d 6c 73 25  |+=1.........=ls%|
000027a0  0d 0f c8 04 0d 0f d2 04  0d 0f dc 2d f4 20 46 69  |...........-. Fi|
000027b0  6e 64 20 68 69 67 68 65  73 74 20 70 6f 77 65 72  |nd highest power|
000027c0  20 6f 66 20 32 20 77 68  69 63 68 20 64 69 76 69  | of 2 which divi|
000027d0  64 65 73 20 6e 0d 0f e6  12 dd a4 70 6f 77 65 72  |des n......power|
000027e0  6f 66 32 28 4e 25 29 0d  0f f0 08 ea 20 6e 25 0d  |of2(N%)..... n%.|
000027f0  0f fa 20 e7 20 4e 25 3d  30 20 8c 20 3d 30 3a f4  |.. . N%=0 . =0:.|
00002800  20 70 6f 73 73 69 62 6c  65 20 65 72 72 6f 72 0d  | possible error.|
00002810  10 04 08 6e 25 3d 30 0d  10 0e 23 c8 95 20 28 4e  |...n%=0...#.. (N|
00002820  25 20 80 20 31 29 3d 30  3a 6e 25 2b 3d 31 3a 4e  |% . 1)=0:n%+=1:N|
00002830  25 3d 4e 25 3e 3e 3e 31  3a ce 0d 10 18 07 3d 6e  |%=N%>>>1:.....=n|
00002840  25 0d 10 22 04 0d 10 2c  19 f4 20 43 68 65 63 6b  |%.."...,.. Check|
00002850  20 6f 75 74 20 72 65 67  69 73 74 65 72 73 0d 10  | out registers..|
00002860  36 11 dd a4 49 6e 76 52  65 67 28 72 65 67 29 0d  |6...InvReg(reg).|
00002870  10 40 2d 3d 28 72 65 67  3c 30 20 84 20 72 65 67  |.@-=(reg<0 . reg|
00002880  3e 31 32 29 20 3a f4 20  55 6e 73 65 6e 73 69 62  |>12) :. Unsensib|
00002890  6c 65 20 72 65 67 69 73  74 65 72 73 0d 10 4a 04  |le registers..J.|
000028a0  0d 10 54 44 f4 20 44 65  63 6f 6d 70 6f 73 65 20  |..TD. Decompose |
000028b0  61 72 67 75 6d 65 6e 74  20 69 6e 74 6f 20 6d 61  |argument into ma|
000028c0  63 68 69 6e 65 20 63 6f  64 65 20 69 6d 6d 65 64  |chine code immed|
000028d0  69 61 74 65 20 76 61 6c  75 65 20 6f 70 65 72 61  |iate value opera|
000028e0  6e 64 20 32 0d 10 5e 22  f4 20 69 66 20 70 6f 73  |nd 2..^". if pos|
000028f0  73 69 62 6c 65 2c 20 65  6c 73 65 20 72 65 74 75  |sible, else retu|
00002900  72 6e 20 2d 31 2e 0d 10  68 42 f4 20 49 45 20 69  |rn -1...hB. IE i|
00002910  6e 74 6f 20 61 6e 20 38  20 62 69 74 20 63 68 75  |nto an 8 bit chu|
00002920  6e 6b 20 27 49 6d 6d 27  20 26 20 61 20 34 20 62  |nk 'Imm' & a 4 b|
00002930  69 74 20 72 6f 74 61 74  69 6f 6e 20 27 52 6f 74  |it rotation 'Rot|
00002940  61 74 65 27 2c 20 73 74  0d 10 72 30 f4 20 31 32  |ate', st..r0. 12|
00002950  20 62 69 74 20 20 20 20  20 20 20 20 20 20 6f 70  | bit          op|
00002960  65 72 61 6e 64 20 3d 20  52 6f 74 61 74 65 3c 3c  |erand = Rotate<<|
00002970  38 20 2b 20 49 6d 6d 2c  0d 10 7c 40 f4 20 77 68  |8 + Imm,..|@. wh|
00002980  65 72 65 20 6f 72 69 67  69 6e 61 6c 20 61 72 67  |ere original arg|
00002990  75 6d 65 6e 74 20 3d 20  49 6d 6d 20 72 6f 74 61  |ument = Imm rota|
000029a0  74 65 64 20 72 69 67 68  74 20 62 79 20 28 32 2a  |ted right by (2*|
000029b0  52 6f 74 61 74 65 29 2e  0d 10 86 10 dd 20 a4 69  |Rotate)...... .i|
000029c0  6d 6f 70 32 28 61 25 29  0d 10 90 0c ea 20 69 25  |mop2(a%)..... i%|
000029d0  2c 20 72 25 0d 10 9a 08  72 25 3d 30 0d 10 a4 13  |, r%....r%=0....|
000029e0  e3 20 69 25 3d 30 20 b8  20 33 30 20 88 20 32 0d  |. i%=0 . 30 . 2.|
000029f0  10 ae 1e e7 20 28 61 25  20 80 20 ac 20 32 35 35  |.... (a% . . 255|
00002a00  29 3d 30 20 8c 20 3d 20  72 25 84 61 25 0d 10 b8  |)=0 . = r%.a%...|
00002a10  2d 61 25 20 3d 20 28 61  25 3e 3e 3e 33 30 29 20  |-a% = (a%>>>30) |
00002a20  84 20 28 61 25 3c 3c 32  29 20 3a f4 20 69 65 20  |. (a%<<2) :. ie |
00002a30  72 6f 74 20 6c 65 66 74  20 32 0d 10 c2 0c 72 25  |rot left 2....r%|
00002a40  2b 3d 20 32 35 36 0d 10  cc 05 ed 0d 10 d6 08 3d  |+= 256.........=|
00002a50  20 2d 31 0d 10 e0 04 0d  10 ea 44 f4 20 52 65 63  | -1.......D. Rec|
00002a60  61 6c 6c 20 69 6e 20 4d  4f 56 20 52 6e 2c 20 23  |all in MOV Rn, #|
00002a70  76 25 2c 20 74 68 65 72  65 20 69 73 20 61 20 72  |v%, there is a r|
00002a80  65 73 74 72 69 63 74 69  6f 6e 20 6f 6e 20 70 65  |estriction on pe|
00002a90  72 6d 69 74 74 65 64 20  76 25 2e 0d 10 f4 42 f4  |rmitted v%....B.|
00002aa0  20 46 6f 6c 6c 6f 77 69  6e 67 20 66 75 6e 63 74  | Following funct|
00002ab0  69 6f 6e 20 61 73 73 65  6d 62 6c 65 73 20 61 20  |ion assembles a |
00002ac0  6d 75 6c 74 69 2d 69 6e  73 74 72 75 63 74 69 6f  |multi-instructio|
00002ad0  6e 20 6d 6f 76 20 63 61  70 61 62 6c 65 0d 10 fe  |n mov capable...|
00002ae0  1e f4 20 6f 66 20 74 61  6b 69 6e 67 20 61 6e 79  |.. of taking any|
00002af0  20 33 32 2d 62 69 74 20  76 25 2e 0d 11 08 42 f4  | 32-bit v%....B.|
00002b00  20 41 69 6d 20 69 73 20  74 6f 20 61 63 68 69 65  | Aim is to achie|
00002b10  76 65 20 74 68 69 73 20  75 73 69 6e 67 20 61 73  |ve this using as|
00002b20  20 66 65 77 20 69 6e 73  74 72 75 63 74 69 6f 6e  | few instruction|
00002b30  73 20 61 73 20 70 6f 73  73 69 62 6c 65 0d 11 12  |s as possible...|
00002b40  3f f4 20 66 6f 72 20 65  61 63 68 20 76 61 6c 75  |?. for each valu|
00002b50  65 20 6f 66 20 76 25 20  28 6e 65 76 65 72 20 6e  |e of v% (never n|
00002b60  65 65 64 20 6d 6f 72 65  20 74 68 61 6e 20 34 2c  |eed more than 4,|
00002b70  20 6f 66 20 63 6f 75 72  73 65 29 2e 0d 11 1c 05  | of course).....|
00002b80  f4 0d 11 26 35 f4 20 2d  20 57 65 6c 6c 2c 20 61  |...&5. - Well, a|
00002b90  63 74 75 61 6c 6c 79 20  66 6f 6c 6c 6f 77 69 6e  |ctually followin|
00002ba0  67 20 69 73 6e 27 74 20  71 75 69 74 65 20 6f 70  |g isn't quite op|
00002bb0  74 69 6d 61 6c 3a 0d 11  30 43 f4 20 49 74 20 6c  |timal:..0C. It l|
00002bc0  6f 6f 6b 73 20 66 6f 72  20 74 68 65 20 6c 6f 6e  |ooks for the lon|
00002bd0  67 65 73 74 20 73 65 71  75 65 6e 63 65 20 6f 66  |gest sequence of|
00002be0  20 7a 65 72 6f 20 62 69  74 73 2c 20 26 20 74 68  | zero bits, & th|
00002bf0  65 6e 20 73 70 6c 69 74  73 0d 11 3a 3d f4 20 72  |en splits..:=. r|
00002c00  65 73 74 20 69 6e 74 6f  20 38 20 62 69 74 20 63  |est into 8 bit c|
00002c10  68 75 6e 6b 73 20 61 73  73 69 67 6e 69 6e 67 20  |hunks assigning |
00002c20  66 69 72 73 74 20 75 73  69 6e 67 20 4d 4f 56 20  |first using MOV |
00002c30  26 20 65 61 63 68 0d 11  44 28 f4 20 73 75 62 73  |& each..D(. subs|
00002c40  65 71 75 65 6e 74 20 6e  6f 6e 2d 7a 65 72 6f 20  |equent non-zero |
00002c50  6f 6e 65 20 75 73 69 6e  67 20 4f 52 52 2e 0d 11  |one using ORR...|
00002c60  4e 40 f4 20 49 66 20 79  6f 75 20 77 65 72 65 20  |N@. If you were |
00002c70  74 6f 20 72 65 70 65 61  74 20 61 6c 67 6f 20 62  |to repeat algo b|
00002c80  65 6c 6f 77 2c 20 62 75  74 20 6c 6f 6f 6b 69 6e  |elow, but lookin|
00002c90  67 20 66 6f 72 20 6c 6f  6e 67 20 73 65 71 0d 11  |g for long seq..|
00002ca0  58 44 f4 20 6f 66 20 31  27 73 20 69 6e 73 74 65  |XD. of 1's inste|
00002cb0  61 64 20 6f 66 20 7a 65  72 6f 73 2c 20 26 20 75  |ad of zeros, & u|
00002cc0  73 65 64 20 61 20 20 73  69 6d 69 6c 61 72 20 70  |sed a  similar p|
00002cd0  72 6f 63 65 73 73 20 74  6f 20 62 65 6c 6f 77 20  |rocess to below |
00002ce0  74 6f 0d 11 62 44 f4 20  62 75 69 6c 64 20 6d 6f  |to..bD. build mo|
00002cf0  76 20 75 73 69 6e 67 20  4d 56 4e 20 26 20 42 49  |v using MVN & BI|
00002d00  43 20 74 6f 20 73 70 65  63 69 66 79 20 30 27 73  |C to specify 0's|
00002d10  20 28 69 6e 73 74 65 61  64 20 6f 66 20 4d 4f 56  | (instead of MOV|
00002d20  20 26 20 4f 52 52 0d 11  6c 42 f4 20 74 6f 20 73  | & ORR..lB. to s|
00002d30  70 65 63 69 66 79 20 31  27 73 29 2c 20 74 68 69  |pecify 1's), thi|
00002d40  73 20 77 6f 75 6c 64 20  69 6e 20 73 6f 6d 65 20  |s would in some |
00002d50  63 61 73 65 73 20 79 69  65 6c 64 20 62 65 74 74  |cases yield bett|
00002d60  65 72 20 73 6f 6c 6e 2e  0d 11 76 26 f4 20 53 6f  |er soln...v&. So|
00002d70  2c 20 69 64 65 61 6c 6c  79 20 64 6f 20 62 6f 74  |, ideally do bot|
00002d80  68 20 26 20 70 69 63 6b  20 62 65 73 74 2e 0d 11  |h & pick best...|
00002d90  80 3f f4 20 4e 42 20 54  68 61 74 20 73 74 69 6c  |.?. NB That stil|
00002da0  6c 20 77 6f 75 6c 64 6e  27 74 20 62 65 20 6f 70  |l wouldn't be op|
00002db0  74 69 6d 61 6c 2c 20 62  75 74 20 69 74 20 6d 69  |timal, but it mi|
00002dc0  67 68 74 20 62 65 20 63  6c 6f 73 65 2e 0d 11 8a  |ght be close....|
00002dd0  05 f4 0d 11 94 22 f4 20  41 6e 79 6f 6e 65 20 6b  |.....". Anyone k|
00002de0  6e 6f 77 20 6f 66 20 61  20 62 65 74 74 65 72 20  |now of a better |
00002df0  77 61 79 3f 0d 11 9e 05  f4 0d 11 a8 1d dd 20 a4  |way?.......... .|
00002e00  6d 65 67 61 6d 6f 76 28  61 25 2c 20 76 25 2c 20  |megamov(a%, v%, |
00002e10  70 61 73 73 25 29 0d 11  b2 1f ea 20 69 25 2c 20  |pass%)..... i%, |
00002e20  6d 25 2c 20 72 25 2c 20  6d 69 25 2c 20 6d 6c 25  |m%, r%, mi%, ml%|
00002e30  2c 20 6c 69 25 0d 11 bc  0c e7 20 76 25 3d 30 20  |, li%..... v%=0 |
00002e40  8c 0d 11 c6 0f 20 5b 4f  50 54 20 70 61 73 73 25  |..... [OPT pass%|
00002e50  0d 11 d0 10 20 20 4d 4f  56 20 61 25 2c 20 23 30  |....  MOV a%, #0|
00002e60  0d 11 da 06 20 5d 0d 11  e4 0c 20 3d 20 70 61 73  |.... ].... = pas|
00002e70  73 25 0d 11 ee 05 cd 0d  11 f8 58 72 25 3d 30 20  |s%........Xr%=0 |
00002e80  3a f4 20 4e 6f 77 20 6e  65 65 64 20 74 6f 20 66  |:. Now need to f|
00002e90  69 6e 64 20 74 68 65 20  6c 6f 6e 67 65 73 74 20  |ind the longest |
00002ea0  73 70 61 6e 20 6f 66 20  7a 65 72 6f 73 2c 20 61  |span of zeros, a|
00002eb0  6c 6c 6f 77 69 6e 67 20  62 69 74 20 77 72 61 70  |llowing bit wrap|
00002ec0  20 66 72 6f 6d 20 62 30  20 74 6f 20 62 33 31 0d  | from b0 to b31.|
00002ed0  12 02 2c c8 95 20 28 76  25 80 31 29 3d 30 20 3a  |..,.. (v%.1)=0 :|
00002ee0  f4 20 72 6f 74 61 74 65  20 74 6f 20 67 65 74 20  |. rotate to get |
00002ef0  61 20 31 20 69 6e 74 6f  20 62 30 0d 12 0c 1d 20  |a 1 into b0.... |
00002f00  76 25 20 3d 20 28 76 25  3e 3e 3e 33 31 29 20 84  |v% = (v%>>>31) .|
00002f10  20 28 76 25 3c 3c 31 29  0d 12 16 0b 20 72 25 2b  | (v%<<1).... r%+|
00002f20  3d 20 31 0d 12 20 05 ce  0d 12 2a 08 69 25 3d 30  |= 1.. ....*.i%=0|
00002f30  0d 12 34 08 6d 25 3d 31  0d 12 3e 30 6d 6c 25 3d  |..4.m%=1..>0ml%=|
00002f40  30 20 3a f4 20 4c 65 6e  67 74 68 20 6f 66 20 6c  |0 :. Length of l|
00002f50  6f 6e 67 65 73 74 20 73  65 71 75 65 6e 63 65 20  |ongest sequence |
00002f60  6f 66 20 7a 65 72 6f 73  0d 12 48 05 f5 0d 12 52  |of zeros..H....R|
00002f70  30 20 f5 20 3a f4 20 73  63 61 6e 20 74 69 6c 6c  |0 . :. scan till|
00002f80  20 67 65 74 20 7a 65 72  6f 20 6f 72 20 61 6c 6c  | get zero or all|
00002f90  20 62 69 74 73 20 63 68  65 63 6b 65 64 0d 12 5c  | bits checked..\|
00002fa0  0c 20 20 69 25 2b 3d 20  31 0d 12 66 10 20 20 6d  |.  i%+= 1..f.  m|
00002fb0  25 20 3d 20 6d 25 3c 3c  31 0d 12 70 1c 20 fd 20  |% = m%<<1..p. . |
00002fc0  28 69 25 3e 33 31 29 20  84 20 28 28 76 25 80 6d  |(i%>31) . ((v%.m|
00002fd0  25 29 3d 30 29 0d 12 7a  10 20 e7 20 28 69 25 3c  |%)=0)..z. . (i%<|
00002fe0  33 32 29 20 8c 0d 12 84  2a 20 20 6c 69 25 20 3d  |32) ....*  li% =|
00002ff0  20 69 25 20 3a f4 20 73  74 61 72 74 20 6f 66 20  | i% :. start of |
00003000  61 20 7a 65 72 6f 20 73  65 71 75 65 6e 63 65 0d  |a zero sequence.|
00003010  12 8e 07 20 20 f5 0d 12  98 0d 20 20 20 69 25 2b  |...  .....   i%+|
00003020  3d 20 31 0d 12 a2 11 20  20 20 6d 25 20 3d 20 6d  |= 1....   m% = m|
00003030  25 3c 3c 31 0d 12 ac 1e  20 20 fd 20 28 69 25 3e  |%<<1....  . (i%>|
00003040  33 31 29 20 84 20 28 28  76 25 80 6d 25 29 3c 3e  |31) . ((v%.m%)<>|
00003050  30 29 0d 12 b6 52 20 20  e7 20 28 69 25 2d 6c 69  |0)...R  . (i%-li|
00003060  25 29 3e 6d 6c 25 20 8c  20 6d 69 25 3d 6c 69 25  |%)>ml% . mi%=li%|
00003070  3a 6d 6c 25 3d 69 25 2d  6c 69 25 20 3a f4 20 73  |:ml%=i%-li% :. s|
00003080  74 61 72 74 20 6f 66 20  6c 6f 6e 67 65 73 74 20  |tart of longest |
00003090  7a 65 72 6f 20 73 65 71  75 65 6e 63 65 20 73 6f  |zero sequence so|
000030a0  20 66 61 72 0d 12 c0 06  20 cd 0d 12 ca 0b fd 20  | far.... ...... |
000030b0  69 25 3e 33 31 0d 12 d4  0d e7 20 6d 6c 25 3e 30  |i%>31..... ml%>0|
000030c0  20 8c 0d 12 de 40 20 f4  20 73 68 69 66 74 20 74  | ....@ . shift t|
000030d0  6f 20 67 65 74 20 7a 65  72 6f 20 73 65 71 75 65  |o get zero seque|
000030e0  6e 63 65 20 69 6e 20 6d  6f 73 74 20 73 69 67 6e  |nce in most sign|
000030f0  69 66 69 63 61 6e 74 20  62 69 74 73 20 6f 66 20  |ificant bits of |
00003100  76 25 0d 12 e8 16 20 69  25 20 3d 20 33 32 2d 28  |v%.... i% = 32-(|
00003110  6d 69 25 2b 6d 6c 25 29  0d 12 f2 23 20 76 25 20  |mi%+ml%)...# v% |
00003120  3d 20 28 76 25 3e 3e 3e  28 33 32 2d 69 25 29 29  |= (v%>>>(32-i%))|
00003130  20 84 20 28 76 25 3c 3c  69 25 29 0d 12 fc 0c 20  | . (v%<<i%).... |
00003140  72 25 2b 3d 20 69 25 0d  13 06 05 cd 0d 13 10 0c  |r%+= i%.........|
00003150  e7 20 72 25 80 31 20 8c  0d 13 1a 16 20 f4 20 72  |. r%.1 ..... . r|
00003160  25 20 6d 75 73 74 20 62  65 20 65 76 65 6e 0d 13  |% must be even..|
00003170  24 1d 20 76 25 20 3d 20  28 76 25 3e 3e 3e 33 31  |$. v% = (v%>>>31|
00003180  29 20 84 20 28 76 25 3c  3c 31 29 0d 13 2e 0b 20  |) . (v%<<1).... |
00003190  72 25 2b 3d 20 31 0d 13  38 05 cd 0d 13 42 04 0d  |r%+= 1..8....B..|
000031a0  13 4c 1f f4 20 6e 6f 77  20 64 6f 20 74 68 65 20  |.L.. now do the |
000031b0  6d 6f 76 65 2c 20 61 74  20 6c 61 73 74 21 0d 13  |move, at last!..|
000031c0  56 0f 69 25 20 3d 20 76  25 80 32 35 35 0d 13 60  |V.i% = v%.255..`|
000031d0  0e 5b 4f 50 54 20 70 61  73 73 25 0d 13 6a 37 20  |.[OPT pass%..j7 |
000031e0  4d 4f 56 20 61 25 2c 20  23 28 69 25 3e 3e 3e 72  |MOV a%, #(i%>>>r|
000031f0  25 29 20 84 20 28 69 25  3c 3c 28 33 32 2d 72 25  |%) . (i%<<(32-r%|
00003200  29 29 20 3a f4 20 69 65  20 69 25 20 72 6f 72 20  |)) :. ie i% ror |
00003210  72 25 0d 13 74 05 5d 0d  13 7e 05 f5 0d 13 88 10  |r%..t.]..~......|
00003220  20 76 25 20 3d 20 76 25  3e 3e 3e 38 0d 13 92 17  | v% = v%>>>8....|
00003230  20 e7 20 28 76 25 3d 30  29 20 8c 20 3d 20 70 61  | . (v%=0) . = pa|
00003240  73 73 25 0d 13 9c 15 20  72 25 20 3d 20 33 31 20  |ss%.... r% = 31 |
00003250  80 20 28 72 25 2d 38 29  0d 13 a6 10 20 69 25 20  |. (r%-8).... i% |
00003260  3d 20 76 25 80 32 35 35  0d 13 b0 0b 20 e7 20 69  |= v%.255.... . i|
00003270  25 20 8c 0d 13 ba 10 20  20 5b 4f 50 54 20 70 61  |% .....  [OPT pa|
00003280  73 73 25 0d 13 c4 2c 20  20 20 84 52 20 61 25 2c  |ss%...,   .R a%,|
00003290  20 61 25 2c 20 23 28 69  25 3e 3e 3e 72 25 29 20  | a%, #(i%>>>r%) |
000032a0  84 20 28 69 25 3c 3c 28  33 32 2d 72 25 29 29 0d  |. (i%<<(32-r%)).|
000032b0  13 ce 07 20 20 5d 0d 13  d8 06 20 cd 0d 13 e2 07  |...  ].... .....|
000032c0  fd 20 a3 0d 13 ec 0b 3d  20 70 61 73 73 25 0d 13  |. .....= pass%..|
000032d0  f6 04 0d 14 00 12 dd 20  f2 64 69 73 28 61 25 2c  |....... .dis(a%,|
000032e0  20 62 25 29 0d 14 0a 14  ea 20 71 25 2c 20 77 25  | b%)..... q%, w%|
000032f0  2c 20 71 24 2c 20 69 25  0d 14 14 16 e3 20 71 25  |, q$, i%..... q%|
00003300  3d 61 25 20 b8 20 62 25  2d 31 20 88 20 34 0d 14  |=a% . b%-1 . 4..|
00003310  1e 20 20 c8 99 20 26 34  30 33 38 30 2c 20 21 71  |.  .. &40380, !q|
00003320  25 2c 20 71 25 20 b8 20  2c 78 25 2c 79 25 0d 14  |%, q% . ,x%,y%..|
00003330  28 0a 20 71 24 3d 22 22  0d 14 32 16 20 e3 20 77  |(. q$=""..2. . w|
00003340  25 3d 78 25 20 b8 20 78  25 2b 79 25 2d 31 0d 14  |%=x% . x%+y%-1..|
00003350  3c 10 20 20 71 24 2b 3d  bd 28 3f 77 25 29 0d 14  |<.  q$+=.(?w%)..|
00003360  46 06 20 ed 0d 14 50 13  20 69 25 20 3d 20 a7 71  |F. ...P. i% = .q|
00003370  24 2c 20 22 3b 22 29 0d  14 5a 0d 20 e7 20 69 25  |$, ";")..Z. . i%|
00003380  3e 31 20 8c 0d 14 64 18  20 20 e3 20 77 25 3d 69  |>1 ...d.  . w%=i|
00003390  25 2d 31 20 b8 20 31 20  88 20 2d 31 0d 14 6e 1d  |%-1 . 1 . -1..n.|
000033a0  20 20 20 e7 20 c1 71 24  2c 20 77 25 2c 20 31 29  |   . .q$, w%, 1)|
000033b0  20 3c 3e 20 22 20 22 20  8c 0d 14 78 15 20 20 20  | <> " " ...x.   |
000033c0  20 71 24 20 3d 20 c0 71  24 2c 20 77 25 29 0d 14  | q$ = .q$, w%)..|
000033d0  82 0c 20 20 20 20 77 25  3d 30 0d 14 8c 08 20 20  |..    w%=0....  |
000033e0  20 cd 0d 14 96 07 20 20  ed 0d 14 a0 06 20 cd 0d  | .....  ..... ..|
000033f0  14 aa 09 20 f1 20 71 24  0d 14 b4 05 ed 0d 14 be  |... . q$........|
00003400  05 e1 0d 14 c8 04 0d 14  d2 0f dd 20 a4 6e 73 74  |........... .nst|
00003410  72 28 6e 25 29 0d 14 dc  13 e7 20 94 28 6e 25 29  |r(n%)..... .(n%)|
00003420  3c 36 35 35 33 36 20 8c  0d 14 e6 0c 20 3d 20 c3  |<65536 ..... = .|
00003430  28 6e 25 29 0d 14 f0 05  cc 0d 14 fa 11 20 3d 20  |(n%)......... = |
00003440  22 26 22 2b c3 7e 28 6e  25 29 0d 15 04 05 cd 0d  |"&"+.~(n%)......|
00003450  15 0e 04 0d 15 18 0a dd  20 f2 65 72 72 0d 15 22  |........ .err.."|
00003460  09 ee 20 85 20 87 0d 15  2c 1a f6 3a f1 22 20 77  |.. . ...,..:." w|
00003470  69 74 68 20 63 6f 64 65  3a 20 22 3b 9e 2f 31 30  |ith code: ";./10|
00003480  0d 15 36 0e e7 20 73 70  6f 6f 6c 25 20 8c 0d 15  |..6.. spool% ...|
00003490  40 0b 20 2a 53 70 6f 6f  6c 0d 15 4a 0d 20 73 70  |@. *Spool..J. sp|
000034a0  6f 6f 6c 25 3d a3 0d 15  54 25 20 ff 28 22 53 65  |ool%=...T% .("Se|
000034b0  74 54 79 70 65 20 22 2b  73 70 6f 6f 6c 70 61 74  |tType "+spoolpat|
000034c0  68 24 2b 22 20 54 65 78  74 22 29 0d 15 5e 05 cd  |h$+" Text")..^..|
000034d0  0d 15 68 05 e1 0d ff                              |..h....|
000034d7