QB64 Phoenix Edition
Faster addition in string math. Now with multiplication! - Printable Version

+- QB64 Phoenix Edition (https://qb64phoenix.com/forum)
+-- Forum: Chatting and Socializing (https://qb64phoenix.com/forum/forumdisplay.php?fid=11)
+--- Forum: General Discussion (https://qb64phoenix.com/forum/forumdisplay.php?fid=2)
+--- Thread: Faster addition in string math. Now with multiplication! (/showthread.php?tid=784)

Pages: 1 2 3


RE: Faster addition in string math. Now with multiplication! - Jack - 08-21-2022

not bad Pete, 6 second here


RE: Faster addition in string math. Now with multiplication! - Pete - 08-21-2022

@Jack

6 seconds for 5000 iterations? I mean I know I bought my computer used from a guy named F. Flintstone, but I wouldn't have thought the difference would b that great. on faster systems. I figured most of you guys would be able to run 5000 loops in around 15 - 20 seconds.

Pete


RE: Faster addition in string math. Now with multiplication! - SMcNeill - 08-22-2022

12.5 seconds on my laptop, unless I got my timer in the wrong place to compare with you guys.

Code: (Select All)
Width 160, 42
_ScreenMove 0, 0
Do
    limit&& = 5000
    'betatest% = -1
    If betatest% Then limit&& = 16

    Do
        Input "Number: "; x$: Print

        If x$ = "" Then System

        If Left$(x$, 1) = "-" Then
            Print "Negatives not allowed. Redo..": _Delay 2: Print
        Else
            validate_string x$
            If InStr(x$, "invalid") = 0 Then Exit Do
            Print "Sorry, "; x$: _Delay 1: Print
        End If
    Loop

    x# = Val(x$) ' Needed for QB64 SQR() comparison only.
    oldy$ = ""

    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

    timed## = Timer
    Do
        stringmatha$ = z$: stringmathb$ = k$
        string_math z$, "-", k$, runningtotal$, terminating_decimal%, limit&&
        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
                string_math sqrt$, "*", "2", y$, terminating_decimal%, limit&&
                y$ = y$ + LTrim$(Str$(j&&))
            Else
                y$ = LTrim$(Str$(j&&))
            End If

            string_math y$, "*", LTrim$(Str$(j&&)), runningtotal$, terminating_decimal%, limit&&

            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
                string_math oldy$, "*", LTrim$(Str$(j&& - h%)), runningtotal$, terminating_decimal%, limit&&
                If String$(Len(z$), "0") = z$ And runningtotal$ = "0" And i&& >= Len(decx$) Then Exit Do

                If dp&& = 0 Then ' Limited to && size unless converted to string.
                    If i&& >= Len(decx$) Then
                        dp&& = Int(Len(decx$) / 2 + .5)
                        If dp&& = 0 Then dp&& = -1
                    End If
                End If

                If betatest% 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%))

                string_math oldy$, "*", LTrim$(Str$(j&& - h%)), runningtotal$, terminating_decimal%, limit&&
                k$ = runningtotal$

                If betatest% Then Print "Remainder "; z$; " minus "; k$; " = ";
                Exit For
            End If
            oldy$ = y$
        Next

        If betatest% Then
            string_math stringmatha$, "-", stringmathb$, runningtotal$, terminating_decimal%, limit&&
            Print runningtotal$; " sqrt = "; sqrt$
        End If

        i&& = i&& + 2
        If Len(z$) >= limit&& Then Exit Do
        x$ = x$ + "00"
    Loop

    Print

    If dp&& Then
        sqrt$ = Mid$(sqrt$, 0, dp&& + 1) + "." + Mid$(sqrt$, dp&& + 1)
    End If

    _Clipboard$ = sqrt$
    Print "QB64 SQR:"; Sqr(x#)
    Print "Pete SQR: "; sqrt$: _Delay 1
    Print
    Print Using "###.##### seconds"; Timer - timed##
    Clear
4 Loop

Sub string_math (stringmatha$, operator$, stringmathb$, runningtotal$, terminating_decimal%, limit&&)
    Dim As _Integer64 a, b, c, aa, bb, cc, s, ss
    a1$ = stringmatha$: b1$ = stringmathb$

    Select Case operator$
        Case "+", "-"
            GoTo string_add_subtract_new
        Case "*"
            GoTo string_multiply_new
        Case "/"
            GoTo string_divide
        Case Else
            Print "Error, no operator selected. operator$ = "; operator$
    End Select

    string_divide:
    terminating_decimal% = 0: divsign% = 0: divremainder& = 0: divremainder$ = "": divplace& = 0: divplace2& = 0: quotient$ = "": divcarry& = 0
    operationdivision% = -1
    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: operationdivision% = 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
        For div_i% = 9 To 1 Step -1
            stringmatha$ = LTrim$(Str$(div_i%)): stringmathb$ = d1divisor$
            m_product$ = "": GoSub string_multiply_new
            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(m_product$) Or Len(tempcutd$) = Len(m_product$) And m_product$ <= tempcutd$ Then Exit For
        Next
        quotient$ = quotient$ + LTrim$(Str$(div_i%))
        stringmatha$ = LTrim$(Str$(div_i%)): stringmathb$ = d1divisor$
        m_product$ = "": GoSub string_multiply_new
        operator$ = "-"
        stringmatha$ = divremainder$
        stringmathb$ = m_product$
        GoSub string_add_subtract_new
        divremainder$ = stringmatha$
        operator$ = "/"
    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
    operationdivision% = 0
    stringmathb$ = quotient$: quotient$ = ""

    If stringmathb$ = "overflow" Then divsign% = 0: operationdivision% = 0: Exit Sub

    runningtotal$ = stringmathb$: stringmathb$ = ""
    If divsign% Then runningtotal$ = "-" + runningtotal$

    If stringmathround$ <> "" Then runningtotal$ = runningtotal$ + stringmathround$
    operationdivision% = 0
    Exit Sub

    '------------------------------------------------------------------------
    string_add_subtract_new:
    s = 18

    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

    s = 18: z$ = ""

    Do
        i&& = i&& + s
        x1$ = Mid$(a$, Len(a$) - i&& + 1, s)
        x2$ = Mid$(b$, Len(b$) - i&& + 1, s)
        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
        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
    Exit Sub

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

    Do
        h&& = h&& + s: i&& = 0
        x2$ = Mid$(b$, Len(b$) - h&& + 1, s)
        While -1
            i&& = i&& + s
            x1$ = Mid$(a$, Len(a$) - i&& + 1, s)
            a = Val(sign_a$ + x1$) * Val(sign_b$ + x2$) + c
            If betatest% Then Print "x1$ = "; x1$;: Locate , 20: Print "x2$ = "; x2$;: Locate , 35: Print Val(x1$) * Val(x2$) + c;: Locate , 55: Print "c = "; c;: Locate , 75: Print "val = "; a,
            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$
            If betatest% Then Locate , 100: Print a;: Locate , 120: Print z$
            If i&& >= Len(a$) And c = 0 Then Exit While
        Wend

        jj&& = jj&& + 1

        If jj&& > 1 Then
            ii&& = 0: cc = 0
            aa$ = holdaa$
            bb$ = z$ + String$((jj&& - 1) * s, "0")
            If betatest% Then Print "aa$ "; aa$; " + bb$ "; z$;: Color 14, 0: Print String$(jj&& - 1, "0"); " = ";: Color 7, 0: Sleep
            Do
                ii&& = ii&& + ss
                xx1$ = Mid$(aa$, Len(aa$) - ii&& + 1, ss)
                xx2$ = Mid$(bb$, Len(bb$) - ii&& + 1, ss)
                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$
            If betatest% Then Color 2, 0: Print holdaa$: Color 7, 0
        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$

    Exit Sub

    replace_decimal:
    If addsubplace& Then
        addsubx1$ = String$(addsubplace& - Len(addsubx1$), "0") + addsubx1$
        addsubx1$ = Mid$(addsubx1$, 1, Len(addsubx1$) - addsubplace&) + "." + Mid$(addsubx1$, Len(addsubx1$) - addsubplace& + 1)
        Do Until Right$(addsubx1$, 1) <> "0" ' Remove trailing zeros in a decimal sum.
            addsubx1$ = Mid$(addsubx1$, 1, Len(addsubx1$) - 1)
            addsubplace& = addsubplace& - 1
        Loop
        If Right$(addsubx1$, 1) = "." Then addsubx1$ = Mid$(addsubx1$, 1, Len(addsubx1$) - 1) ' Number is now an integer.
    End If
    Return

    string_comp:
    Do
        ' Remove trailing zeros after a decimal point.
        If InStr(acomp$, ".") Then
            Do Until Right$(acomp$, 1) <> "0" And Right$(acomp$, 1) <> "." And Right$(acomp$, 1) <> "-"
                acomp$ = Mid$(acomp$, 1, Len(acomp$) - 1)
            Loop
        End If
        If InStr(bcomp$, ".") Then
            Do Until Right$(bcomp$, 1) <> "0" And Right$(bcomp$, 1) <> "." And Right$(bcomp$, 1) <> "-"
                bcomp$ = Mid$(bcomp$, 1, Len(bcomp$) - 1)
            Loop
        End If

        If Mid$(acomp$, 1, 2) = "-0" Or acomp$ = "" Or acomp$ = "-" Then acomp$ = "0"
        If Mid$(bcomp$, 1, 2) = "-0" Or bcomp$ = "" Or bcomp$ = "-" Then bcomp$ = "0"

        ' A - and +
        If Left$(acomp$, 1) = "-" Then j% = -1
        If Left$(bcomp$, 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(acomp$, ".")
        k% = InStr(bcomp$, ".")
        If j% = 0 And k% Then
            If acomp$ = "0" Then gl% = -1 Else gl% = 1
            Exit Do
        End If
        If k% = 0 And j% Then
            If bcomp$ = "0" Then gl% = 1 Else gl% = -1
            Exit Do
        End If

        ' Both decimals.
        If j% Then
            If acomp$ > bcomp$ Then
                gl% = 1
            ElseIf acomp$ = bcomp$ Then gl% = 0
            ElseIf acomp$ < bcomp$ Then gl% = -1
            End If
            Exit Do
        End If

        ' Both positive or both negative whole numbers.
        Select Case Len(acomp$)
            Case Is < Len(bcomp$)
                gl% = -1
            Case Is = Len(bcomp$)
                If acomp$ = bcomp$ Then
                    gl% = 0
                ElseIf acomp$ > bcomp$ Then gl% = 1
                ElseIf acomp$ < bcomp$ Then gl% = -1
                End If
            Case Is > Len(bcomp$)
                gl% = 1
        End Select
        Exit Do
    Loop
    Return
End Sub

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: Print "1*": Exit Do
        If j% = 0 And k% Then gl% = 1: Print "2*": 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: Print "4*" Else gl% = 1: Print "5*"
            Exit Do
        End If
        If k% = 0 And j% Then
            If compb$ = "0" Then gl% = 1: Print "6*" Else gl% = -1: Print "7*"
            Exit Do
        End If

        ' Both decimals.
        If j% Then
            If compa$ > compb$ Then
                gl% = 1: Print "8*"
            ElseIf compa$ = compb$ Then gl% = 0: Print "9*"
            ElseIf compa$ < compb$ Then gl% = -1: Print "10*"
            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

Sub validate_string (stringmathb$)
    Do ' Faux loop.
        vsn_negcnt& = 0: vsn_poscnt& = 0: vsn_depresent& = 0: decimalcnt& = 0: vsn_numberpresent& = 0: vsn_zerospresent& = 0
        If Left$(stringmathb$, 1) = "-" Then stringmathb$ = Mid$(stringmathb$, 2): sm_sign$ = "-" Else sm_sign$ = ""
        If Left$(stringmathb$, 1) = "+" Then If sm_sign$ <> "-" Then stringmathb$ = Mid$(stringmathb$, 2) Else stringmathb$ = "invalid number": Exit Do
        If InStr(UCase$(stringmathb$), "D") Or InStr(UCase$(stringmathb$), "E") Then ' Evaluate for Scientific Notation.
            For sm_i& = 1 To Len(stringmathb$)
                validatenum$ = Mid$(UCase$(stringmathb$), sm_i&, 1)
                Select Case validatenum$
                    Case "+"
                        If vsn_depresent& Then vsn_poscnt& = vsn_poscnt& + 1 Else stringmathb$ = "invalid number": Exit Do
                    Case "-"
                        If vsn_depresent& Then vsn_negcnt& = vsn_negcnt& + 1 Else stringmathb$ = "invalid number": Exit Do
                    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$(stringmathb$, 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 stringmathb$ = Mid$(stringmathb$, 1, 1) + "." + Mid$(stringmathb$, 2) ' Standardize "."
            If vsn_numberpresent& = 0 Or vsn_negcnt& = 1 And vsn_poscnt& = 1 Or decimalcnt& > 1 Or InStr(stringmathb$, ".") <> 2 Then stringmathb$ = "invalid number": Exit Do
            vsn_depresent& = InStr(stringmathb$, "e")
            sm_x$ = Mid$(stringmathb$, vsn_depresent& + 1, 1) ' Standardize exponent "+" these two lines.
            If sm_x$ <> "+" And sm_x$ <> "-" Then stringmathb$ = Mid$(stringmathb$, 1, vsn_depresent&) + "+" + Mid$(stringmathb$, vsn_depresent& + 1)
            If Mid$(stringmathb$, vsn_depresent& + 2, 1) = "0" Then
                If Mid$(stringmathb$, vsn_depresent& + 3, 1) <> "" Then stringmathb$ = "invalid number": Exit Do ' No leading zeros allowed in exponent notation.
            End If
            jjed& = InStr(stringmathb$, "e") ' Get position of notation.
            valexpside$ = Mid$(stringmathb$, jjed&) ' These two lines break up into number and notation
            stringmathb$ = Mid$(stringmathb$, 1, jjed& - 1) ' stringmathb$ is +- single digit whole number, decimal point and decimal number. valexpside$ is notation, sign and exponent.
            Do Until Right$(stringmathb$, 1) <> "0" ' Remove any trailing zeros for number. Example 1.0d3 or 1.0000d3, etc.
                stringmathb$ = Mid$(stringmathb$, 1, Len(stringmathb$) - 1)
            Loop
            If Val(Mid$(stringmathb$, 1, InStr(stringmathb$, ".") - 1)) = 0 Then
                If Right$(stringmathb$, 1) = "." Then
                    stringmathb$ = "0.e+0" ' Handles all types of zero entries.
                Else
                    stringmathb$ = "invalid number": Exit Do
                End If
                Exit Do
            End If
            stringmathb$ = sm_sign$ + stringmathb$ + valexpside$
            Exit Do
        Else
            For sm_i& = 1 To Len(stringmathb$)
                validatenum$ = Mid$(stringmathb$, 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
                        stringmathb$ = "invalid number": Exit Do
                End Select
            Next
            If decimalcnt& > 1 Or vsn_negcnt& > 1 Or vsn_poscnt& > 1 Or vsn_negcnt& >= 1 And vsn_poscnt& >= 1 Then
                stringmathb$ = "invalid number": Exit Do
            End If

            Rem IF INSTR(stringmathb$, "$") THEN GOSUB currency_validate
            Rem IF INSTR(stringmathb$, ",") THEN
            Rem GOSUB comma_validation
            Rem IF stringmathb$ = "invalid number" THEN exit do
            Rem GOSUB comma_removal
            Rem END IF

            If Right$(stringmathb$, 1) = "." Then stringmathb$ = Mid$(stringmathb$, 1, Len(stringmathb$) - 1)
            Do Until Left$(stringmathb$, 1) <> "0" ' Strip off any leading zeros.
                stringmathb$ = Mid$(stringmathb$, 2)
            Loop
            stringmathb$ = sm_sign$ + stringmathb$
            If InStr(stringmathb$, ".") Then
                Do Until Right$(stringmathb$, 1) <> "0" ' Strip off any trailing zeros in a decimal.
                    stringmathb$ = Mid$(stringmathb$, 1, Len(stringmathb$) - 1)
                Loop
            End If
            If Right$(stringmathb$, 1) = "." Then stringmathb$ = Mid$(stringmathb$, 1, Len(stringmathb$) - 1)
            If vsn_numberpresent& = 0 Then
                If vsn_zerospresent& Then
                    stringmathb$ = "0"
                Else
                    stringmathb$ = "invalid number"
                End If
            End If
        End If
        Exit Do
    Loop
End Sub



RE: Faster addition in string math. Now with multiplication! - Pete - 08-22-2022

Now working with pi and found one more bug, which didn't affect all of the sqrt calcs, amazingly enough.

Before the DO:LOOP that uses the counter h&& = h&& + s begins, I added...

IF LEN(a$) < LEN(b$) THEN SWAP a$, b$

The loop takes care of some calculation where the VAL() drops leading zeros, but to do so properly, the fist variable a$ of a$ and b$ variables, must always be the longest string, or at lease equal in length for that leading zero conversion from VAL() to STR() to work properly.

I have edited the last post with this statement addition.

It looks like I lost a couple of seconds in the process. Oh well, fast and accurate beats faster and wrong.

Pete