Thread Rating:
  • 0 Vote(s) - 0 Average
  • 1
  • 2
  • 3
  • 4
  • 5
KISS MY ASCII GOOD PI!
#31
Pete
why do you increase the precision on every loop count ?
I assume that's what limit&& does ?
Reply
#32
(08-26-2022, 08:48 PM)Jack Wrote: Pete
why do you increase the precision on every loop count ?
I assume that's what limit&& does ?

For faster computations. Let's say we want to use 150-digits. I could just set limit&& = 150 at the start, but when we do the initial loops, where only a few digits are returned, the numbers that are generated to make those smaller amounts are much larger in scale than they need to be to produce the same results, but when we approach a 150 digit readout, all the computations that make it up need to be worked out to 150 digit precision or greater in order for the results to be valid. This is where Treebeard's string functions miss when at 26 and 38 digits, the SQR(8) or 8 is not worked out far enough. Oh, for mine, I just put in a cheat with the SQR(8) for now, which defines the value just once, at 200-digits. A bit more than is needed for all the equations.

From what I've tested so far, it's the non-updated division routine that is where I would have to go to achieve better speed. I'm just not up to tackling that, at the present.

Another consideration would be to tweak the limit&& variable so it could be interchangeable with the digit%variable. As it stands now, the limit&& variable needs to be a bit bigger than the digit% variable to produce the correct results.


Pete
Reply
#33
This cake is baked, for now. Tweaked the string math division part just enough to match speed with Treebeard's routine. I also switched out digits% to limit&& variable.

Code: (Select All)
'Jack's Ramanujan's Pi Estimator with Pete's String Math Routines.
WIDTH 180, 42
_SCREENMOVE 0, 0
DIM SHARED sqrt$, limit&&, betatest%
betatest% = 0
DIM AS STRING sum, f, f4, f4k, c1, c2, c3, c34k, t1, t2, t3
DIM AS LONG k, k4
DIM t AS DOUBLE

limit&& = 150: square_root "8", sqrt$ ' Limit must be as many or more digits than the max digits of the returned value for pi.

FOR pete% = 0 TO 16
    limit&& = pete% + 10 + pete% * 8
    t = TIMER
    c1 = "1103"
    c2 = "26390"
    c3 = "396"
    f = "1"
    f4k = "1"
    sum = "1103"
    c34k = "1"
    k4 = 0
    t1 = c3
    t2 = c3
    sm t1, "*", t2, c3
    t1 = c3
    t2 = c3
    sm t1, "*", t2, c3

    FOR k = 1 TO limit&& / (7.984)
        t1 = f
        sm STR$(k), "*", t1, f
        IF betatest% THEN PRINT "results = "; f: SLEEP
        t1 = f: t2 = f
        sm t1, "*", t2, f4
        IF betatest% THEN PRINT "results = "; f4: SLEEP
        t1 = f4: t2 = f4
        sm t1, "*", t2, f4
        IF betatest% THEN PRINT "results = "; f4: SLEEP
        t1 = c34k
        sm c3, "*", t1, c34k
        IF betatest% THEN PRINT "results = "; c34k: SLEEP
        t1 = STR$(k4 + 1)
        t2 = f4k
        sm t1, "*", t2, f4k
        IF betatest% THEN PRINT "results = "; f4k: SLEEP
        t1 = STR$(k4 + 2)
        t2 = f4k
        sm t1, "*", t2, f4k
        IF betatest% THEN PRINT "results = "; f4k: SLEEP
        t1 = STR$(k4 + 3)
        t2 = f4k
        sm t1, "*", t2, f4k
        IF betatest% THEN PRINT "results = "; f4k: SLEEP
        t1 = STR$(k4 + 4)
        t2 = f4k
        sm t1, "*", t2, f4k
        IF betatest% THEN PRINT "results = "; f4k: SLEEP
        k4 = k4 + 4
        t1 = STR$(k)
        sm t1, "*", c2, t2
        IF betatest% THEN PRINT "results = "; t2: SLEEP
        sm c1, "+", t2, t1
        IF betatest% THEN PRINT "results = "; t1: SLEEP
        sm f4k, "*", t1, t2
        IF betatest% THEN PRINT "results = "; t2: SLEEP
        sm f4, "*", c34k, t1
        IF betatest% THEN PRINT "results = "; t1: SLEEP
        sm t2, "/", t1, t3
        IF betatest% THEN PRINT "results = "; t3: SLEEP
        t1 = sum
        sm t1, "+", t3, sum
        IF betatest% THEN PRINT "sum =   "; sum: SLEEP
        CALL pi(t1, sum, k)
    NEXT
    COLOR 14, 0: PRINT "Ramanujan pi = "; MID$("3.141592653589793238462643383279502884197169399375105820974944592307816406286208998628034825342117067982148086513282306647093844609550582231725359408128481", 1, 11 + (k - 2) * 8)
    COLOR 7, 0
    t = TIMER - t
    PRINT "Time:"; t: PRINT
NEXT pete%
END

SUB pi (t1$, sum$, k)
    REM square_root "8", sqrt$
    IF betatest% THEN PRINT "Pi # = "; sqrt$: SLEEP
    t2$ = "9801"
    sm sqrt$, "/", t2$, t3$
    IF betatest% THEN PRINT "Pi # = "; t3$: SLEEP
    sm t3$, "*", sum$, t2$
    IF betatest% THEN PRINT "Pi # = "; t2$: SLEEP
    sm t1$, "/", t2$, t3$
    IF betatest% THEN PRINT "Pi # = "; t3$: SLEEP
    sm "1", "/", t2$, t1$
    IF betatest% THEN PRINT "Pi # = "; t1$: SLEEP
    PRINT "loop #"; LTRIM$(STR$(k));: LOCATE , 10: PRINT " pi = "; MID$(t1$, 1, 11 + (k - 1) * 8);: COLOR 8, 0: PRINT MID$(t1$, 11 + (k - 1) * 8 + 1, 4): COLOR 7, 0
END SUB

DEFINT A-Z
SUB sm (s_var1$, operator$, s_var2$, runningtotal$)
    DIM AS _INTEGER64 a, c, aa, cc, s, ss
    stringmatha$ = s_var1$: stringmathb$ = s_var2$

    SELECT CASE operator$
        CASE "+", "-"
            GOSUB string_add_subtract_new
        CASE "*"
            GOSUB string_multiply_new
        CASE "/"
            GOSUB string_divide
        CASE ELSE
            PRINT "Error, no operator selected. operator$ = "; operator$: END
    END SELECT
    EXIT SUB

    string_divide:
    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 SUB
    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$
            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$
        GOSUB string_multiply_new ' Gets runningtotal$
        stringmatha$ = divremainder$: stringmathb$ = runningtotal$
        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 SUB

    runningtotal$ = stringmathb$: stringmathb$ = ""
    IF divsign% THEN runningtotal$ = "-" + runningtotal$

    IF stringmathround$ <> "" THEN runningtotal$ = runningtotal$ + stringmathround$
    RETURN

    string_add_subtract_new:
    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$

            string_compare 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
    RETURN

    string_multiply_new:
    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 z$ = "" OR z$ = "0" THEN z$ = "0" ELSE z$ = sign$ + z$

    decimal% = 0: sign$ = ""

    runningtotal$ = z$
    RETURN
END SUB

DEFINT A-Z
SUB string_compare (compa$, compb$, gl%)
    DO
        ' 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 +
        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

        ' A decimal and non-decimal.
        j% = INSTR(compa$, ".")
        k% = INSTR(compb$, ".")

        IF j% = 0 AND k% THEN
            IF compa$ = "0" THEN gl% = -1 ELSE gl% = 1
            EXIT DO
        END IF
        IF k% = 0 AND j% THEN
            IF compb$ = "0" THEN gl% = 1 ELSE gl% = -1
            EXIT DO
        END IF

        ' Both decimals.
        IF j% THEN
            IF compa$ > compb$ THEN
                gl% = 1
            ELSEIF compa$ = compb$ THEN gl% = 0
            ELSEIF compa$ < compb$ THEN gl% = -1
            END IF
            EXIT DO
        END IF

        ' 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
END SUB

DEFINT A-Z
SUB square_root (x$, sqrt$)
    oldy$ = "": sqrt$ = "": custom_limit&& = limit&& + 50

    IF INSTR(x$, ".") THEN
        decx$ = MID$(x$, 1, INSTR(x$, ".") - 1)
        x$ = MID$(x$, 1, INSTR(x$, ".") - 1) + MID$(x$, INSTR(x$, ".") + 1)
        IF LEN(x$) = 1 THEN x$ = x$ + "0"
    ELSE
        decx$ = x$
    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
        sm z$, "-", k$, runningtotal$
        z$ = runningtotal$ + (MID$(x$, 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
                sm sqrt$, "*", "2", y$
                y$ = y$ + LTRIM$(STR$(j&&))
            ELSE
                y$ = LTRIM$(STR$(j&&))
            END IF

            sm y$, "*", LTRIM$(STR$(j&&)), runningtotal$

            string_compare runningtotal$, z$, gl%
            IF gl% > -1 THEN
                IF gl% = 0 THEN
                    h% = 0: oldy$ = y$ ' Perfect square division.
                ELSE
                    h% = 1
                END IF
                sm 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%))

                sm 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
        x$ = x$ + "00"
    LOOP

    IF dpx&& THEN
        sqrt$ = MID$(sqrt$, 0, dpx&& + 1) + "." + MID$(sqrt$, dpx&& + 1)
    END IF
END SUB


Good pi!

Pete
Reply




Users browsing this thread: 2 Guest(s)