(09-13-2022, 06:59 PM)Jack Wrote: bplus, the log and exp are done in double precision as part of the first approximation, I don't see a problem with that, also what if you want to take the root of a huge number?
for example
31415926535897932384626433832795028841971693993751058209749445923078164062862089986280348253421170679821480865132823066470938446095505822317253594081284811174502841027019385211055596446229489549303819644288109756659334461284756482337867831652712019091456485669234603486104543266482133936072602491412737245870066063155881748815209209628292540917153643678925903600113305305488204665213841469519415116094330572703657595919530921861173819326117931051185480744623799627495673518857527248912279381830119491298336733624406566430860213949463952247371907021798609437027705392171762931767523846748184676694051320005681271452635608277857713427577896091736371787214684409012249534301465495853710507922796892589235420199561121290219608640344181598136297747713099605187072113499999983729780499510597317328160963185950244594553469083026425223082533446850352619311881710100031378387528865875332083814206171776691473035982534904287554687311595628638823537875937519577818577805321712268066130019278766111959092164201989 ^ (1/3)
I have split the first approximation to allow for larger exponents than double allows
instead of t2 = Log(t) / p + Log(10) * ex / p, do
t2 = Log(t) / p
t2 = Exp(t2)
str2fp ry, Str$(t2) 'convert the double t2 to decfloat in ry
t = Log(10) * ex / p
t2 = Exp(t - Fix(t))
str2fp tmp, Str$(t2) 'convert the double t2 to decfloat in tmp
fpmul ry, ry, tmp, prec
str2fp tmp, "2.7182818284590452353602874713527"
fpipow tmp, tmp, Fix(t), 24
fpmul ry, ry, tmp, prec
basically it does the following
here the value of x is split into a fractional part and a base 10 exponent, so if x = 3.14159e2000 then frac_x=3.14159 and ex=2000
first approximation =
exp(log(frac_x) / p) * exp(fix(ex/p)) * exp(frac(ex/p)) 'here frac is the fractional part of expression
I tried this out with my string math Newton method and in 300 iterations got:
3155367569301821867326519405336421207498251961314999997901193388809739079012897744887631254739292007907947433618484758481627548989501719089220482459948775432816342410555282540612960501433021296640960423450227920209938211887719077129428385543361947758023983184697480787087966223432486682721792221472648796720202642738747343051078071241.1117071041521464114467665711102448773294129185086168601317116963185840973781697545265065162416345701960981890223171963919001466208647505186686688214089040608753503438578563616725892063902904031115393739976591472520070482477893735495911139188769943267929855525949446230204126900153007732827612762319412945242149116780371747470206338539664157784440481347746085970295430028320843441298257423953610577963963949129300606668858848121206003518186891859385615602534889346333454621516856947153242770387046690053536732721613842936129950903162157547041886847070767874866662505338899454778151212530761556961371244325097728839734967258370200043173928708494473297733210411715984593169290517702411869427839950464670060349819760147612661909441546958517699224130778087110443124358261707076171153443438495681205599420721937187851525696893584001727191760274149236224353644424090955353510261465763750332840754794617508053971409028884388363664964752877980030249110322873254352734271785400456477991026383527973330108928903271467756263321278894522083868571618282515818461381943038367779552617133598991116964887655701157012974067987940699411399501229096552888963789307921632996569433309896456328377371297669783052361470311472211
Qube that answer and we get:
31415926535897932384626433832795028841971693993751058209749445923078164062862089986280348253421170679821480865132823066470938446095505822317253594081284811174502841027019385211055596446229489549303819644288109756659334461284756482337867831652712019091456485669234603486104543266482133936072602491412737245870066063155881748815209209628292540917153643678925903600113305305488204665213841469519415116094330572703657595919530921861173819326117931051185480744623799627495673518857527248912279381830119491298336733624406566430860213949463952247371907021798609437027705392171762931767523846748184676694051320005681271452635608277857713427577896091736371787214684409012249534301465495853710507922796892589235420199561121290219608640344181598136297747713099605187072113499999983729780499510597317328160963185950244594553469083026425223082533446850352619311881710100031378387528865875332083814206171776691473035982534904287554687311595628638823537875937519577818577805321712268066130019278766111959092164201989.000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000603499005139366862799701780720158591410366351998129151511119525687388749502797039682234552131747456613792066033484465152215809841804291448971276204046929625487309185281858037724869323483434152864858964962994001836657061656106352620454324148283376076399490345337954627590065806114045867049052326544516109184526712585489406993500328338398198408461889212477292574781998715931861578961152941542876486164940515418178077033851931868282699884213321398226844876483100577921117201183608525521876800029277538167845818865776704783972229142090194304398125633856083142539675220841343105833147855969761212488889068336718053011348609919308647064997293549061755379552770378475493541876952345373313969858594175197125353608135184548862740674157528924231852223405208449504748388921445240958214690995810105025065423855693672088622863753117064768322664890025536617798854536218488816791848538821446950866269851253733911386611361910540274644323253232874172081162346914699996142266777798954022070123212527344388924719217925914386633353072987330648829157403550708115027223200044807883656469347663655876969648987101678645940222022831480079400768418299325559664895684045999255371982432620239090677375662502747701542703358133368428665082731835860910000665702147427296276045564628750796535846183280725239965866623509246666148961072282514122502077078743852037518058193632425928923084786277291885961300536668681338313110684273723118785419227857031392445436462972677644980466766435357102613205226750122405761223701269699916778576569554050536346411140767860976270187630791949828546645057030248690468772912088596795560468444063512633185518997406170826723372775379876955170922403298311843012025288476087485121551879800953646194661776016049207809926994868956877276788933438172018961190857263702091141726455945984960349569883378976481691201424503846716470549678954871666104627769881334536069365184512548629329824854143087775243885679288308641597452616789909800095812019114437954817600548618681574588627849594754143169473932594598937914117840979460016740619770688788545236109486266753724433791353227792899002288778552124706192536713772490236607545877818633549777809122533461987954188757373396000734054021074761847398893009527051762586890797854285944214083130177511207817184310434788177482556340875733459076305930401101867740557129021454597311093304249357526453113349715688916583994808262174737596388796185189688284300995099114815929770078432405884155920175427576979092016431903239034848212944617640707267844664353544109998979530824698138597632254927543828879612566189320793914511582305163073365737983758502482677721478732753892280786074576136564428824243375592483381200215324298908739000854267257562524746199375548144863137863318489017325830040905355143109220371392913354012472788837467428130745760495771708768099321048804173582693961219013757642478754104803966634627299465120902984446399248781478306905405997541726676409883232468635606493479953311325416216747257599651982333093941048126219978507387638390288595752818405351078630965605875184189176621134721573958750820153788398487490359386406455645497953416129931
Woohoo! So somewhere less than 300 iterations gets the job done. Just cut off the crap afet the decimal point and it's a match.
Please note that doing this routine allowed me to find one bug in my new division routine, so DON'T try running this in the older post in this thread. Here is the one I used...
Code: (Select All)
'WIDTH 120, 42
'_SCREENMOVE 0, 0
$CONSOLE:ONLY
' Treebeard's String Math +-*/
CONST neg$ = "-"
CONST negative = -1
CONST positive = 1
CONST asc0 = 48
CONST dp_tree$ = "."
CONST zero$ = "0"
CONST one$ = "1"
CONST two$ = "2"
CONST three$ = "3"
CONST four$ = "4"
CONST five$ = "5"
CONST False = 0
CONST True = -1
CONST basechr = "@"
CONST basesep$ = ","
CONST maxlongdig = 8
CONST emem = 32
CONST memget = 0
CONST memput = 1
CONST defaultdigits = 30
CONST maxmem = 35
CONST maxstack = 10
CONST minconst = 30
CONST maxconst = 35
CONST pimem = 30
CONST pi2mem = 31
CONST phimem = 33
CONST ln10mem = 34
CONST ln2mem = 35
CONST memclr = 2
'useful shared stuff, initialize these in bInit()
DIM SHARED errormsg$, abortmsg$, Error$, bmem$(maxmem), out$
DIM SHARED zmem$(maxstack), cname$(maxconst)
DIM SHARED bncpath$, prmcntfile$
DIM SHARED digits%, zstack%
'Prime count table data
DIM maxprmcnt%
DIM prmcnt&
digits% = 16
'--------------------------------------------
DIM SHARED limit&&, betatest%: betatest% = 0 '-1
n$ = "31415926535897932384626433832795028841971693993751058209749445923078164062862089986280348253421170679821480865132823066470938446095505822317253594081284811174502841027019385211055596446229489549303819644288109756659334461284756482337867831652712019091456485669234603486104543266482133936072602491412737245870066063155881748815209209628292540917153643678925903600113305305488204665213841469519415116094330572703657595919530921861173819326117931051185480744623799627495673518857527248912279381830119491298336733624406566430860213949463952247371907021798609437027705392171762931767523846748184676694051320005681271452635608277857713427577896091736371787214684409012249534301465495853710507922796892589235420199561121290219608640344181598136297747713099605187072113499999983729780499510597317328160963185950244594553469083026425223082533446850352619311881710100031378387528865875332083814206171776691473035982534904287554687311595628638823537875937519577818577805321712268066130019278766111959092164201989"
limit&& = LEN(n$) + 8
digits% = limit&&: PRINT n$, LEN(n$): PRINT
REM Newton's Square Root Algorithm expanded for general roots...
REM a - ((a) ^ root - n) / (root * a ^ (root - 1))
DO
INPUT "Enter 1 for Pete's string math or 2 for Treebeard's: "; choice
IF choice < 1 OR choice > 2 THEN RUN
a$ = "314159265358979323846264338327950288419716939937510582097494459230781640628620899862803482534211706798214808651328230664709384460955058223172535940812848111745028410270193852110555964462294895493038196442881097566593344612847564823378678316527120190914564856692346034861045432664821339360726024914127372458700660631558817488152092096"
''LINE INPUT "Number: "; n$
''LINE INPUT "Root: "; root$
root$ = "3"
DO
temp1$ = sm_sub$(root$, "1")
IF betatest% = 1 THEN PRINT "root - 1 ="; temp1$
i&& = 1: temp2$ = a$
DO UNTIL LTRIM$(STR$(i&&)) = temp1$
i&& = i&& + 1
IF choice = 1 THEN
temp2$ = sm_mult$(a$, temp2$)
ELSE
bMul a$, temp2$, x$: temp2$ = x$
END IF
LOOP
IF betatest% = 1 THEN PRINT "a$, temp2$: "; a$; " * "; temp2$
IF choice = 1 THEN
sqrt_divisor$ = sm_mult$(temp2$, root$)
ELSE
bMul temp2$, root$, sqrt_divisor$
END IF
IF betatest% = 1 THEN PRINT "divisor$ = "; sqrt_divisor$
temp2$ = a$: i&& = 1
DO UNTIL LTRIM$(STR$(i&&)) = root$
i&& = i&& + 1
IF choice = 1 THEN
temp2$ = sm_mult$(a$, temp2$)
ELSE
bMul a$, temp2$, x$: temp2$ = x$
END IF
''COLOR 8: PRINT i&&, temp2$: COLOR 7: SLEEP
LOOP
IF betatest% = 1 THEN PRINT "a^root, n$: "; temp2$; " - "; n$
IF choice = 1 THEN
sqrt_dividend$ = sm_sub$(temp2$, n$)
ELSE
bSub temp2$, n$, sqrt_dividend$
END IF
IF betatest% = 1 THEN PRINT "dividend$ = "; sqrt_dividend$
IF choice = 1 THEN
temp1$ = sm_div$(sqrt_dividend$, sqrt_divisor$)
ELSE
bDiv sqrt_dividend$, sqrt_divisor$, temp1$
END IF
IF betatest% = 1 THEN COLOR 15: PRINT "a$ = "; a$; " - "; "temp1$ = "; temp1$, sqrt_dividend$, sqrt_divisor$: COLOR 7
IF betatest% = 1 THEN PRINT "a$, dividend$, divisor$: "; a$; " - "; sqrt_dividend$; " / "; sqrt_divisor$
IF choice = 1 THEN
a$ = sm_sub$(a$, temp1$)
ELSE
bSub a$, temp1$, x$: a$ = x$
END IF
PRINT "Iteration"; v + 1; a$: PRINT
v = v + 1
LOOP UNTIL v = 300
_CLIPBOARD$ = a$
PRINT STRING$(_WIDTH, "-"): PRINT
v = 0
LOOP
SUB sm_greater_lesser (stringmatha$, stringmathb$, gl%)
compa$ = stringmatha$: compb$ = stringmathb$ ' So original variables do not get changed.
DO
WHILE -1 ' Falx loop.
IF gl% = 2 THEN EXIT WHILE ' For bypassing sign and decimal adjustments when only positive non-decimal numbers are being evaluated.
' Remove trailing zeros after a decimal point.
IF INSTR(compa$, ".") THEN
DO UNTIL RIGHT$(compa$, 1) <> "0" AND RIGHT$(compa$, 1) <> "." AND RIGHT$(compa$, 1) <> "-"
compa$ = MID$(compa$, 1, LEN(compa$) - 1)
LOOP
END IF
IF INSTR(compb$, ".") THEN
DO UNTIL RIGHT$(compb$, 1) <> "0" AND RIGHT$(compb$, 1) <> "." AND RIGHT$(compb$, 1) <> "-"
compb$ = MID$(compb$, 1, LEN(compb$) - 1)
LOOP
END IF
IF MID$(compa$, 1, 2) = "-0" OR compa$ = "" OR compa$ = "-" THEN compa$ = "0"
IF MID$(compb$, 1, 2) = "-0" OR compb$ = "" OR compb$ = "-" THEN compb$ = "0"
' A - and +
j% = 0: k% = 0
IF LEFT$(compa$, 1) = "-" THEN j% = -1
IF LEFT$(compb$, 1) = "-" THEN k% = -1
IF k% = 0 AND j% THEN gl% = -1: EXIT DO
IF j% = 0 AND k% THEN gl% = 1: EXIT DO
j&& = INSTR(compa$, ".")
k&& = INSTR(compb$, ".")
' A starting decimal and non-decimal.
IF j&& = 0 AND k&& = 1 THEN
IF compa$ = "0" THEN gl% = -1 ELSE gl% = 1
EXIT DO
END IF
IF k&& = 0 AND j&& = 1 THEN
IF compb$ = "0" THEN gl% = 1 ELSE gl% = -1
EXIT DO
END IF
' remove decimals and align.
j2&& = 0: k2&& = 0
IF j&& <> 0 OR k&& <> 0 THEN
IF j&& THEN compa$ = MID$(compa$, 1, INSTR(compa$, ".") - 1) + MID$(compa$, INSTR(compa$, ".") + 1): j2&& = LEN(compa$) - j&& + 1
IF k&& THEN compb$ = MID$(compb$, 1, INSTR(compb$, ".") - 1) + MID$(compb$, INSTR(compb$, ".") + 1): k2&& = LEN(compb$) - k&& + 1
compa$ = compa$ + STRING$(k2&& - j2&&, "0")
compb$ = compb$ + STRING$(j2&& - k2&&, "0")
END IF
EXIT WHILE
WEND
' Remove leading zeros if any.
DO UNTIL LEFT$(compa$, 1) <> "0"
compa$ = MID$(compa$, 2)
LOOP
IF compa$ = "" THEN compa$ = "0"
DO UNTIL LEFT$(compb$, 1) <> "0"
compb$ = MID$(compb$, 2)
LOOP
IF compb$ = "" THEN compb$ = "0"
' Both positive or both negative whole numbers.
SELECT CASE LEN(compa$)
CASE IS < LEN(compb$)
gl% = -1
CASE IS = LEN(compb$)
IF compa$ = compb$ THEN
gl% = 0
ELSEIF compa$ > compb$ THEN gl% = 1
ELSEIF compa$ < compb$ THEN gl% = -1
END IF
CASE IS > LEN(compb$)
gl% = 1
END SELECT
EXIT DO
LOOP
'''PRINT "<> gl% ="; gl%; " "; compa$; " "; compb$; " "; stringmatha$; " "; stringmathb$ '''''''
'''IF gl% = 1 AND VAL(compa$) <= VAL(compb$) THEN BEEP: SLEEP ''''''
'''IF gl% = -1 AND VAL(compa$) >= VAL(compb$) THEN BEEP: SLEEP '''''
END SUB
SUB sm_add_subtract_router (stringmatha$, operator$, stringmathb$, runningtotal$)
DIM AS _INTEGER64 a, c, s
a1$ = stringmatha$: b1$ = stringmathb$
s = 18: i&& = 0: c = 0
a$ = stringmatha$: b$ = stringmathb$: op$ = operator$
IF op$ = "-" THEN
IF LEFT$(b$, 1) = "-" THEN b$ = MID$(b$, 2) ELSE b$ = "-" + b$
END IF
IF INSTR(a$, ".") <> 0 OR INSTR(b$, ".") <> 0 THEN
decimal% = -1
IF INSTR(a$, ".") <> 0 THEN
dec_a&& = LEN(MID$(a$, INSTR(a$, ".") + 1))
a$ = MID$(a$, 1, INSTR(a$, ".") - 1) + MID$(a$, INSTR(a$, ".") + 1)
END IF
IF INSTR(b$, ".") <> 0 THEN
dec_b&& = LEN(MID$(b$, INSTR(b$, ".") + 1))
b$ = MID$(b$, 1, INSTR(b$, ".") - 1) + MID$(b$, INSTR(b$, ".") + 1)
END IF
' Line up decimal places by inserting trailing zeros.
IF dec_b&& > dec_a&& THEN
j&& = dec_b&&
a$ = a$ + STRING$(dec_b&& - dec_a&&, "0")
ELSE
j&& = dec_a&&
b$ = b$ + STRING$(dec_a&& - dec_b&&, "0")
END IF
END IF
IF LEFT$(a$, 1) = "-" OR LEFT$(b$, 1) = "-" THEN
IF LEFT$(a$, 1) = "-" AND LEFT$(b$, 1) = "-" THEN
sign$ = "": a$ = MID$(a$, 2): b$ = MID$(b$, 2)
ELSE
IF LEFT$(a$, 1) = "-" THEN a$ = MID$(a$, 2): sign_a$ = "-"
IF LEFT$(b$, 1) = "-" THEN b$ = MID$(b$, 2): sign_b$ = "-"
IF LEFT$(a1$, 1) = "-" THEN a1_x$ = MID$(a1$, 2) ELSE a1_x$ = a1$
IF LEFT$(b1$, 1) = "-" THEN b1_x$ = MID$(b1$, 2) ELSE b1_x$ = b1$
sm_greater_lesser a1_x$, b1_x$, gl%
IF gl% < 0 THEN
IF LEN(sign_b$) THEN sign$ = "-": SWAP a$, b$
ELSE
IF LEN(sign_a$) THEN sign$ = "-": SWAP sign_a$, sign_b$
END IF
END IF
END IF
z$ = ""
' Addition and subtraction of digits.
DO
i&& = i&& + s
x1$ = MID$(a$, LEN(a$) - i&& + 1, s)
x2$ = MID$(b$, LEN(b$) - i&& + 1, s)
IF LEN(x2$) > LEN(x1$) THEN SWAP x1$, x2$
a = VAL(sign_a$ + x1$) + VAL(sign_b$ + x2$) + c
IF x1$ + x2$ = "" AND c = 0 THEN EXIT DO
c = 0
IF a > VAL(STRING$(s, "9")) THEN a = a - 10 ^ s: c = 1
IF a < 0 THEN a = a + 10 ^ s: c = -1 ' a will never be less than 0.
tmp$ = LTRIM$(STR$(a))
z$ = STRING$(LEN(x1$) - LEN(tmp$), "0") + tmp$ + z$
LOOP
IF decimal% THEN
z$ = MID$(z$, 1, LEN(z$) - j&&) + "." + MID$(z$, LEN(z$) - j&& + 1)
END IF
' Remove any leading zeros.
DO
IF LEFT$(z$, 1) = "0" THEN z$ = MID$(z$, 2) ELSE EXIT DO
LOOP
IF z$ = "" OR z$ = "0" THEN z$ = "0" ELSE z$ = LEFT$(sign$, 1) + z$
runningtotal$ = z$
sign$ = "": sign_a$ = "": sign_b$ = "": i&& = 0: j&& = 0: decimal% = 0: c = 0
END SUB
FUNCTION sm_validate (validate$)
sm_validate = 0: vsn_negcnt& = 0: vsn_poscnt& = 0: vsn_depresent& = 0: decimalcnt& = 0: vsn_numberpresent& = 0: vsn_zerospresent& = 0
IF LEFT$(validate$, 1) = "-" THEN validate$ = MID$(validate$, 2): sm_sign$ = "-" ELSE sm_sign$ = ""
WHILE -1 ' Falx loop.
IF LEFT$(validate$, 1) = "+" THEN IF sm_sign$ <> "-" THEN validate$ = MID$(validate$, 2) ELSE validate$ = "invalid number": EXIT WHILE
IF INSTR(UCASE$(validate$), "D") OR INSTR(UCASE$(validate$), "E") THEN ' Evaluate for Scientific Notation.
FOR sm_i& = 1 TO LEN(validate$)
validatenum$ = MID$(UCASE$(validate$), sm_i&, 1)
SELECT CASE validatenum$
CASE "+"
IF vsn_depresent& THEN vsn_poscnt& = vsn_poscnt& + 1 ELSE validate$ = "invalid number": EXIT WHILE
CASE "-"
IF vsn_depresent& THEN vsn_negcnt& = vsn_negcnt& + 1 ELSE validate$ = "invalid number": EXIT WHILE
CASE "0" TO "9"
vsn_numberpresent& = -1
CASE "D", "E"
vsn_depresent& = vsn_depresent& + 1
IF decimalcnt& = 0 AND sm_i& <> 2 OR vsn_depresent& > 1 OR vsn_numberpresent& = 0 OR vsn_negcnt& > 1 OR vsn_poscnt& > 1 OR vsn_negcnt& = 1 AND vsn_poscnt& >= 1 THEN vsn_numberpresent& = 0: EXIT FOR
vsn_numberpresent& = 0
MID$(validate$, sm_i&, 1) = "e" ' Standardize
CASE "."
decimalcnt& = decimalcnt& + 1
IF sm_i& <> 2 THEN vsn_numberpresent& = 0: EXIT FOR
CASE ELSE
vsn_numberpresent& = 0: EXIT FOR
END SELECT
NEXT
IF decimalcnt& = 0 THEN validate$ = MID$(validate$, 1, 1) + "." + MID$(validate$, 2) ' Standardize "."
IF vsn_numberpresent& = 0 OR vsn_negcnt& = 1 AND vsn_poscnt& = 1 OR decimalcnt& > 1 OR INSTR(validate$, ".") <> 2 THEN validate$ = "invalid number": EXIT WHILE
vsn_depresent& = INSTR(validate$, "e")
sm_x$ = MID$(validate$, vsn_depresent& + 1, 1) ' Standardize exponent "+" these two lines.
IF sm_x$ <> "+" AND sm_x$ <> "-" THEN validate$ = MID$(validate$, 1, vsn_depresent&) + "+" + MID$(validate$, vsn_depresent& + 1)
IF MID$(validate$, vsn_depresent& + 2, 1) = "0" THEN
IF MID$(validate$, vsn_depresent& + 3, 1) <> "" THEN validate$ = "invalid number": EXIT WHILE ' No leading zeros allowed in exponent notation.
END IF
jjed& = INSTR(validate$, "e") ' Get position of notation.
valexpside$ = MID$(validate$, jjed&) ' These two lines break up into number and notation
validate$ = MID$(validate$, 1, jjed& - 1) ' validate$ is +- single digit whole number, decimal point and decimal number. valexpside$ is notation, sign and exponent.
DO UNTIL RIGHT$(validate$, 1) <> "0" ' Remove any trailing zeros for number. Example 1.0d3 or 1.0000d3, etc.
validate$ = MID$(validate$, 1, LEN(validate$) - 1)
LOOP
IF VAL(MID$(validate$, 1, INSTR(validate$, ".") - 1)) = 0 THEN
IF RIGHT$(validate$, 1) = "." THEN
validate$ = "0.e+0" ' Handles all types of zero entries.
ELSE
validate$ = "invalid number": EXIT WHILE
END IF
EXIT WHILE
END IF
validate$ = sm_sign$ + validate$ + valexpside$
EXIT WHILE
ELSE
FOR sm_i& = 1 TO LEN(validate$)
validatenum$ = MID$(validate$, sm_i&, 1)
SELECT CASE validatenum$
CASE "."
decimalcnt& = decimalcnt& + 1
CASE "0"
vsn_zerospresent& = -1
CASE "1" TO "9"
vsn_numberpresent& = -1
CASE "$"
CASE ELSE
validate$ = "invalid number": EXIT WHILE
END SELECT
NEXT
IF decimalcnt& > 1 OR vsn_negcnt& > 1 OR vsn_poscnt& > 1 OR vsn_negcnt& >= 1 AND vsn_poscnt& >= 1 THEN
validate$ = "invalid number": EXIT WHILE
END IF
REM IF INSTR(validate$, "$") THEN GOSUB currency_validate
IF INSTR(validate$, ",") THEN
REM GOSUB comma_validation
IF validate$ = "invalid number" THEN EXIT WHILE
REM GOSUB comma_removal
END IF
IF RIGHT$(validate$, 1) = "." THEN validate$ = MID$(validate$, 1, LEN(validate$) - 1)
DO UNTIL LEFT$(validate$, 1) <> "0" ' Strip off any leading zeros.
validate$ = MID$(validate$, 2)
LOOP
validate$ = sm_sign$ + validate$
IF INSTR(validate$, ".") THEN
DO UNTIL RIGHT$(validate$, 1) <> "0" ' Strip off any trailing zeros in a decimal.
validate$ = MID$(validate$, 1, LEN(validate$) - 1)
LOOP
END IF
IF RIGHT$(validate$, 1) = "." THEN validate$ = MID$(validate$, 1, LEN(validate$) - 1)
IF vsn_numberpresent& = 0 THEN
IF vsn_zerospresent& THEN
validate$ = "0"
ELSE
validate$ = "invalid number"
END IF
END IF
END IF
EXIT WHILE
WEND
IF validate$ = "invalid number" THEN sm_validate = 1 ELSE sm_validate = 0
END FUNCTION
FUNCTION sm_add$ (stringmatha$, stringmathb$)
operator$ = "+"
sm_add_subtract_router stringmatha$, operator$, stringmathb$, runningtotal$
sm_add$ = runningtotal$
END FUNCTION
FUNCTION sm_sub$ (stringmatha$, stringmathb$)
operator$ = "-"
sm_add_subtract_router stringmatha$, operator$, stringmathb$, runningtotal$
sm_sub$ = runningtotal$
END FUNCTION
FUNCTION sm_mult$ (stringmatha$, stringmathb$)
DIM AS _INTEGER64 a, c, aa, cc, s, ss
z$ = "": sign$ = "": mult&& = 0: h&& = 0: i&& = 0: j&& = 0: c = 0: decimal% = 0
zz$ = "": ii&& = 0: jj&& = 0
s = 8: ss = 18
a$ = stringmatha$: b$ = stringmathb$
IF INSTR(a$, "-") <> 0 OR INSTR(b$, "-") <> 0 THEN
IF INSTR(a$, "-") <> 0 AND INSTR(b$, "-") <> 0 THEN
a$ = MID$(a$, 2): b$ = MID$(b$, 2)
ELSE
IF INSTR(a$, "-") <> 0 THEN a$ = MID$(a$, 2) ELSE b$ = MID$(b$, 2)
sign$ = "-"
END IF
END IF
IF INSTR(a$, ".") <> 0 OR INSTR(b$, ".") <> 0 THEN
decimal% = -1
IF INSTR(a$, ".") <> 0 THEN
dec_a&& = LEN(MID$(a$, INSTR(a$, ".") + 1))
a$ = MID$(a$, 1, INSTR(a$, ".") - 1) + MID$(a$, INSTR(a$, ".") + 1)
END IF
IF INSTR(b$, ".") <> 0 THEN
dec_b&& = LEN(MID$(b$, INSTR(b$, ".") + 1))
b$ = MID$(b$, 1, INSTR(b$, ".") - 1) + MID$(b$, INSTR(b$, ".") + 1)
END IF
END IF
IF LEN(a$) < LEN(b$) THEN SWAP a$, b$ ' Needed so x1$ is always the largest for leading zero replacements.
' Multiplication of digits.
DO
h&& = h&& + s: i&& = 0
x2$ = MID$(b$, LEN(b$) - h&& + 1, s)
DO
i&& = i&& + s
x1$ = MID$(a$, LEN(a$) - i&& + 1, s)
a = VAL(x1$) * VAL(x2$) + c
c = 0
tmp$ = LTRIM$(STR$(a))
IF LEN(tmp$) > s THEN c = VAL(MID$(tmp$, 1, LEN(tmp$) - s)): tmp$ = MID$(tmp$, LEN(tmp$) - s + 1)
z$ = STRING$(LEN(x1$) - LEN(tmp$), "0") + tmp$ + z$
LOOP UNTIL i&& >= LEN(a$) AND c = 0
jj&& = jj&& + 1
IF jj&& > 1 THEN
ii&& = 0: cc = 0
aa$ = holdaa$
bb$ = z$ + STRING$((jj&& - 1) * s, "0")
' Addition only of digits.
DO
ii&& = ii&& + ss
xx1$ = MID$(aa$, LEN(aa$) - ii&& + 1, ss)
xx2$ = MID$(bb$, LEN(bb$) - ii&& + 1, ss)
IF LEN(xx1$) < LEN(xx2$) THEN SWAP xx1$, xx2$
aa = VAL(xx1$) + VAL(xx2$) + cc
IF xx1$ + xx2$ = "" AND cc = 0 THEN EXIT DO ' Prevents leading zeros.
cc = 0
IF aa > VAL(STRING$(ss, "9")) THEN aa = aa - 10 ^ ss: cc = 1
tmp$ = LTRIM$(STR$(aa))
zz$ = STRING$(LEN(xx1$) - LEN(tmp$), "0") + tmp$ + zz$
LOOP
DO WHILE LEFT$(zz$, 1) = "0"
IF LEFT$(zz$, 1) = "0" THEN zz$ = MID$(zz$, 2)
LOOP
IF zz$ = "" THEN zz$ = "0"
holdaa$ = zz$
ELSE
holdaa$ = z$ + STRING$(jj&& - 1, "0")
END IF
z$ = "": zz$ = ""
LOOP UNTIL h&& >= LEN(b$)
z$ = holdaa$
IF decimal% THEN
DO UNTIL LEN(z$) >= dec_a&& + dec_b&&
z$ = "0" + z$
LOOP
z$ = MID$(z$, 0, LEN(z$) - (dec_a&& + dec_b&& - 1)) + "." + MID$(z$, LEN(z$) - (dec_a&& + dec_b&&) + 1)
DO UNTIL RIGHT$(z$, 1) <> "0" AND RIGHT$(z$, 1) <> "."
z$ = MID$(z$, 1, LEN(z$) - 1)
LOOP
END IF
IF STRING$(LEN(z$), "0") = z$ OR z$ = "" OR z$ = "0" THEN z$ = "0" ELSE z$ = sign$ + z$
decimal% = 0: sign$ = ""
runningtotal$ = z$
sm_mult$ = z$
END FUNCTION
FUNCTION sm_div$ (stringmatha$, stringmathb$)
hold_stringmatha$ = stringmatha$: hold_stringmathb$ = stringmathb$
q$ = "": divisor$ = stringmathb$: dividend$ = stringmatha$
DO ' Falx loop.
'Strip off neg(s) and determine quotent sign.
IF LEFT$(divisor$, 1) = "-" THEN divisor$ = MID$(divisor$, 2): q$ = "-"
IF LEFT$(dividend$, 1) = "-" THEN dividend$ = MID$(dividend$, 2): IF q$ = "-" THEN q$ = "" ELSE q$ = "-"
' Quick results for divisor 1 or 0.
IF dividend$ = "0" THEN q$ = "0": EXIT DO
IF divisor$ = "1" THEN q$ = dividend$: EXIT DO
IF divisor$ = "0" THEN q$ = "Division by zero not possible.": EXIT DO
' Determine decimal direction. -1 to left, +1 to right.
gl% = 0: sm_greater_lesser divisor$, dividend$, gl%
IF betatest% AND gl% = 1 THEN PRINT divisor$; " > "; dividend$; " Move decimal to the left"
IF betatest% AND gl% = 0 THEN PRINT divisor$; " = "; dividend$
IF betatest% AND gl% = -1 THEN PRINT divisor$; " < "; dividend$; " Move deciml to the right."
IF gl% = 1 THEN ' Divisor is larger than dividend so decimal moves to the left.
div_decimal% = -1 ' Move decimal point to the left.
ELSEIF gl% = -1 THEN
div_decimal% = 1 ' Move decimal point to the right.
ELSE
' Divisor and dividend are the same number.
q$ = q$ + "1": EXIT DO
END IF
divisor_ratio_dividend% = gl%
' Strip off decimal point(s) and determine places in these next 2 routines.
dp&& = 0: dp2&& = 0: j2&& = 0
temp&& = INSTR(divisor$, ".")
IF temp&& THEN
divisor$ = MID$(divisor$, 1, temp&& - 1) + MID$(divisor$, temp&& + 1)
IF temp&& = 1 THEN
DO UNTIL LEFT$(divisor$, 1) <> "0" ' Strip off any leading zeros on divisor only.
divisor$ = MID$(divisor$, 2)
dp&& = dp&& + 1
LOOP
dp&& = dp&& + 1
ELSE
dp&& = -(temp&& - 2)
END IF
ELSE
dp&& = -(LEN(divisor$) - 1)
END IF
temp&& = INSTR(dividend$, ".")
IF temp&& THEN
dividend$ = MID$(dividend$, 1, temp&& - 1) + MID$(dividend$, temp&& + 1)
IF temp&& = 1 THEN
DO UNTIL LEFT$(dividend$, 1) <> "0" ' Strip off any leading zeros on divisor only.
dividend$ = MID$(dividend$, 2)
dp2&& = dp2&& + 1
LOOP
dp2&& = dp2&& + 1
ELSE
dp2&& = -(temp&& - 2)
END IF
ELSE
dp2&& = -(LEN(dividend$) - 1)
END IF
IF betatest% THEN COLOR 11: PRINT "Divisor decimal moves "; LTRIM$(STR$(dp&&)); ". Dividend decimal moves"; LTRIM$(STR$(dp2&&)); ". Quotent decimal ABS("; LTRIM$(STR$(dp&&)); " - "; LTRIM$(STR$(dp2&&)); ") =";: COLOR 14: PRINT ABS(dp&& - dp2&&);: COLOR 11: PRINT "+ any adjustment.": COLOR 7
dp&& = ABS(dp&& - dp2&&)
IF betatest% THEN PRINT "Divisor 1st# = "; MID$(divisor$, 1, 1); " Remainder 1st# = "; MID$(dividend$, 1, 1)
' Adjust decimal place for instances when divisor is larger than remainder the length of the divisor.
j% = 0
IF MID$(divisor$, 1, 1) > MID$(dividend$, 1, 1) THEN
j% = 1
IF betatest% THEN PRINT "Larger divisor, so move quotent decimal one place back to: ";: COLOR 14: PRINT LTRIM$(STR$(dp&&)): COLOR 7
ELSEIF MID$(divisor$, 1, 1) = MID$(dividend$, 1, 1) THEN
IF LEN(divisor$) = LEN(dividend$) THEN
IF divisor$ > dividend$ THEN j% = 1
ELSE
IF LEN(divisor$) > LEN(dividend$) THEN
temp$ = dividend$ + STRING$(LEN(divisor$) - LEN(dividend$), "0")
ELSE
temp$ = MID$(dividend$, 1, LEN(divisor$))
END IF
IF divisor$ > temp$ THEN j% = 1
END IF
IF j% THEN
dp&& = dp&& - div_decimal%
IF betatest% THEN PRINT "Larger divisor than dividend at LEN(divisor$), so move quotent decimal one place back to: ";: COLOR 14: PRINT LTRIM$(STR$(dp&&)): COLOR 7
ELSE
IF betatest% THEN PRINT "Smaller divisor than dividend at LEN(divisor$), so no quotent decimal place adjustment needed. Quotent decimal place = ";: COLOR 14: PRINT LTRIM$(STR$(dp&&)): COLOR 7
END IF
ELSE
j% = 0
IF betatest% THEN PRINT "Smaller divisor, so no quotent decimal place adjustment needed. Quotent decimal place = ";: COLOR 14: PRINT LTRIM$(STR$(dp&&)): COLOR 7
END IF
IF j% THEN dp&& = dp&& - div_decimal%
origdividend$ = dividend$
' Determine length of divisor and dividend to begin initial long divison step.
gl% = 2: sm_greater_lesser divisor$, MID$(dividend$, 1, LEN(divisor$)) + STRING$(LEN(divisor$) - LEN(dividend$), "0"), gl%
divisor_ratio_dividend% = gl%
IF gl% = 1 AND MID$(dividend$, 1, 1) <> "0" THEN
dividend$ = MID$(dividend$, 1, LEN(divisor$) + 1) + STRING$(LEN(divisor$) + 1 - LEN(dividend$), "0")
ELSE
dividend$ = MID$(dividend$, 1, LEN(divisor$)) + STRING$(LEN(divisor$) - LEN(dividend$), "0")
END IF
' Long divison loop. Mult and subtraction of dividend and remainder.
k&& = 0
IF betatest% THEN PRINT "Begin long divison loop..."
DO
SELECT CASE MID$(divisor$, 1, 1)
CASE IS < MID$(dividend$, 1, 1)
adj_rem_len% = 0
CASE IS = MID$(dividend$, 1, 1)
gl% = 2: sm_greater_lesser divisor$, MID$(dividend$, 1, LEN(divisor$)), gl%
IF gl% = 1 THEN adj_rem_len% = 1 ELSE adj_rem_len% = 0
CASE IS > MID$(dividend$, 1, 1)
adj_rem_len% = 1
END SELECT
IF j2&& = 0 THEN j2&& = LEN(divisor$) + adj_rem_len%
DO
IF LEN(divisor$) > LEN(dividend$) THEN
w3&& = 0: runningtotal$ = dividend$: stringmathb$ = "0"
IF betatest% THEN PRINT: COLOR 3: PRINT "Divisor is larger so "; dividend$; " \ "; divisor$; " =";: COLOR 5: PRINT w3&&: COLOR 7
EXIT DO
END IF
IF LEN(divisor$) = LEN(dividend$) THEN
gl% = 2: sm_greater_lesser divisor$, dividend$, gl%
IF gl% = 1 THEN
w3&& = 0: runningtotal$ = dividend$: stringmathb$ = "0"
IF betatest% THEN COLOR 9: PRINT "Length of divisor is the same as remainder but remainder is smaller so w3&& = ";: COLOR 5: PRINT "0": COLOR 7
EXIT DO
END IF
END IF
SELECT CASE LEN(dividend$)
CASE IS > 2
w3&& = VAL(MID$(dividend$, 1, 2 + adj_rem_len%)) \ VAL(MID$(divisor$, 1, 2))
IF betatest% THEN PRINT MID$(dividend$, 1, 2 + adj_rem_len%); " \ "; MID$(divisor$, 1, 2); " =";
CASE ELSE
w3&& = VAL(MID$(dividend$, 1, 1 + adj_rem_len%)) \ VAL(MID$(divisor$, 1, 1))
IF betatest% THEN PRINT MID$(dividend$, 1, 1 + adj_rem_len%); " \ "; MID$(divisor$, 1, 1); " =";
END SELECT
IF betatest% THEN COLOR 5: PRINT " " + LTRIM$(STR$(w3&&));: COLOR 7: PRINT ". Begin mult est. at or one above this number."
IF w3&& < 9 THEN w3&& = w3&& + 1 ELSE IF w3&& = 10 THEN w3&& = 9
DO
stringmatha$ = divisor$: stringmathb$ = LTRIM$(STR$(w3&&))
runningtotal$ = sm_mult$(divisor$, LTRIM$(STR$(w3&&)))
gl% = 2: sm_greater_lesser runningtotal$, dividend$, gl%
IF gl% <= 0 OR w3&& = 0 THEN EXIT DO
IF betatest% THEN COLOR 8: PRINT "Mult loop:"; w3&&; "* "; divisor$; " = "; runningtotal$: COLOR 7
w3&& = w3&& - 1
LOOP
stringmatha$ = dividend$: stringmathb$ = runningtotal$
sm_add_subtract_router dividend$, "-", stringmathb$, runningtotal$
EXIT DO
LOOP
IF betatest% THEN PRINT LTRIM$(STR$(w3&&)); " * "; divisor$; " = "; stringmathb$; " | "; stringmatha$; " - "; stringmathb$; " = "; runningtotal$; " Remainder and drop-down = ";
j2&& = j2&& + 1
drop$ = "0": MID$(drop$, 1, 1) = MID$(origdividend$, j2&&, 1)
IF runningtotal$ <> "0" THEN remainder$ = runningtotal$ ELSE remainder$ = ""
dividend$ = remainder$ + drop$
w3$ = LTRIM$(STR$(w3&&))
temp$ = ""
IF div_decimal% = -1 THEN
IF dp&& AND k&& = 0 THEN
q$ = q$ + "." + STRING$(dp&& - 1, "0")
IF w3&& = 0 THEN w3$ = ""
END IF
END IF
IF div_decimal% >= 0 THEN
IF dp&& = k&& THEN
temp$ = "."
END IF
END IF
q$ = q$ + w3$ + temp$
IF betatest% AND remainder$ = "" THEN betatemp$ = CHR$(34) + CHR$(34) ELSE IF betatest% THEN betatemp$ = remainder$
IF betatest% AND MID$(origdividend$, j2&&, 1) = "" THEN betatemp2$ = CHR$(34) + CHR$(34) ELSE IF betatest% THEN betatemp2$ = MID$(origdividend$, j2&&, 1)
IF betatest% THEN PRINT dividend$; " ("; betatemp$; " + "; drop$; ") at:"; j2&&; "of "; origdividend$; " Loop"; k&& + 1; "Quotent = ";: COLOR 14, 4: PRINT q$;: COLOR 7, 0: PRINT: SLEEP
' Check to terminate
IF div_decimal% = -1 THEN
' Decimal to left.
IF remainder$ = "" AND MID$(origdividend$, j2&&, 1) = "" OR LEN(q$) >= limit&& THEN EXIT DO
ELSE
' Decimal to right.
IF remainder$ = "" AND MID$(origdividend$, j2&&, 1) = "" AND k&& >= dp&& OR LEN(q$) >= limit&& THEN EXIT DO
END IF
IF INKEY$ = " " THEN EXIT DO
k&& = k&& + 1
LOOP
EXIT DO
LOOP
IF RIGHT$(q$, 1) = "." AND divisor$ <> "0" THEN runningtotal$ = MID$(q$, 1, LEN(q$) - 1) ELSE runningtotal$ = q$
sm_div$ = runningtotal$
stringmatha$ = hold_stringmatha$: stringmathb$ = hold_stringmathb$
END FUNCTION
FUNCTION sm_sqrt$ (sm_var$)
oldy$ = "": sqrt$ = "": IF limit&& < 150 THEN custom_limit&& = 150 ELSE custom_limit&& = limit&&
sqrt_a$ = sm_var$
IF INSTR(sqrt_a$, ".") THEN
decx$ = MID$(sqrt_a$, 1, INSTR(sqrt_a$, ".") - 1)
sqrt_a$ = MID$(sqrt_a$, 1, INSTR(sqrt_a$, ".") - 1) + MID$(sqrt_a$, INSTR(sqrt_a$, ".") + 1)
IF LEN(sqrt_a$) = 1 THEN sqrt_a$ = sqrt_a$ + "0"
ELSE
decx$ = sqrt_a$
END IF
j&& = LEN(decx$)
' VAL() okay, one character eval.
IF VAL(RIGHT$(LTRIM$(STR$(j&&)), 1)) / 2 = VAL(RIGHT$(LTRIM$(STR$(j&&)), 1)) \ 2 THEN
i&& = 1 ' Even number length.
ELSE
i&& = 0 ' Odd number length.
END IF
DO
runningtotal$ = sm_sub$(z$, k$) ''''' sm z$, "-", k$, runningtotal$
z$ = runningtotal$ + (MID$(sqrt_a$, i&&, 2))
IF LEFT$(z$, 1) = "0" THEN z$ = MID$(z$, 2) ' Remove leading zeros
oldy$ = ""
FOR j&& = 1 TO 10
IF i&& > 1 THEN
y$ = sm_mult$(sqrt$, "2") '''' sm sqrt$, "*", "2", y$
y$ = y$ + LTRIM$(STR$(j&&))
ELSE
y$ = LTRIM$(STR$(j&&))
END IF
runningtotal$ = sm_mult$(y$, LTRIM$(STR$(j&&))) '''''sm y$, "*", LTRIM$(STR$(j&&)), runningtotal$
sm_greater_lesser runningtotal$, z$, gl%
IF gl% > -1 THEN
IF gl% = 0 THEN
h% = 0: oldy$ = y$ ' Perfect square division.
ELSE
h% = 1
END IF
runningtotal$ = sm_mult$(oldy$, LTRIM$(STR$(j&& - h%))) '''', runningtotal$
IF STRING$(LEN(z$), "0") = z$ AND runningtotal$ = "0" AND i&& >= LEN(decx$) THEN EXIT DO
IF dpx&& = 0 THEN ' Limited to && size unless converted to string.
IF i&& >= LEN(decx$) THEN
dpx&& = INT(LEN(decx$) / 2 + .5)
IF dpx&& = 0 THEN dpx&& = -1
END IF
END IF
IF betatest% < -1 THEN PRINT "Sqrt "; sqrt$; " * 2 = ";: COLOR 2, 0: PRINT LTRIM$(STR$(VAL(sqrt$) * 2));: COLOR 7, 0: PRINT LTRIM$(STR$(j&& - h%)); " * "; LTRIM$(STR$(j&& - h%)); " ="; VAL(oldy$) * (j&& - h%)
sqrt$ = sqrt$ + LTRIM$(STR$(j&& - h%))
runningtotal$ = sm_mult$(oldy$, LTRIM$(STR$(j&& - h%))) '''', runningtotal$
k$ = runningtotal$
IF betatest% < -1 THEN PRINT "Remainder "; z$; " minus "; k$; " = ";
EXIT FOR
END IF
oldy$ = y$
NEXT
i&& = i&& + 2
IF LEN(z$) >= custom_limit&& THEN EXIT DO
sqrt_a$ = sqrt_a$ + "00"
LOOP
IF dpx&& THEN sqrt$ = MID$(sqrt$, 0, dpx&& + 1) + "." + MID$(sqrt$, dpx&& + 1)
sm_sqrt$ = sqrt$
END FUNCTION
FUNCTION sm_sqr$ (sm_var$)
runningtotal$ = sm_mult$(sm_var$, sm_var$)
sm_sqr$ = runningtotal$
END FUNCTION
FUNCTION sm_div_old$ (stringmatha$, stringmathb$)
terminating_decimal% = 0: divsign% = 0: divremainder& = 0: divremainder$ = "": divplace& = 0: divplace2& = 0: quotient$ = "": divcarry& = 0
divbuffer& = LEN(stringmathb$) - LEN(stringmatha$)
IF divbuffer& < 0 THEN divbuffer& = 0
d2dividend$ = stringmatha$
d1divisor$ = stringmathb$
IF LEFT$(d1divisor$, 1) = "0" AND LEN(d1divisor$) = 1 THEN PRINT "Division by zero not allowed.": divsign% = 0: EXIT FUNCTION
IF LEFT$(d1divisor$, 1) = "-" THEN divsign% = -1: d1divisor$ = MID$(d1divisor$, 2)
IF LEFT$(d2dividend$, 1) = "-" THEN
IF divsign% THEN
divsign% = 0
ELSE
divsign% = -1
END IF
d2dividend$ = MID$(d2dividend$, 2)
END IF
IF INSTR(d1divisor$, ".") <> 0 THEN
DO UNTIL RIGHT$(d1divisor$, 1) <> "0"
d1divisor$ = MID$(d1divisor$, 1, LEN(d1divisor$) - 1) ' Strip off trailing zeros
LOOP
divplace& = LEN(d1divisor$) - INSTR(d1divisor$, ".")
d1divisor$ = MID$(d1divisor$, 1, INSTR(d1divisor$, ".") - 1) + MID$(d1divisor$, INSTR(d1divisor$, ".") + 1) ' Strip off decimal point.
DO UNTIL LEFT$(d1divisor$, 1) <> "0"
d1divisor$ = MID$(d1divisor$, 2) ' Strip off leading zeros for divisors smaller than .1
LOOP
END IF
IF INSTR(d2dividend$, ".") <> 0 THEN
d2dividend$ = d2dividend$ + STRING$(divplace& - LEN(d2dividend$) - INSTR(d2dividend$, "."), "0") ' Add any zeros based on the length of dividend at decimal - length of divisor at decimal. If less than zero, nothing added.
divplace2& = INSTR(d2dividend$, ".")
DO UNTIL RIGHT$(d2dividend$, 1) <> "0"
d2dividend$ = MID$(d2dividend$, 1, LEN(d2dividend$) - 1) ' Strip off trailing zeros
LOOP
d2dividend$ = MID$(d2dividend$, 1, INSTR(d2dividend$, ".") - 1) + MID$(d2dividend$, INSTR(d2dividend$, ".") + 1) ' Strip off decimal point.
ELSE
d2dividend$ = d2dividend$ + STRING$(divplace&, "0") ' Add any zeros based on the length of dividend at decimal - length of divisor at decimal. If less than zero, nothing added.
divplace& = 0
END IF
DO
DO
divremainder& = divremainder& + 1: divremainder$ = divremainder$ + MID$(d2dividend$, divremainder&, 1)
IF MID$(d2dividend$, divremainder&, 1) = "" THEN
IF divremainder$ = STRING$(LEN(divremainder$), "0") AND LEN(quotient$) > LEN(d2dividend$) THEN
divflag% = -1
terminating_decimal% = -1
EXIT DO
END IF
divcarry& = divcarry& + 1
IF divcarry& = 1 THEN divplace3& = divremainder& - 1
IF divcarry& > limit&& + 1 + divbuffer& THEN
divflag% = -2: EXIT DO
END IF
divremainder$ = divremainder$ + "0" ' No more digits to bring down.
END IF
IF LEN(divremainder$) > LEN(d1divisor$) OR LEN(divremainder$) = LEN(d1divisor$) AND divremainder$ >= d1divisor$ THEN EXIT DO
quotient$ = quotient$ + "0"
LOOP
IF divflag% THEN divflag% = 0: EXIT DO
w1% = VAL(MID$(d1divisor$, 1, 1))
w2% = VAL(MID$(divremainder$, 1, 1))
SELECT CASE w1%
CASE IS > w2%
w3% = (w2% * 10 + VAL(MID$(divremainder$, 2, 1))) \ w1% + 1
IF w3% > 9 THEN w3% = 9
CASE IS = w2%
IF LEN(divremainder$) > LEN(d1divisor$) THEN w3% = (w2% * 10) \ w1% + 1 ELSE w3% = 2
CASE IS < w2%
IF LEN(divremainder$) < LEN(d1divisor$) THEN w3% = (w2% * 10) \ w1% + 1 ELSE w3% = w2% \ w1%
END SELECT
FOR div_i% = w3% TO 1 STEP -1
stringmatha$ = LTRIM$(STR$(div_i%)): stringmathb$ = d1divisor$
runningtotal$ = sm_mult$(stringmatha$, stringmathb$) ''''GOSUB string_multiply_new ' Gets runningtotal$
tempcutd$ = divremainder$ ' divremainder$ can be 00 or other leading zero values.
DO
IF LEN(tempcutd$) = 1 THEN EXIT DO
IF LEFT$(tempcutd$, 1) = "0" THEN
tempcutd$ = MID$(tempcutd$, 2)
ELSE
EXIT DO
END IF
LOOP
IF LEN(tempcutd$) > LEN(runningtotal$) OR LEN(tempcutd$) = LEN(runningtotal$) AND runningtotal$ <= tempcutd$ THEN EXIT FOR
NEXT
quotient$ = quotient$ + LTRIM$(STR$(div_i%))
stringmatha$ = LTRIM$(STR$(div_i%)): stringmathb$ = d1divisor$
runningtotal$ = sm_mult$(stringmatha$, stringmathb$) ''''GOSUB string_multiply_new ' Gets runningtotal$
stringmatha$ = divremainder$: stringmathb$ = runningtotal$
runningtotal$ = sm_sub$(stringmatha$, stringmathb$) '''''operator$ = "-": GOSUB string_add_subtract_new
divremainder$ = runningtotal$
LOOP
IF divplace& = 0 AND divplace2& = 0 THEN divplace& = divplace3&
IF divplace2& THEN divplace& = divplace& + divplace2& - 1
IF quotient$ = "" THEN divplace& = 0 ' dividend is zero.
IF divplace& OR divplace2& THEN
quotient$ = MID$(quotient$, 1, divplace&) + "." + MID$(quotient$, divplace& + 1)
DO UNTIL RIGHT$(quotient$, 1) <> "0"
quotient$ = MID$(quotient$, 1, LEN(quotient$) - 1) ' Strip off trailing zeros
LOOP
IF RIGHT$(quotient$, 1) = "." THEN quotient$ = MID$(quotient$, 1, LEN(quotient$) - 1) ' Strip off abandoned decimal.
END IF
DO UNTIL LEFT$(quotient$, 1) <> "0"
quotient$ = MID$(quotient$, 2) ' Strip off leading zeros
LOOP
IF quotient$ = "" THEN quotient$ = "0": divsign% = 0
stringmathb$ = quotient$: quotient$ = ""
IF stringmathb$ = "overflow" THEN divsign% = 0: EXIT FUNCTION
runningtotal$ = stringmathb$: stringmathb$ = ""
IF divsign% THEN runningtotal$ = "-" + runningtotal$
IF stringmathround$ <> "" THEN runningtotal$ = runningtotal$ + stringmathround$
sm_div_old$ = runningtotal$
END FUNCTION
SUB bAdd (s1$, s2$, out$)
DIM last1%, dp1%, sign1%, last2%, dp2%, sign2%
DIM last%, d1%, d2%, dpt%, carry%
DIM i%, n%
'strip the numbers
bStripDp s1$, last1%, dp1%, sign1%
bStripDp s2$, last2%, dp2%, sign2%
'treat different signs as subtraction and exit
IF sign1% = negative AND sign2% = positive THEN
bSub s2$, s1$, out$
bNeg s1$
EXIT SUB
ELSEIF sign1% = positive AND sign2% = negative THEN
bSub s1$, s2$, out$
bNeg s2$
EXIT SUB
END IF
'align the decimal points and digit pointers
last% = bMaxInt%(last1% - dp1%, last2% - dp2%)
d1% = last% + dp1%
d2% = last% + dp2%
dpt% = bMaxInt%(dp1%, dp2%)
last% = dpt% + last%
out$ = SPACE$(last%)
carry% = 0
'do the addition right to left
FOR i% = last% TO 1 STEP -1
IF i% <> dpt% THEN
n% = carry%
IF d1% > 0 THEN n% = n% + VAL(MID$(s1$, d1%, 1))
IF d2% > 0 THEN n% = n% + VAL(MID$(s2$, d2%, 1))
carry% = n% \ 10
MID$(out$, i%, 1) = CHR$(asc0 + (n% MOD 10))
ELSE
MID$(out$, i%, 1) = dp_tree$
END IF
d1% = d1% - 1
d2% = d2% - 1
NEXT i%
IF carry% THEN out$ = one$ + out$
'clean up
IF sign1% = negative THEN s1$ = neg$ + s1$: s2$ = neg$ + s2$: out$ = neg$ + out$
bClean s1$
bClean s2$
bClean out$
END SUB
SUB bSub (s1$, s2$, out$)
DIM last1%, dp1%, sign1%
DIM last2%, dp2%, sign2%
DIM last%, d1%, d2%, dpt%, borrow%, swapflag%
DIM i%, n%
'strip the numbers
bStripDp s1$, last1%, dp1%, sign1%
bStripDp s2$, last2%, dp2%, sign2%
'treat different signs as addition
IF sign1% = negative AND sign2% = positive THEN
bNeg s1$
bNeg s2$
bAdd s1$, s2$, out$
bNeg s2$
EXIT SUB
ELSEIF sign1% = positive AND sign2% = negative THEN
bAdd s1$, s2$, out$
bNeg s2$
EXIT SUB
END IF
'align the decimal points and digit pointers
last% = bMaxInt%(last1% - dp1%, last2% - dp2%)
d1% = last% + dp1%
d2% = last% + dp2%
dpt% = bMaxInt%(dp1%, dp2%)
last% = dpt% + last%
out$ = SPACE$(last%)
borrow% = 0
'always subtract smaller from bigger to avoid complements
IF bIsMore%(s2$, s1$) THEN
bSwapString s1$, s2$
bSwapInt d2%, d1%
swapflag% = True
END IF
'do the subtraction right to left
FOR i% = last% TO 1 STEP -1
IF i% <> dpt% THEN
IF d1% > 0 THEN n% = VAL(MID$(s1$, d1%, 1)) ELSE n% = 0
IF d2% > 0 THEN n% = n% - VAL(MID$(s2$, d2%, 1))
n% = n% - borrow%
IF n% >= 0 THEN borrow% = 0 ELSE borrow% = 1: n% = n% + 10
MID$(out$, i%, 1) = CHR$(asc0 + n%)
ELSE
MID$(out$, i%, 1) = dp_tree$
END IF
d1% = d1% - 1
d2% = d2% - 1
NEXT i%
'clean up
IF sign1% = negative THEN s1$ = neg$ + s1$: s2$ = neg$ + s2$
IF swapflag% THEN
bSwapString s1$, s2$
sign1% = -sign1%
END IF
IF sign1% = negative THEN out$ = neg$ + out$
bClean s1$
bClean s2$
bClean out$
END SUB
SUB bSqr (s$, out$)
DIM dvd$, div$, dig$, newdiv$, t$, z$
DIM slog%, ssign%, slen%, spt%, olddigits%, n%, m%
IF bIsNeg%(s$) THEN out$ = errormsg$: EXIT SUB
'strip to whole number + group digits by 2 left or right of decimal
bLogGet s$, slog%, ssign%, True
slen% = LEN(s$)
IF slog% MOD 2 THEN spt% = 2 ELSE spt% = 1
'Force at least enough digits to show integer of root
olddigits% = digits%
n% = 1 + slog% \ 2
IF digits% < n% THEN digits% = n%
'figure first digit and setup loop
n% = VAL(LEFT$(s$ + "0", spt%))
m% = INT(SQR(n%))
out$ = LTRIM$(STR$(m%))
dvd$ = LTRIM$(STR$(n% - m% * m%))
spt% = spt% + 1
DO
'all done?
IF (spt% > slen% AND bIsZero%(dvd$)) OR LEN(out$) >= digits% THEN EXIT DO
'append next 2 digits (or 0s) to dividend
dvd$ = dvd$ + LEFT$(MID$(s$, spt%, 2) + "00", 2)
spt% = spt% + 2
'divisor=twice the root * 10
z$ = out$
bAdd out$, z$, div$
bShift div$, 1
'estimate divisor, and adjust if too big. Unit is next digit of root.
bDivInt dvd$, div$, dig$
DO
bAdd div$, dig$, newdiv$
bMul newdiv$, dig$, t$
IF NOT bIsMore%(t$, dvd$) THEN EXIT DO
bInc dig$, -1
LOOP
out$ = out$ + dig$
'form new divisor
z$ = dvd$
bSub z$, t$, dvd$
LOOP
'clean up
bLogPut s$, slog%, ssign%
IF slog% < 0 THEN slog% = slog% - 1
bLogPut out$, slog% \ 2, ssign%
digits% = olddigits%
END SUB
SUB bMul (s1$, s2$, out$)
DIM t$
DIM slog1%, sign1%, slog2%, sign2%, outdp%, outsign%, outlog%, swapflag%
'strip multiplier
t$ = s2$
bLogGet t$, slog2%, sign2%, True
'times 0
IF t$ = zero$ THEN
out$ = zero$
'do powers of 10 with shifts
ELSEIF t$ = one$ THEN
out$ = s1$
sign1% = bSign%(out$)
IF sign1% = negative THEN bAbs out$
bShift out$, slog2%
IF sign1% <> sign2% THEN bNeg out$
'the hard way
ELSE
'strip all
s2$ = t$: t$ = ""
bLogGet s1$, slog1%, sign1%, True
'figure decimal point and sign of answer
outdp% = bLogDp%(s1$, slog1%) + bLogDp%(s2$, slog2%)
IF sign1% <> sign2% THEN outsign% = negative ELSE outsign% = positive
'always multiply by the shorter number
IF LEN(s2$) > LEN(s1$) THEN bSwapString s1$, s2$: swapflag% = True
'do it
IF LEN(s2$) <= maxlongdig THEN bMulLong s1$, s2$, out$ ELSE bMulChar s1$, s2$, out$
'clean up
outlog% = bLogDp%(out$, outdp%)
bLogPut out$, outlog%, outsign%
IF swapflag% THEN bSwapString s1$, s2$
bLogPut s1$, slog1%, sign1%
bLogPut s2$, slog2%, sign2%
END IF
END SUB
SUB bMulChar (s1$, s2$, out$)
DIM last1%, last2%, last%
DIM i%, j%, k%, sj%, ej%
DIM product&
last1% = LEN(s1$)
last2% = LEN(s2$)
last% = last1% + last2%
out$ = SPACE$(last%)
product& = 0
FOR i% = 0 TO last% - 1
k% = last1% - i%
sj% = 1 - k%: IF sj% < 0 THEN sj% = 0
ej% = last1% - k%: IF ej% > last2% - 1 THEN ej% = last2% - 1
FOR j% = sj% TO ej%
product& = product& + VAL(MID$(s1$, k% + j%, 1)) * VAL(MID$(s2$, last2% - j%, 1))
NEXT j%
MID$(out$, last% - i%, 1) = CHR$(asc0 + CINT(product& MOD 10&))
product& = product& \ 10&
NEXT i%
IF product& THEN out$ = LTRIM$(STR$(product&)) + out$
END SUB
SUB bMulLong (s1$, s2$, out$)
DIM last1%, i%
DIM s2val&, product&
last1% = LEN(s1$)
s2val& = VAL(s2$)
out$ = SPACE$(last1%)
FOR i% = last1% TO 1 STEP -1
product& = product& + VAL(MID$(s1$, i%, 1)) * s2val&
MID$(out$, i%, 1) = CHR$(asc0 + CINT(product& MOD 10&))
product& = product& \ 10&
NEXT i%
IF product& THEN out$ = LTRIM$(STR$(product&)) + out$
END SUB
SUB bDivLong (s1$, s2$, quotient$, remainder$)
DIM rmdr&, dividend&, divisor&
DIM dig%, i%
quotient$ = ""
rmdr& = 0
divisor& = VAL(s2$)
FOR i% = 1 TO digits%
dividend& = rmdr& * 10& + VAL(MID$(s1$, i%, 1))
dig% = dividend& \ divisor&
quotient$ = quotient$ + CHR$(asc0 + dig%)
rmdr& = dividend& - dig% * divisor&
NEXT i%
IF LEN(quotient$) = 0 THEN quotient$ = zero$
remainder$ = LTRIM$(STR$(rmdr&))
END SUB
SUB bDiv (s1$, s2$, out$)
DIM t$
DIM slog1%, sign1%, slog2%, sign2%
DIM outlog%, outsign%, olddigits%
'strip divisor
t$ = s2$
bLogGet t$, slog2%, sign2%, True
'divide by zero?
IF t$ = zero$ THEN
out$ = Error$
'do powers of 10 with shifts
ELSEIF t$ = one$ THEN
out$ = s1$
sign1% = bSign%(out$)
IF sign1% = negative THEN bAbs out$
bShift out$, -slog2%
IF sign1% <> sign2% THEN bNeg out$
'the hard way
ELSE
'strip all
s2$ = t$: t$ = ""
bLogGet s1$, slog1%, sign1%, True
'figure decimal point and sign of answer
outlog% = slog1% + bLogDp%(s2$, slog2%)
IF sign1% <> sign2% THEN outsign% = negative ELSE outsign% = positive
'bump digits past leading zeros and always show whole quotient
olddigits% = digits%
digits% = digits% + LEN(s2$)
IF digits% < outlog% + 1 THEN digits% = outlog% + 1
'do it, ignore remainder
IF LEN(s2$) <= maxlongdig THEN bDivLong s1$, s2$, out$, t$ ELSE bDivChar s1$, s2$, out$, t$
'clean up
bLogPut out$, outlog%, outsign%
bLogPut s1$, slog1%, sign1%
bLogPut s2$, slog2%, sign2%
digits% = olddigits%
END IF
END SUB
SUB bDivChar (s1$, s2$, quotient$, remainder$)
DIM last1%, last2%, ldvd%, lrem%, dig%, borrow%
DIM i%, j%, n%
DIM dvd$
last1% = LEN(s1$) 'length of the dividend
last2% = LEN(s2$) 'length of the divisor
quotient$ = ""
remainder$ = ""
FOR i% = 1 TO digits%
'get next digit of dividend or zero$ if past end
IF i% <= last1% THEN
dvd$ = remainder$ + MID$(s1$, i%, 1)
ELSE
dvd$ = remainder$ + zero$
END IF
'if dividend < divisor then digit%=0 else have to calculate it.
'do fast compare using string operations. see bComp%()
bStripZero dvd$
ldvd% = LEN(dvd$)
IF (ldvd% < last2%) OR ((ldvd% = last2%) AND (dvd$ < s2$)) THEN
'divisor is bigger, so digit is 0, easy!
dig% = 0
remainder$ = dvd$
ELSE
'dividend is bigger, but no more than 9 times bigger.
'subtract divisor until we get remainder less than divisor.
'time hog, average is 5 tries through j% loop. There's a better way.
FOR dig% = 1 TO 9
remainder$ = ""
borrow% = 0
FOR j% = 0 TO ldvd% - 1
n% = last2% - j%
IF n% < 1 THEN n% = 0 ELSE n% = VAL(MID$(s2$, n%, 1))
n% = VAL(MID$(dvd$, ldvd% - j%, 1)) - n% - borrow%
IF n% >= 0 THEN borrow% = 0 ELSE borrow% = 1: n% = n% + 10
remainder$ = CHR$(asc0 + n%) + remainder$
NEXT j%
'if remainder < divisor then exit
bStripZero remainder$
lrem% = LEN(remainder$)
IF (lrem% < last2%) OR ((lrem% = last2%) AND (remainder$ < s2$)) THEN EXIT FOR
dvd$ = remainder$
ldvd% = LEN(dvd$)
NEXT dig%
END IF
quotient$ = quotient$ + CHR$(asc0 + dig%)
NEXT i%
END SUB
SUB bLogGet (s$, slog%, sign%, zeroflag%)
DIM dpt%, n%
IF LEFT$(s$, 1) = neg$ THEN s$ = MID$(s$, 2): sign% = negative ELSE sign% = positive
bStripZero s$
dpt% = INSTR(s$, dp_tree$)
SELECT CASE dpt%
CASE 0
slog% = LEN(s$) - 1
CASE 1
n% = dpt% + 1
DO WHILE MID$(s$, n%, 1) = zero$
n% = n% + 1
LOOP
s$ = MID$(s$, n%)
slog% = dpt% - n%
CASE ELSE
s$ = LEFT$(s$, dpt% - 1) + MID$(s$, dpt% + 1)
slog% = dpt% - 2
END SELECT
'remove trailing 0's if zeroflag%
IF zeroflag% THEN bStripTail s$
END SUB
SUB bLogPut (s$, slog%, sign%)
DIM last%
last% = LEN(s$)
IF LEN(s$) = 0 OR s$ = zero$ THEN
s$ = zero$
ELSEIF slog% < 0 THEN
s$ = dp_tree$ + STRING$(-slog% - 1, zero$) + s$
ELSEIF slog% > last% - 1 THEN
s$ = s$ + STRING$(slog% - last% + 1, zero$) + dp_tree$
ELSE
s$ = LEFT$(s$, slog% + 1) + dp_tree$ + MID$(s$, slog% + 2)
END IF
bClean s$
IF sign% = negative THEN s$ = neg$ + s$
END SUB
SUB bInt (s$)
DIM n%
n% = INSTR(s$, dp_tree$)
IF n% THEN
IF n% = 1 THEN s$ = zero$ ELSE s$ = LEFT$(s$, n% - 1)
IF s$ = neg$ OR LEFT$(s$, 2) = "-." THEN s$ = zero$
END IF
END SUB
SUB bStr (s$, out$)
DIM t$
DIM n%, i%
n% = INSTR(s$, ".")
IF n% THEN t$ = MID$(s$, n% + 1) ELSE t$ = RIGHT$(s$, 1)
out$ = ""
FOR i% = 1 TO VAL(s$)
out$ = t$ + out$
NEXT i%
IF LEN(out$) = 0 THEN out$ = zero$
END SUB
'Trim leading spaces, add decimal points, eliminate signs.
'Returns last%=length of string, dpt%=decimal place, sign%=-1 or 1.
'Called only by bAdd() and bSub() which needs a final decimal point.
'
SUB bStripDp (s$, last%, dpt%, sign%)
IF LEFT$(s$, 1) = neg$ THEN s$ = MID$(s$, 2): sign% = negative ELSE sign% = positive
bStripZero s$
IF INSTR(s$, dp_tree$) = 0 THEN s$ = s$ + dp_tree$
IF s$ = dp_tree$ THEN s$ = "0."
dpt% = INSTR(s$, dp_tree$)
last% = LEN(s$)
END SUB
'Strip trailing 0s to "." (but leave something)
'
SUB bStripTail (s$)
DIM n%
n% = LEN(s$)
DO WHILE MID$(s$, n%, 1) = zero$
n% = n% - 1
IF n% <= 1 THEN EXIT DO
LOOP
IF n% THEN IF MID$(s$, n%, 1) = dp_tree$ THEN n% = n% - 1
s$ = LEFT$(s$, n%)
IF LEN(s$) = 0 THEN s$ = zero$
END SUB
'Strip leading 0s and final "." (but leave something)
'
SUB bStripZero (s$)
DIM n%
n% = 1
DO WHILE MID$(s$, n%, 1) = zero$
n% = n% + 1
LOOP
IF n% > 1 THEN s$ = MID$(s$, n%)
IF RIGHT$(s$, 1) = dp_tree$ THEN s$ = LEFT$(s$, LEN(s$) - 1)
IF LEN(s$) = 0 THEN s$ = zero$
END SUB
SUB bNeg (s$)
IF LEFT$(s$, 1) = neg$ THEN s$ = MID$(s$, 2) ELSE s$ = neg$ + s$
END SUB
SUB bClean (s$)
DIM sign%
IF LEFT$(s$, 1) = neg$ THEN s$ = MID$(s$, 2): sign% = True
bStripZero s$
IF INSTR(s$, dp_tree$) THEN bStripTail s$
IF sign% AND s$ <> zero$ THEN s$ = neg$ + s$
END SUB
SUB bSwapInt (s1%, s2%)
DIM t%
t% = s1%
s1% = s2%
s2% = t%
END SUB
SUB bSwapString (s1$, s2$)
DIM t$
t$ = s1$
s1$ = s2$
s2$ = t$
END SUB
SUB bShift (s$, n%)
DIM slog%, sign%
bLogGet s$, slog%, sign%, False
bLogPut s$, slog% + n%, sign%
END SUB
SUB bDivInt (s1$, s2$, out$)
DIM t$
bDivIntMod s1$, s2$, out$, t$
END SUB
SUB bDivIntMod (s1$, s2$, quotient$, remainder$)
DIM slog1%, sign1%, slog2%, sign2%
DIM olddigits%, outlog%, outsign%
olddigits% = digits%
'strip the numbers, set flag false to NOT trim zeros, slower but needed
bLogGet s2$, slog2%, sign2%, False
IF s2$ = zero$ THEN quotient$ = Error$: remainder$ = Error$: EXIT SUB
bLogGet s1$, slog1%, sign1%, False
'figure decimal point and sign of answer
outlog% = slog1% + bLogDp%(s2$, slog2%)
IF sign1% <> sign2% THEN outsign% = negative ELSE outsign% = positive
'a trick: figure the decimal and only find that many digits
digits% = outlog% + 1
'send the work out
IF LEN(s2$) <= maxlongdig THEN bDivLong s1$, s2$, quotient$, remainder$ ELSE bDivChar s1$, s2$, quotient$, remainder$
'clean up
bLogPut s1$, slog1%, sign1%
bLogPut s2$, slog2%, sign2%
bClean quotient$
bClean remainder$
IF sign1% <> sign2% THEN bNeg quotient$
digits% = olddigits%
END SUB
SUB bInc (s$, num%)
DIM dig%, n%, borrow%
IF num% = 0 THEN EXIT SUB
dig% = INSTR(s$, dp_tree$)
IF dig% THEN dig% = dig% - 1 ELSE dig% = LEN(s$)
n% = num%
IF n% > 0 THEN 'increment (n>0)
DO WHILE n%
IF dig% < 1 THEN
s$ = LTRIM$(STR$(n%)) + s$
n% = 0
ELSE
n% = n% + VAL(MID$(s$, dig%, 1))
MID$(s$, dig%, 1) = CHR$(asc0 + (n% MOD 10))
n% = n% \ 10
dig% = dig% - 1
END IF
LOOP
ELSE 'decrement (n<0)
n% = -n%
DO WHILE n%
IF dig% < 1 THEN s$ = zero$: EXIT DO
borrow% = 0
n% = VAL(MID$(s$, dig%, 1)) - n%
DO WHILE n% < 0
n% = n% + 10: borrow% = borrow% + 1
LOOP
MID$(s$, dig%, 1) = CHR$(asc0 + n%)
n% = borrow%
dig% = dig% - 1
LOOP
END IF
bStripZero s$
END SUB
SUB bAbs (s$)
IF LEFT$(s$, 1) = neg$ THEN s$ = MID$(s$, 2)
END SUB
SUB bMod (s1$, s2$, out$)
DIM t$
bDivIntMod s1$, s2$, t$, out$
END SUB
SUB bModPower (s1$, s2$, s3$, out$)
'Use variation of "Russian Peasant Method" to figure m=(c^d) mod n.
'Byte, Jan 83, p.206.
'test value: (71611947 ^ 63196467) mod 94815109 = 776582
'm=1
'do
' if d is odd then m=(m*c) mod n
' c=(c*c) mod n
' d=int(d/2)
'loop while d>0
'm is the answer
DIM c$, d$, z$, w$
STATIC n$ 'remember modulus for next call
'positive numbers only, modulus must be >1! Find mod inverse if s2=-1.
out$ = errormsg$
IF LEN(s3$) THEN n$ = s3$
IF bIsNeg%(s1$) OR bIsNeg%(n$) THEN EXIT SUB
IF bIsNeg%(s2$) THEN
IF bIsEqual%(s2$, "-1") THEN bModInv s1$, n$, out$
EXIT SUB
END IF
c$ = s1$
d$ = s2$
out$ = one$
DO
IF bIsOdd%(d$) THEN
z$ = out$
bMul z$, c$, out$
z$ = out$
bMod z$, n$, out$
END IF
z$ = c$
w$ = c$
bMul z$, w$, c$
z$ = c$
bMod z$, n$, c$
z$ = d$
bDivInt z$, two$, d$
LOOP UNTIL bIsZero%(d$)
END SUB
SUB bModInv (s1$, s2$, out$)
DIM g0$, g1$, g2$, v0$, v1$, v2$, y$, t$, z$
IF NOT bIsRelPrime%(s1$, s2$) THEN out$ = zero$: EXIT SUB
g0$ = s2$: g1$ = s1$
v0$ = zero$: v1$ = one$
DO UNTIL bIsZero%(g1$)
bDivInt g0$, g1$, y$
bMul y$, g1$, t$
bSub g0$, t$, g2$
bMul y$, v1$, t$
bSub v0$, t$, v2$
g0$ = g1$: g1$ = g2$
v0$ = v1$: v1$ = v2$
LOOP
out$ = v0$
IF bIsNeg%(out$) THEN
z$ = out$
bAdd z$, s2$, out$
END IF
END SUB
SUB bGCD (s1$, s2$, out$)
DIM div$, dvd$, t$
'work with copies
div$ = s1$
dvd$ = s2$
IF bIsMore%(div$, dvd$) THEN bSwapString div$, dvd$
DO UNTIL bIsZero%(div$)
bMod dvd$, div$, t$
dvd$ = div$
div$ = t$
LOOP
out$ = dvd$
END SUB
SUB bSqrInt (s$, out$)
DIM t$
DIM olddigits%
IF bIsNeg%(s$) THEN out$ = errormsg$: EXIT SUB
t$ = s$
bInt t$
'a trick: let bSqr() figure the decimal and only find that many digits
olddigits% = digits%
digits% = 0
bSqr t$, out$
digits% = olddigits%
END SUB
FUNCTION bIsBase% (s$)
bIsBase% = INSTR(UCASE$(s$), basechr$)
END FUNCTION
'return true if s1 divides s2
'
FUNCTION bIsDiv% (s1$, s2$)
DIM t$
bMod s2$, s1$, t$
bIsDiv% = (t$ = zero$)
END FUNCTION
'return true if s1 = s2
'
FUNCTION bIsEqual% (s1$, s2$)
bIsEqual% = (s1$ = s2$)
END FUNCTION
'return true if s$ is even, no decimals!
'
FUNCTION bIsEven% (s$)
bIsEven% = (VAL(RIGHT$(s$, 1)) MOD 2 = 0)
END FUNCTION
'return true if s in an integer (no decimal point).
'
FUNCTION bIsInteger% (s$)
bIsInteger% = (INSTR(s$, dp_tree$) = 0)
END FUNCTION
'return true if s1 < s2
'
FUNCTION bIsLess% (s1$, s2$)
bIsLess% = (bComp%(s1$, s2$) = -1)
END FUNCTION
FUNCTION bComp% (s1$, s2$)
DIM s1flag%, s2flag%, sign1%, sign2%
DIM dp1%, dp2%, arg%
'kludge to fix 0<.1
IF LEFT$(s1$, 1) = dp_tree$ THEN s1$ = zero$ + s1$: s1flag% = True
IF LEFT$(s2$, 1) = dp_tree$ THEN s2$ = zero$ + s2$: s2flag% = True
sign1% = (LEFT$(s1$, 1) = neg$)
sign2% = (LEFT$(s2$, 1) = neg$)
dp1% = INSTR(s1$, dp_tree$): IF dp1% = 0 THEN dp1% = LEN(s1$) + 1
dp2% = INSTR(s2$, dp_tree$): IF dp2% = 0 THEN dp2% = LEN(s2$) + 1
IF sign1% <> sign2% THEN
IF sign1% THEN arg% = -1 ELSE arg% = 1
ELSEIF s1$ = s2$ THEN
arg% = 0
ELSEIF (dp1% < dp2%) OR ((dp1% = dp2%) AND (s1$ < s2$)) THEN
arg% = -1
ELSE
arg% = 1
END IF
IF sign1% AND sign2% THEN arg% = -arg%
IF s1flag% THEN s1$ = MID$(s1$, 2)
IF s2flag% THEN s2$ = MID$(s2$, 2)
bComp% = arg%
END FUNCTION
'return true if s1 > s2
'
FUNCTION bIsMore% (s1$, s2$)
bIsMore% = (bComp%(s1$, s2$) = 1)
END FUNCTION
'return true if s is negative
'
FUNCTION bIsNeg% (s$)
bIsNeg% = (LEFT$(s$, 1) = neg$)
END FUNCTION
FUNCTION bIsNotZero% (s$)
DIM flag%, i%
flag% = False
FOR i% = 1 TO LEN(s$)
IF INSTR("0-. ", MID$(s$, i%, 1)) = False THEN flag% = True: EXIT FOR
NEXT i%
bIsNotZero% = flag%
END FUNCTION
'return true if odd
'
FUNCTION bIsOdd% (s$)
bIsOdd% = (VAL(RIGHT$(s$, 1)) MOD 2 <> 0)
END FUNCTION
'return true if s is prime
'
FUNCTION bIsPrime% (s$)
bIsPrime% = (bPrmDiv$(s$, False) = s$)
END FUNCTION
's is pseudoprime to base b if (b,s)=1 and b^(s-1)=1 (mod s). Integers only!
'
FUNCTION bIsPseudoPrime% (s$, bas$)
DIM t$, smin$
DIM flag%
flag% = False
IF bIsRelPrime%(s$, bas$) THEN
smin$ = s$: bInc smin$, -1
bModPower bas$, smin$, s$, t$
flag% = (t$ = one$)
END IF
bIsPseudoPrime% = flag%
END FUNCTION
'return true if s1 and s2 are relatively prime, ie share no factor
'
FUNCTION bIsRelPrime% (s1$, s2$)
DIM gcd$
bGCD s1$, s2$, gcd$
bIsRelPrime% = bIsEqual%(gcd$, one$)
END FUNCTION
'Return true if s$ is zero$ or null, s$ needn't be clean.
'
FUNCTION bIsZero% (s$)
DIM flag%, i%
flag% = True
FOR i% = 1 TO LEN(s$)
IF INSTR("0-. ", MID$(s$, i%, 1)) = False THEN flag% = False: EXIT FOR
NEXT i%
bIsZero% = flag%
END FUNCTION
FUNCTION bSign% (s$)
IF bIsNeg%(s$) THEN bSign% = negative ELSE bSign% = positive
END FUNCTION
FUNCTION bLogDp% (s$, logdp%)
bLogDp% = LEN(s$) - 1 - logdp%
END FUNCTION
FUNCTION bPrmDiv$ (s$, dspflag%)
DIM num$, sfac$, maxfac$, t$
DIM lfac&, lnum&, lmaxfac&, ldfac&
DIM i%, cnt%, flag%, dfac%
num$ = s$
bInt num$
bAbs num$
IF LEN(num$) <= maxlongdig THEN GOSUB bpdLong ELSE GOSUB bpdChar
EXIT FUNCTION
bpdChar:
'try some classic divisibility tests for small factors.
'Cf Gardner, Unexpected Hanging, p.160.
'by 2?
' If dspflag% Then
' frmBncFactor.lblTryNum.Caption = two$
' frmBncFactor.lblTryNum.Refresh
'End If
IF VAL(RIGHT$(num$, 1)) MOD 2 = 0 THEN bPrmDiv$ = two$: RETURN
'by 3?
'IF dspflag% THEN LOCATE , dspflag%: PRINT three$;
' If dspflag% Then
' frmBncFactor.lblTryNum.Caption = three$
' frmBncFactor.lblTryNum.Refresh
'End If
lfac& = 0
FOR i% = 1 TO LEN(num$)
lfac& = lfac& + ASC(MID$(num$, i%, 1)) - asc0
NEXT i%
IF lfac& MOD 3 = 0 THEN bPrmDiv$ = three$: RETURN
'by 5?
'IF dspcol% THEN LOCATE , dspcol%: PRINT five$;
' If dspflag% Then
' frmBncFactor.lblTryNum.Caption = five$
' frmBncFactor.lblTryNum.Refresh
'End If
IF VAL(RIGHT$(num$, 1)) MOD 5 = 0 THEN bPrmDiv$ = five$: RETURN
'by 7, 11, or 13?
'IF dspcol% THEN LOCATE , dspcol%: PRINT "7+";
' If dspflag% Then
' frmBncFactor.lblTryNum.Caption = "7+"
' frmBncFactor.lblTryNum.Refresh
'End If
lfac& = 0
i% = LEN(num$) + 1
cnt% = 3
flag% = True
DO
i% = i% - 3: IF i% < 1 THEN cnt% = i% + 2: i% = 1
IF flag% THEN
lfac& = lfac& + VAL(MID$(num$, i%, cnt%))
ELSE
lfac& = lfac& - VAL(MID$(num$, i%, cnt%))
END IF
flag% = NOT flag%
LOOP WHILE i% > 1
IF lfac& MOD 7 = 0 THEN bPrmDiv$ = "7": RETURN
IF lfac& MOD 11 = 0 THEN bPrmDiv$ = "11": RETURN
IF lfac& MOD 13 = 0 THEN bPrmDiv$ = "13": RETURN
'main loop, increment factor by 2 or 4.
sfac$ = "17"
dfac% = 2
bSqrInt num$, maxfac$
DO
'IF dspcol% THEN LOCATE , dspcol%: PRINT sfac$;
' If dspflag% Then
' frmBncFactor.lblTryNum.Caption = sfac$
' frmBncFactor.lblTryNum.Refresh
'End If
bMod num$, sfac$, t$
IF bIsZero%(t$) THEN EXIT DO
bInc sfac$, dfac%
dfac% = 6 - dfac%
IF bIsMore%(sfac$, maxfac$) THEN sfac$ = num$: EXIT DO
'If INKEY$ = esc$ Then sfac$ = zero$: Exit Do
LOOP
bPrmDiv$ = sfac$
RETURN
bpdLong:
lnum& = VAL(num$)
IF lnum& <= 1 THEN
lfac& = 1&
ELSEIF lnum& MOD 2& = 0& THEN
lfac& = 2&
ELSEIF lnum& MOD 3& = 0& THEN
lfac& = 3&
ELSE
lmaxfac& = INT(SQR(lnum&))
lfac& = 5&
ldfac& = 2&
DO
'IF dspcol% THEN LOCATE , dspcol%: PRINT lfac&;
' If dspflag% Then
' frmBncFactor.lblTryNum.Caption = LTrim$(Str$(lfac&))
' frmBncFactor.lblTryNum.Refresh
'End If
IF lnum& MOD lfac& = 0& THEN EXIT DO
lfac& = lfac& + ldfac&
ldfac& = 6& - ldfac&
IF lfac& > lmaxfac& THEN lfac& = lnum&: EXIT DO
LOOP
END IF
bPrmDiv$ = LTRIM$(STR$(lfac&))
RETURN
END FUNCTION
FUNCTION bMaxInt% (n1%, n2%)
IF n1% >= n2% THEN bMaxInt% = n1% ELSE bMaxInt% = n2%
END FUNCTION
Pete