Menu

How much recursion is too much?

Anonymous
2019-06-17
2019-06-20
  • Anonymous

    Anonymous - 2019-06-17

    Crazy amounts of recursion in compiled programs appears to freeze the VM, at least on Android 5.1.1, and now the SF forums editor hates me.

    
    
     
  • Markus Hoffmann

    Markus Hoffmann - 2019-06-19

    Hm, OK. Can you be more specific? What version of X11-Basic are you using? What is the kind of recursion problem you see?

     
    • Yet Another Troll

      In this case, I was the anonymoose. It was the only way SF seems to let me post a new topic now, but the editor was even glitchier than usual and posted prematurely. In this program, if the recursion depth guard at about line 300 is disabled, the program compiled and run, and 7500 input, it freezes when the actual recursion depth reaches 467 or so. With the guard, the program runs to completion, eventually, but then not all possible longest palindromic subsequences can be calculated. I realize the call stack is a finite resource and this can be worked around using another matrix like in the FORTRAN II days. :)

      #!/usr/bin/xbasic
      
      Program Palindromic
       ShowK
       Input "How long? ", N%
       HideK
      
       Start = Timer
      
       Alpha$ = "GATTACA"
       ! Alpha$ = "non~EXO xenon"
       ! Alpha$ = "Able was I, ere I saw Elba."
       ! Alpha$ = "Eva, can I see beezies ~~ in a cave???"
       ! Alpha$ = "!!A MAN. A PLAN. A CANAL. PANAMA!"
      
       Alpha$ = Upper$(Alpha$)
       LenA% = Len(Alpha$)
      
       If Glob(Alpha$, "*[-{}]*") Then
        Print "Forbidden characters in Alpha$"
        Stop
       EndIf
      
       ' Belt, suspenders, drones, crane, cargo helicopter, orbital skyhook
       Dim Alpha%(256)
       Clr Alpha%()
       For i% = 1 To Len(Alpha$)
        ' Parallelizable, but would it actually be worth it?
        Alpha%(Asc(Mid$(Alpha$, i%, 1))) = True
       Next i%
      
       Corpus$ = String$(N%, "-") ! No sentinels this time
      
       Print "Allocated "; Len(Corpus$); " bytes in "; Timer - Start
      
       Clr i%, j%, k%, VPA%, VPC%
      
       ' Randomize
      
       ' Watch out on 64-bit
       VPA% = VarPtr(Alpha$)
       VPC% = VarPtr(Corpus$)
       For i% = 1 To N%
        If (i% And 0xFFF) = 0 Then
         Print " "; i%; "  "; Chr$(13);
         Flush
        EndIf
        ' Parallelizable, I guess
        ' Repeat
         ! RANDOM sometimes b0rks in Winblows
         j% = Random(LenA%)
        ' Until (0 = j%) Or (j% < LenA%)
        ' k% = Asc(Mid$(Alpha$, j% + 1, 1))
        k% = Peek(VPA% + j% + 1 - 1)
        ' Caution, this sanity check adds significant overhead
        If Not Alpha%(k%) ! InStr(Alpha$, Chr$(k%)) = 0 Then
         Print "Invalid character at 0x"; Hex$(VPA%); " + "; j%, k%
         Stop
        EndIf
        ' Mid$(Corpus$, i%, 1) = Chr$(k%)
        Poke VPC% + i% - 1, k%
       Next i%
      
       Print "Corpus$ initialized in "; Timer - Start
      
       If N% <= 600 Then
        Print "'"; Corpus$; "'"
       EndIf
      
       If Glob(Corpus$, "*[!" + Alpha$ + "]*") Then
        Print "Invalid characters!"
        Stop
       EndIf
      
       Print "Sanity checked in "; Timer - Start
      
       ' Bottom-up algorithm blatantly ripped off from:
       ' https://www.techiedelight.com/longest-palindromic-subsequence-using-dynamic-programming/
      
       If N% < LenA% Then
        Print "'"; Alpha$; "'"
        Corpus$ = Upper$(Alpha$)
        N% = Len(Corpus$)
       EndIf
      
       If N% <= 600 Then
        Print "'"; Corpus$; "'"
       EndIf
      
       Dim Lookup%(N% + 1, N% + 1) ! This doesn't seem too terribly bad
       Clr Lookup%()
      
       Print ((N% + 1) ^ 2) * 4; " bytes of ";
       Print "monster matrix allocated in "; Timer - Start
       Flush
      
       Clr i%, j%, k%, l%, VPC%
      
       VPC% = VarPtr(Corpus$)
      
       For i% = 1 To N%
        Print Chr$(13); "Row "; i%; " ";
        For j% = 1 To N%
      
         ' k% = Asc(Mid$(Corpus$, i%, 1))
         ' l% = Asc(Mid$(Corpus$, N% - j% + 1, 1))
         k% = Peek(VPC% + i% - 1)
         l% = Peek(VPC% + N% - j% + 1 - 1)
      
         If (Not Alpha%(k%)) Or (Not Alpha%(l%)) Then
          Print "Bad chars from Corpus$?", k%, l%
          Stop
         Else If k% = l% Then
          Lookup%(i%, j%) = Lookup%(i% - 1, j% - 1) + 1
         Else If Lookup%(i% - 1, j%) > Lookup%(i%, j% - 1) Then
          Lookup%(i%, j%) = Lookup%(i% - 1, j%)
         Else
          Lookup%(i%, j%) = Lookup%(i%, j% - 1)
         EndIf
      
        Next j%
      
        Print "   "; Round(Timer - Start, 3); "        ";
       Next i%
      
       Print
       Print Lookup%(N%, N%); " length of longest palindromic subsequence(s),"
      
       Print "Found length in "; Timer - Start
      
       ' Even more Globals???
      
       Dim H%(128) ! Hash table for S$(), size must be power of two
       Dim S$(16)  ! DYNAMIC, Duplicated string table for StringInsanity
       Dim C%(16)  ! DYNAMIC, Open hashing chains for S$() and H%()
      
       HMask% = UBound(H%()) - 1
       ArrayFill H%(), -1
       Clr S$(), C%()
       SCount% = 0
      
       ' Still more Globals, call stack limits are nasty
      
       Clr R$, PalindromeCount%, MaxCallDepth%, MaxActualCallDepth%
      
       GoSub StringInsanity(N%, N%, 0, 0)
      
       Print PalindromeCount%, SCount%, MaxCallDepth%, MaxActualCallDepth%
      
       Print "Found some/all/most? in "; Timer - Start
      
       Print "OK"
      End
      
      ' IN     C$, N%, i%, j%, R$, CallDepth%
      ' OUT    NIL
      ' IN/OUT PalindromeCount%, MaxCallDepth%, MaxActualCallDepth%
      ' COMMON Alpha%(), Lookup%(), S$(), H%(), C%(), SCount%
      
      Procedure StringInsanity(i%, j%, CallDepth%, ActualCallDepth%)
       ' Local VPC%, VPR%
       Local k%, l%
       ' Local KeepGoing%, PalindromeOK%
       ' Global Alpha%()
      
       Inc ActualCallDepth%
       If ActualCallDepth% > MaxActualCallDepth% Then
        MaxActualCallDepth% = ActualCallDepth%
        'Print MaxActualCallDepth%, MaxCallDepth%
       EndIf
      
      TailCallElimination:
      
       Inc CallDepth%
       If CallDepth% > MaxCallDepth% Then
        MaxCallDepth% = CallDepth%
       EndIf
      
       Print "  "; ActualCallDepth%; " "; CallDepth%; " ";
       Print MaxActualCallDepth%; " "; MaxCallDepth%;
       Print "  "; Chr$(13);
       Flush
      
       VPC% = VarPtr(Corpus$)
      
       If (i% = 0) Or (j% = 0) Then
        k% = 1
        l% = Len(R$)
        VPR% = VarPtr(R$)
        KeepGoing% = (l% = Lookup%(N%, N%))
        PalindromeOK% = (l% = Lookup%(N%, N%))
        While KeepGoing%
         If Not (k% < l%) Then
          PalindromeOK% = True
          KeepGoing% = False
         Else If (Not Alpha%(Peek(VPR% + k% - 1))) Or (Not Alpha%(Peek(VPR% + l% - 1))) Then
          Print "Bad character(s) at", k%, l%
          Stop
         Else If Not (Peek(VPR% + k% - 1) = Peek(VPR% + l% - 1)) Then
          PalindromeOK% = False
          KeepGoing% = False
         Else
          Inc k%
          Dec l%
         EndIf
        Wend
        If Not PalindromeOK% Then
         Print PalindromeOK%, Len(R$), k%, l%, "'"; R$; "'"
         Stop
        EndIf
      
        Hash% = CRC(R$) And HashMask%
        Prev% = 0xDEAFBEEF
        Curr% = H%(Hash%)
        Do
         Exit If Curr% < 0
         Exit If S$(Curr%) = R$
         Prev% = Curr%
         Curr% = C%(Curr%)
        Loop
      
        If Curr% < 0 Then
         If SCount% = UBound(S$()) Then
          Print "*";
          Flush
          Dim S$(SCount% + ShR(SCount%, 2) + 4) ! REDIM PRESERVE
          Dim C%(SCount% + ShR(SCount%, 2) + 4) ! REDIM PRESERVE
          Print "*";
          Flush
         EndIf
      
         S$(SCount%) = R$
         C%(SCount%) = H%(Hash%)
         H%(Hash%) = SCount%
         Inc SCount%
      
         Inc PalindromeCount%
         Print PalindromeCount%; "  '"; R$; "'  "; Timer - Start
        Else
         If Prev% >= 0 Then
          ' Move the found duplicate string up to the front
          ' of the hash chain in case of repeated searches
          C%(Prev%) = C%(Curr%)
          C%(Curr%) = H%(Hash%)
          H%(Hash%) = Curr%
         EndIf
         Print " DUP ";
         ' Print "'"; R$; "'  "; Hash%; " "; Prev%; " "; Curr%; "     ";
         ' Print Chr$(13);
        EndIf
        Flush
      
       Else If Peek(VPC% + i% - 1) = Peek(VPC% + N% - j% + 1 - 1) Then
        ' R$ = R$ + Mid$(C$, i%, 1)
        R$ = R$ + Chr$(Peek(VPC% + i% - 1))
        k% = Lookup%(N%, N%) - Len(R$) + 1
        l% = Len(R$)
        Clr PalindromeOK%
        If Not (k% < l%) Then
         PalindromeOK% = True
        Else If Mid$(R$, k%, 1) = Mid$(R$, l%, 1) Then
         PalindromeOK% = True
        Else
         PalindromeOK% = False
        EndIf
        If Not PalindromeOK% Then
         Print "'"; R$; "' NOT OK"
         Stop
        Else If k% < l% Then
         ' Print "'"; R$; "' OK"
         R$ = R$ + Reverse$(Left$(R$, Lookup%(N%, N%) - Len(R$)))
         Clr i%, j%
         GoTo TailCallElimination
        Else
         ' Print "'"; R$; "' ???"
         ' GoSub StringInsanity(C$, N%, i% - 1, j% - 1, R$)
         Dec i%
         Dec j%
         GoTo TailCallElimination
        EndIf
        Flush
      
       Else If Lookup%(i% - 1, j%) > Lookup%(i%, j% - 1) Then
        ' Should more compilers recognize tail recursion
        ' GoSub StringInsanity(C$, N%, i% - 1, j%, R$)
        Dec i%
        GoTo TailCallElimination
      
       Else If Lookup%(i%, j% - 1) > Lookup%(i% - 1, j%) Then
        ' and turn it into a GOTO
        ' GoSub StringInsanity(C$, N%, i%, j% - 1, R$)
        Dec j%
        GoTo TailCallElimination
      
       Else
        ' Finally, some non-tail recursion
        ' Print "Actual recursive call", i% - 1, j%
        ' Obvious SPAWN thread candidate is obvious
        l% = Len(R$)
        If ActualCallDepth% < 465 Then ! RECURSION DEPTH GUARD
         GoSub StringInsanity(i% - 1, j%, CallDepth%, ActualCallDepth%)
        EndIf
        If l% < Len(R$) Then
         Print " Trimming R$ back to "; l%; Space$(20); Chr$(13);
         Flush
         R$ = Left$(R$, l%)
        Else If l% > Len(R$) Then
         Stop
        EndIf
        ' ...and back to the tail recursion
        ' GoSub StringInsanity(C$, N%, i%, j% - 1, R$)
        Dec j%
        GoTo TailCallElimination
       EndIf
      Return
      
       
  • Markus Hoffmann

    Markus Hoffmann - 2019-06-19

    OK, I am also confused why I have to approve your post.... Well, SF has bugs.

     
  • Markus Hoffmann

    Markus Hoffmann - 2019-06-19

    FYI: The call stack size is 512. This will limit recusion depth. The value is arbitrary and comes from 20 years ago when RAM was expensive and limited. What stack size would your program need?

     
    • Yet Another Troll

      I have no idea. I tend to keep trying larger and larger problems to see what breaks. Could the stack be dynamically expanded by perhaps 25% and contracted by 50% as needed like half my arrays? You know, I haven't actually contracted an array yet in xbasic. I should try it.

       
      • Markus Hoffmann

        Markus Hoffmann - 2019-06-20

        Well, increasing the stack size from 512 to any other number would be a quick fix. Implementing a dynamic adaption is a lot of work. Thats why I ask.

         
        • Yet Another Troll

          I'd table it for now then. I can simulate the dynamic stack myself if need be, which I think I'll try. Thank you for looking into it though.

           
  • Markus Hoffmann

    Markus Hoffmann - 2019-06-20

    I have fixed it. Now the statck sizeis dynamically adjusted in steps of 512 up to a (hardcoded) maximum which is 8000 (recusion depth) at the moment, or better say in the next release of X11-Baisic.
    Also the app will not crash, when the limit is reached, but will print out an error message instead.
    The upper maximum is necessaary, because an endless recursion loop would oherwise eat all of the available system memory which in the end causes a crash, but before wold slow down and freeze the device.

    BTW: The stack does store return addresses and pointers to all local variables.

     

    Last edit: Markus Hoffmann 2019-06-20
    • Yet Another Troll

      Wow, thank you! Does moving arguments and local variables into globals help increase the recursion depth limit, or does that not matter? Should there be some way to optionally declare which global variables a function or procedure can access? I currently try to do so with comments, but something like Option Explicit and Global or Common enforced by the language would be awesome. I don't ask for all that much, do I? (Don't answer that!)

      If this keeps up, X11 BASIC might eventually mutate into X11 SPARK or something.

      https://en.m.wikipedia.org/wiki/SPARK_(programming_language)#Contract_examples

      https://en.m.wikipedia.org/wiki/SPARK_(programming_language)#Verification_conditions

      Any progress on what an X11 BASIC way to do UDTs might look like? And then expanding on that into modules and interfaces? Don't worry, no multiple or even single implementation inheritance. Extends is evil.

      I'm going to need a list of things to try stress testing in the next release. I'm actually going to try some bioinformatics algorithms which ought to do it.

      Thanks again!

       

Anonymous
Anonymous

Add attachments
Cancel





Want the latest updates on software, tech news, and AI?
Get latest updates about software, tech news, and AI from SourceForge directly in your inbox once a month.