Results 1 to 9 of 9

Thread: Recursion Procedures in Excel VBA. Recursion technique in coding

  1. #1
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,316
    Rep Power
    10
    Recursion Procedures in Excel VBA. Recursion technique in coding

    Procedures Calling others
    I think this can be very easy to understand. I think it has been made unnecessary hard to understand by a couple of things:
    _ (i) The usual initial explanation or definition : …. .." A procedure that calls itself is a recursive procedure…"


    https://www.youtube.com/channel/UCnxwq2aGJRbjOo_MO54oaHA

    https://www.youtube.com/channel/UCnxwq2aGJRbjOo_MO54oaHA
    https://eileenslounge.com/viewtopic.php?f=27&t=35521&p=276185#p276185
    https://eileenslounge.com/viewtopic.php?p=276185#p276185
    https://eileenslounge.com/viewtopic.php?p=276185#p276185
    https://eileenslounge.com/viewtopic.php?p=276673#p276673
    https://eileenslounge.com/viewtopic.php?p=276751#p276751
    https://eileenslounge.com/viewtopic.php?p=276754#p276754
    https://eileenslounge.com/viewtopic.php?f=30&t=35100&p=274367#p274367
    https://eileenslounge.com/viewtopic.php?p=274368#p274368
    https://eileenslounge.com/viewtopic.php?p=274370#p274370
    https://eileenslounge.com/viewtopic.php?p=274578#p274578
    https://eileenslounge.com/viewtopic.php?p=274577#p274577
    https://eileenslounge.com/viewtopic.php?p=274474#p274474
    https://eileenslounge.com/viewtopic.php?p=274579#p274579
    https://www.excelfox.com/forum/showthread.php/261-Scrolling-Marquee-text-on-Userform?p=864&viewfull=1#post864
    https://www.youtube.com/channel/UCnxwq2aGJRbjOo_MO54oaHA



    https://www.youtube.com/channel/UCnxwq2aGJRbjOo_MO54oaHA
    https://www.youtube.com/watch?v=TW3l7PkSPD4&lc=UgwAL_Jrv7yg7WWC8x14AaABAg
    https://www.youtube.com/watch?v=zHJPliWS9FQ&lc=Ugz39PGfytiMUCmTPTl4AaABAg.91d_Pbzklsp9zfGbIr8h gW
    https://www.youtube.com/watch?v=zHJPliWS9FQ&lc=UgwbcybM8fXnaIK-Y3B4AaABAg.97WIeYeaIeh9zfsJvc21iq
    https://www.youtube.com/watch?v=vSjTzhoJFdk&lc=UgzTC8V4jCzDHbmfCHF4AaABAg.9zaUSUoUUYs9zciSZa95 9d
    https://www.youtube.com/watch?v=vSjTzhoJFdk&lc=UgzTC8V4jCzDHbmfCHF4AaABAg.9zaUSUoUUYs9zckCo1tv PO
    https://www.youtube.com/watch?v=vSjTzhoJFdk&lc=UgwMsgdKKlhr2YPpxXl4AaABAg
    https://www.youtube.com/watch?v=XQAIYCT4f8Q&lc=UgwTUdEgR4bdt6crKXF4AaABAg.9xmkXGSciKJ9xonTti2s Ix
    https://www.youtube.com/watch?v=XQAIYCT4f8Q&lc=UgwWw16qBFX39JCRRm54AaABAg.9xnskBhPnmb9xoq3mGxu _b
    https://www.youtube.com/watch?v=XQAIYCT4f8Q&lc=UgzgWvzV-kvC4TJ8O414AaABAg.9xnFzCj8HRM9xon1p2ImxO
    https://www.youtube.com/watch?v=XQAIYCT4f8Q&lc=UgybZfNJd3l4FokX3cV4AaABAg.9xm_ufqOILb9xooIlv5P LY
    https://www.youtube.com/watch?v=XQAIYCT4f8Q&lc=UgzgWvzV-kvC4TJ8O414AaABAg.9xnFzCj8HRM9y38bzbSqaG
    https://www.youtube.com/watch?v=XQAIYCT4f8Q&lc=UgyWm8nL7syjhiHtpBF4AaABAg.9xmt8i0IsEr9y3FT9Y9F eM
    https://www.youtube.com/channel/UCnxwq2aGJRbjOo_MO54oaHA
    Last edited by DocAElstein; 04-11-2024 at 06:23 PM.

  2. #2
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,316
    Rep Power
    10
    Simple recursion example 1


    Basically all we need to do to get at the typical recursion situation in VBA coding is to add a single code line in the second procedure, Sub2 , something of this form
    _ Call Sub2( ____ , ____ )
    If we take a moment to think about the arguments we pass, ( ____ , ____ ) , then we can use effectively my suggested idea of the variable for keeping track

    Each copy of Sub2 is a unique procedure with its own independent variables
    As soon as a procedure Calls another, the Calling procedure pauses. It is effectively frozen. Or in suspension. It has not Ended. It is not dead. All its variables hold there values "frozen" in them.
    The Called procedure is a separate individual copy of instructions. We see things with our eyes as the same. But they are not. Also we do not progress through the previous coding instructions. This appears the case to us in the VB Editor when we step through the coding in debug F8 mode. But we actually progress through a separate copy of the procedure.
    So every time the Call Sub2( ____ , ____ ) is encountered a new separate procedure is called into life. All variables, such as CopyNo in each copy are independent from those with the same name in other copies.
    We gave Sub2 a value for the copy number of 1 from the initial Call in the main procedure , Sub1
    Last edited by DocAElstein; 03-19-2019 at 11:15 PM.

  3. #3
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,316
    Rep Power
    10

    Simple recursion example 2

    Simple recursion example 2

    In simple general terms a recursion routine can be an efficient way to do a sort of looping while looking for something. Sometimes the idea of "tunnelling down" or digging down" can describe the situation well. Sometimes a standard looping routine of the Do Loop While type form can replace a recursion routine more efficiently ( https://www.excelforum.com/tips-and-...omparison.html )
    The characteristic that possibly distinguishes recursion routines is the ability to seemingly intelligently go up and down: Compare it to the situation of digging down , whereby from time to time you come back up a bit, then dig down again in a slightly different direction. That is best illustrated by using a recursion routine for one of its most common practical uses, that of searching through Folders and sub Folders in a Directory. That will be done in the over next post.
    As a pre requisite to that we will demonstrate how a much simpler recursion routine may dig down until a condition is met, and then, thereafter it comes back up, level for level , i.e. copy for copy. This usage is very similar to the standard looping routine of the Do Loop While type form except that you have a last coming back up the levels, or coming back up the copies, which you would not have with a simple Do Loop While type form ( https://www.excelforum.com/developme...ml#post4221234 )

    We did not experience this coming back up in the last code because we Stoped. In general use of a recursion process, we do not have a simple way to end with like If ____ Then End Sub. Such a solution would be difficult to implement in a recursion process, as we would be ending the current copy with the End Sub.
    So generally a recursion process ends by somehow "coming back up levels" or ending each copy one after the other, either
    in sequence for a simple routine,
    or
    after going back and forth / up and down in a more complicated implementation of a recursion process.

    In most cases the coming back up is rarely experienced. We have specifically a message box at that point to show when a copy of the routine is ended. In practical uses what happens at this point is ether nothing, or for more complex implementation of recursion, we may be in a Loop at that point which would determine if we "go back down" again: Some controlled looping at this point is what triggers the possibility to "go back down" , pseudo…

    Sub Sub2( CpyNo , ______ )
    CurrentCopyNumber=CpyNo
    '
    '
    __Do
    ___Call Sub2(CurrentCopyNumber+1 , ______ )
    __Loop While__
    MsgBox Prompt:="You are Ending Sub2 , copy " & CurrentCopyNumber
    End Sub


    This will be discussed in the over next post.
    For now we look at the simple case

    One immediate way to stop us going further than say the second copy, would be to change our last coding pair from…_
    Code:
    Sub Sub1()
    Dim StrtCpyNo As Long ' To count copy number of code instructions being run
     Let StrtCpyNo = 1
     
     
     Call Sub2(CpyNo:=StrtCpyNo, Msg:="Initial Message")
     
     MsgBox Prompt:="Ending main procedure"
    End Sub
    ' Code above is Main calling procedure '____________________________________________________________________
    
    ' Code below is called procedure
    Sub Sub2(ByVal CpyNo As Long, ByVal Msg As String)
    Dim CopyNo As Long ' This is to indicate which copy of Sub2 is currently running
     Let CopyNo = CpyNo
     MsgBox Prompt:="You are Starting Sub2 , copy  " & CopyNo
     
    Call Sub2(CpyNo:=CopyNo + 1, Msg:="Message coming from Sub2, copy  " & CopyNo & "")
     MsgBox Prompt:="You are Ending Sub2 , copy  " & CopyNo
    End Sub
    _... to
    Code:
    Sub Sub1()
    Dim StrtCpyNo As Long ' To count copy number of code instructions being run
     Let StrtCpyNo = 1
     
     
     Call Sub2(CpyNo:=StrtCpyNo, Msg:="Initial Message")
     
     MsgBox Prompt:="Ending main procedure"
    End Sub
    ' Code above is Main calling procedure '_____________________________________________________________________________
    
    ' Code below is called procedure
    Sub Sub2(ByVal CpyNo As Long, ByVal Msg As String)
    Dim CopyNo As Long ' This is to indicate which copy of Sub2 is currently running
     Let CopyNo = CpyNo
     MsgBox Prompt:="You are Starting Sub2 , copy  " & CopyNo
    
         If CopyNo < 2 Then Call Sub2(CpyNo:=CopyNo + 1, Msg:="Message coming from Sub2, copy  " & CopyNo & "")
     MsgBox Prompt:="You are Ending Sub2 , copy  " & CopyNo
    End Sub
    You can safely run the above coding, ( by running Sub1 ) , in normal mode, as it will no longer try to go on for ever. But it is probably more demonstrative to use debug F8 mode


    Here is an attempt to show the last run as Excel VBA actually experienced it, - running Sub1 followed by two separate copies of Sub2, or rather
    Start Sub1
    _Start Sub2Copy1
    ___Start Sub2Copy2
    ___End Sub2Copy2
    _End Sub2Copy1
    End Sub1

    Code:
    Sub Sub1Sub2Sub2()
    Dim StrtCpyNo As Long ' To count copy number of code instructions being run
     Let StrtCpyNo = 1
    
    
    'Call Sub2(CpyNo:=StrtCpyNo, Msg:="Initial Message")
    ' Sub2 Copy 1
    Dim CpyNo As Long: Let CpyNo = StrtCpyNo: Dim Msg As String: Let Msg = "Initial Message"
    Dim CopyNo As Long ' This is to indicate which copy of Sub2 is currently running
     Let CopyNo = CpyNo
     MsgBox Prompt:="You are Starting Sub2 , copy  " & CopyNo
    
        If CopyNo < 2 Then
         'Call Sub2(CpyNo:=CopyNo+1, Msg:="Message coming from Sub2, copy  " & CopyNo & "")
         ' Sub2 Copy 2
        Dim CpyNo_ As Long: Let CpyNo_ = CopyNo + 1: Dim Msg_ As String: Let Msg_ = "Message coming from Sub2, copy  " & CopyNo & ""
        Dim CopyNo_ As Long ' This is to indicate which copy of Sub2 is currently running
         Let CopyNo_ = CpyNo_
         MsgBox Prompt:="You are Starting Sub2 , copy  " & CopyNo_
        End If
        If CopyNo_ < 2 Then
        Else
         MsgBox Prompt:="You are Ending Sub2 , copy  " & CopyNo_
        End If
        'End Sub2 ' End Copy 2 of Sub2
     MsgBox Prompt:="You are Ending Sub2 , copy  " & CopyNo
    'End Sub2 ' End Copy 1 of Sub2
    
     MsgBox Prompt:="Ending main procedure"
    End Sub
    Last edited by DocAElstein; 03-15-2019 at 02:09 AM.

  4. #4
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,316
    Rep Power
    10
    All Sub Folder and File List from VBA Recursion routine. Explanation and Method Comparisons.


    Introduction/ Overview.

    On the over next posts I am giving a very detailed description an including a lot of commented out lines allowing for the possibility to do other things, such as selectively opening the files.
    This might make it easy to get lost and loose the overview of what is going on.
    This post is intended to give a shorter overview , which might further serve to help in a revision at a later date, as an alternative to a full revision of all the following posts.

    The best start point would be to get to a shortened code version and a set of test files and folders.
    The files and folders can than be used as a basis for your own customised coding or for using in the full detailed code descriptions in the next posts

    _1 Download zipped Folder. This Folder and instructions on downloading and unzipping at these links**, and also zip Folder uploaded in this post, „EileensFldr.zip"
    https://www.excelforum.com/tips-and-...ml#post4811394
    http://www.excelfox.com/forum/showth...ll=1#post10422
    ( **Note: Some Folder may be missing
    Attached Images Attached Images
    Attached Files Attached Files
    Last edited by DocAElstein; 03-15-2019 at 02:08 AM.

  5. #5
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,316
    Rep Power
    10

    All Sub Folder and File List from VBA Recursion routine. Explanation review of simplified routines.

    All Sub Folder and File List from VBA Recursion routine. Explanation review of simplified routines.


    Main Initial starting routine
    Code:
    Private Sub EFDoStuffInFoldersInFolderRecursion()
                                                                                                                   Cells.Clear:                                                                                                  Range("C1:F1").Value = Array("Copy1", "Copy2", "Copy3", "Copy4")
    Dim myFolder
        With CreateObject("Scripting.FileSystemObject")
         Set myFolder = .GetFolder("C:\Users\Elston\EileensFldr\") ' ----- change to suit where you have the sample Folder, or Folder that you wish to use.
        End With
    
    Dim CopyNumber As Long:  CopyNumber = 1
    Range("A1").Value = myFolder.Name: 'Columns("A:C").AutoFit
    Call EFLoopThroughEachFolderAndItsFile(myFolder, 1, CopyNumber)
    Columns("A:H").AutoFit
    End Sub
    Called recursion routine
    Code:
    ' Called Recursion routine:
    Private Sub EFLoopThroughEachFolderAndItsFile(ByVal fldFldr As Object, ByRef rCnt As Long, ByVal CopyNumberFroNxtLvl As Long)
    Dim CopyNumber As Long: Let CopyNumber = CopyNumberFroNxtLvl:                                                  Debug.Print fldFldr.Name & "   " & CopyNumber
                                                                                                                                                                     'If CopyNumber = 0 Then CopyNumber = CopyNumberFroNxtLvl
    Dim myFldrs As Object
        For Each myFldrs In fldFldr.SubFolders '==========================================
        ''''''''Doing stuff for each Folder
        rCnt = rCnt + 2:                                                                                           Debug.Print myFldrs.Name & "   " & CopyNumber
        Range("A1").Cells(rCnt, 1).Value = myFldrs.Path: Range("A1").Cells(rCnt, CopyNumber).Offset(0, 2).Value = myFldrs.Name:
        ''''''''End doing stuff for each Folder
        Dim oFile As Object
            For Each oFile In myFldrs.Files ' --------------------------------
            ''''''''Doing Stuff for Each File
             rCnt = rCnt + 1
            Range("A1").Cells(rCnt, CopyNumber).Offset(0, 2).Value = oFile.Name
            ''''''''End Doing Sttuff for Each File
            Next '------------------------------------------------------------
        Call EFLoopThroughEachFolderAndItsFile(myFldrs, rCnt, CopyNumber + 1)
        Next '=============================================================================
     'MsgBox prompt:="Ending Copy  " & CopyNumber
    End Sub
    Recursion techniques are well suited to situations like these. In simple terms what does situations like these mean?: We want to do to the bits of something, and that something may have similar bits of something that we want to do things to… Like we want to do something to everyone's children. Which will then mean the children, the children's children, the children's children's children, the children's children's children's children, … etc.
    In our example we want to do something to the Sub Folders, the Sub Folders's Sub Folders, the Sub Folders's Sub Folders's Sub Folders, the Sub Folders's Sub Folders's Sub Folders's Sub Folders, … etc
    We have no idea how many Sub Folders or children are at each level.
    It would not be impossible to write a simple single routine to do all we want.
    But a recursion technique is very efficient, at least in the amount of code writing necessary.
    The strategy is to do something For Each of the Sub Folders in the initial given main Folder, the last thing being to Call the recursion routine again so as to do something For Each of the Sub Folders in the current Subfolder
    Each Call of the recursion routine we go down a level . As any Copy or a recursion routine Ends , that causes us to "come back up a level ". Typically this "come back up a level " is what goes unnoticed, as rarely we have anything there. ( For demo purposes we have sometimes shown a Message box there, 'MsgBox prompt:="Ending Copy " & CopyNumber)

    Summarised Coding Progression
    Basic strategy

    The recursion routine takes as the main argument, at the signature line, a Folder. This will be initially given as your main chosen Folder. In addition we take the variable for the copy number of the routine, initially given as 1 and subsequently given as the value of that variable in the current CopyNumber+1 when the current copy Calls the recursion routine
    In the simple example of printing out an explorer type view, the use of the CopyNumber variable allows us to determine the horizontal position across.
    One other variable is passed , rCnt. This is always incremented anytime we do anything. This is used to allow us to add things neatly positioned down the spreadsheet. This variable is always taken As Referred to. Effectively we can then consider that variable as being passed as a variable, so that variable is always added to, so it will always be the same variable in any copy of the recursion routine, unlike the CopyNumber variable which will be unique for each copy of the recursion routine
    So we have a continual going down the spreadsheet output as we do things, and we go back and forth as we go up and down "level" in a typical Folder explorer type view. ( We only go back and forth once with the sample data Folder, because it proved difficult to upload more complicated Folders. If you run the code selecting a more typical Folder, then this back and forth should be more easily visible )
    Walkthrough
    Calling routine , Sub EFDoStuffInFoldersInFolderRecursion()
    The chosen Folder is obtained, and the Name pasted out. (It is often the case that the actions that will be repeatedly done with the recursion routine will be done the first time in then main Calling routine)
    The Folder, As a Folder object is passed to the recursion routine along with an initial value of 1 for the "row" , (rCnt), and "column" , (CopyNumber) , coordinates, that is to say variables for spreadsheet progression vertically down and horizontally back and forth

    Sub EFLoopThroughEachFolderAndItsFile(ByVal fldFldr As Object, ByRef rCnt As Long, ByVal CopyNumberFroNxtLvl As Long)
    The unique variable for each Copy Number of the routine is given the passed number, initially 1.
    __Immediately after we have the main For Each loop which will do for every subfolder. '===============
    The rCnt is incremented by 2. One is required to ensure all outputs are pasted on a new line, and the extra is done at this point to give an extra space between Folders
    The Folder full path and name and name is then pasted out.
    ____A second Inner loop, ------- , then pastes out the File name for all files in the current Folder.
    After the last File name is pasted out , and just before the end of the main loop, the routine is Called again, this time "by itself". Important to remember always is that this does not mean that the current routine starts gain: It means the current routine pauses: It stops: "It freezes". Whilst it is "frozen" a new independent copy is started.

    Note: Every Folder is entered into the signature line of a starting copy of the recursion routine.
    But, if it has no Sub Folders in it then nothing is done with that Folder when it is passed as a Folder, and the routine Ends. If for example, the given main Folder has no Sub Folders in it, then the Called routine ends at the first copy, and nothing is done. ( if it was required to look for Files in the main Folder, then that would have to be done in the first routine)
    The recursion routine will keep "going down" subfolders until there are no more, so in effect every Sub Folder will eventually go through a
    Being passed to a new copy, without doing anything. When each of the Sub Folders in a Folder is gone through, then the main Loop ends causing the recursion routine to end.
    So the recursion routine can end either within the main loop or by bypassing that loop.
    The end by bypassing is an "empty" run which prevents further "tunnelling down".
    The end from within the Loop , that is to say at the Next'=== , point is when all Sub Folders in a Folder have been gone through.


    _.________________________________________________ ________


    The next posts do another more detailed analysis, and use a larger full 'commented coding. The 'commented lines also show possible other code lines for doing things other than just pasting File or Folder names out.
    Intentionally, some things will be repeated.
    Last edited by DocAElstein; 03-09-2019 at 01:12 AM.

  6. #6
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,316
    Rep Power
    10

    All Sub Folder and File List from VBA Recursion routine[

    All Sub Folder and File List from VBA Recursion routine.

    Recursion type code.
    The code discussed here makes use of the FileSystemObject Object, to get access to a computers File system, and uses recursion

    Recursion Process , a quick alternative simple explanation.
    Recursion is often described as ..”.. a routine that calls itself..”..
    Before I sussed out what that was about, it sounded like a very confusing and clever thing. I find it very simple now, thinking about it in a different way. The following may not be a truly technically correct description of what is going on, but it helps me to understand it, (and I haven’t met anyone yet that fully understands what the internal workings are doing anyway in a recursion process anyway)..
    So here you go:
    Two things I find are good to bear in mind initially
    _ (i) I would forget initially the ..”.. a routine that calls itself..”.. stuff. That can be misleading on my opinion. I think it is more helpful to say “…A routine that pauses, whilst another copy of the routine is done”….
    _ (ii) Be careful if you use the Debug mode ( F8 when looking at the code in the VB developer environment ) to step through a recursion routine. That can be misleading as well.
    ( The output that my code example produces, if looked at whilst stepping through the code in Debug mode, can help make it a bit clearer what is going on).
    The key to both understanding and not getting confused when in Debug mode is that typically you are actually stepping through many separate copies of a routine. What is actually going on does not show up very well in Debug mode as it appears when stepping through a code in Debug mode as though the same routine is done many times. That is not the case. By following in the Debug mode in the VB Editor it is easy to overlook that there will typically be many separate variables for each copy of a the routine which ,although they have the same name, are independent. Think of it like this: Each time the routine is said to “call itself”, the following happens: It freezes. A copy is made and laid directly over the frozen one. That new copy is started. When the new copy is finished, the copy is removed. The original then unfreezes, and continues from the point at which it froze.

    Any code is just a master set of instructions and a run follows copy of that instructions
    Think of a code as just a written set of instructions and when a code “runs” a copy of the instructions are made and followed in order to do something. Usually the copy is trashed when the code stops, ( Ends ) , but there may sometimes be something left over, or changed or made at the End
    Broadly speaking we can think about 3 main sort of code situations, and the third one is recursion
    _1) A simple single code, a Sub( ) is a Master copy of a set of instructions. You make a copy of the instructions, follow them and do it. Then stop / End. To a first approximation, usually, but not always, everything is over with at the End and gone. Usually the ( ) is empty , - the ( ) is meaningless in such a code case.
    _2) Codes where an initial simple code ( calling ) a Function (oftenSomethingHere) or another Sub( oftenSomethingHere) . In a simple example of this situation, it is a code , often referred to a the main (Sub ( ) ) or main routine, that “Calls” a Function( oftenSomethingHere)or another Sub( oftenSomethingHere) . In simple terms this second routine is just another master copy of a set of instructions. The main difference is that as there is “( oftenSomethingHere)” that means that something is “taken into it” from the Calling main routine.
    So just to be clear: We have 2 routines: We have a main routine and a second Called routine. The second routine cannot usually be run on its own, - it needs another routine to Call it, as it usually is given something. ( VBA syntax does not usually let you set off such a routine on its own with “(SomethingInHere)”. **You have to give the “SomethingInHere” at the “Call” code line which “calls” or “sets off” a copy of the second routine instructions.
    So typically in this second code situation you initially start doing 1) , a simple Sub ( ) , as before, but before you are finished, you pause what you are doing ( “freeze” the situation, not stop / End , so you may still have stuff temporarily stored or hanging around somewhere ). This pausing happens at the “Call” line. You then make a copy of the second routine instructions. Usually , but not always, you may take something with you from the Sub, ( ** in the “(SomethingInHere)” bit ) , then Follow that next set of ( second routine ) instructions. Usually that will involve doing something with what you took with you. You do and finish / End that. Often , but not always, you may take something back which you did or made in the second routine, and then use that when you then “unfreeze” and carry on the initial (Sub) set of instructions from the point where you left them, ( at the “Call” line ). Then stop / End. To a first approximation, usually, but not always, everything is over with at the End and everything is gone.
    _3) Recursion situation: This is not really much different to 2). In fact it is almost the same. The situation is that you are in the second set of instructions ( second routine ). But before you are finished , you once again pause. You make a second copy of the second routine instruction. Once again, you freeze the situation of the fist copy of the second routine instruction, ( and remember, you have already previously frozen / paused the initial main Sub instructions. So a couple of code instruction copies are hanging around, frozen, on hold, and waiting to restart from where they paused).
    So you now do again what you just started but you do it this second time completely first before you go back and finished doing it the first time… Sounds a bit pointless initially. But the point is that usually what you take with you and consequently what you bring back is different. So you do different things using the same set of instructions, and/ or what you end up will be different each time as it depends on what you take with you when you go through each copy of the ( second routine ) instructions . You can keep pausing the current copy of the second routine instructions and starting again with a new copy set of the second routine instructions, at least until something gets overfilled.
    Some process/place in the computer has to keep a record / track of all the copies of the second routine instructions currently not finished along with any “frozen” values of variables locally held in those copies , which would have been also frozen at the values had at the pause, and which will be needed for when each copy restarts. That process/place is usually referred to as a stack. So when that gets overfilled you get the famous “Stack overflow” error. In the practice you would usually have some condition checked which needs to be satisfied before you start following a new copy of the second routine instructions. In the following example, that condition to be satisfied ( indirectly ) will be if there are Sub Folders in a current Folder. If there is not then the main outer For Next loop wont start: Towards the end of that For Next loop is a recursion call designed to see if the current folder which just had its files gone through, has sub folders in it

    Recursion example

    Purpose of the code:
    The aim is to produce a Tree root sort of a sketch in a worksheet to show all the Folders, Sub Folders and files starting within an initial Folder. That is what I need, for example , to get finally a list of Titles to help me search for a particular subject area, to see if I have a code already to solve a particular problem . ( I don’t really need a worksheet full of the titles, but it looks nice and does demo very well the recursion process .. in particular the “up and down” nature of the process, which is very difficult to explain in words. It is also handy to have a worksheet saved showing pictorially all the files and where they are. It ends up looking like a classic Explorer Window)

    General Code Form and strategy.
    The code is a shortened version of this one Recursion version:
    https://www.excelforum.com/excel-pro...ml#post4348630
    various code variations in VBA and full code descriptions https://www.excelforum.com/developme...directory.html
    .
    To simplify for demo purposes, assume a main Folder is known and so is hard coded in this example.
    ( I supply the demo Folder with my code example. You will need to download it and place it, unzipped , in the same Folder in which the Excel File is in which you place and run my code )

    Following on from the idea explained in the last post.. it follows that the main Sub will pass over to a second routine ( or put another way the second routine will take (here) ) a single Folder which may have Files and / or Sub Folders. Those Sub Folders could themselves have Files and/ or Sub Folders. Those Sub Folders could themselves have Files and/ or Sub Folders. Those Sub Folders could themselves have Files and/ or Sub Folders. Those Sub Folders could themselves have Files and/ or Sub Folders. …etc.
    So the second routine would usually “take in” just a Folder. It then does For all the Sub Folders in it the following:
    _ Increments the row count by 1+1, then writes the folder name. ( 1 is for a new line for the next Folder name entry, and the extra 1 is so that an extra empty line is made for clarity before each Folder name. )
    and
    _ writes the name of any contained excel File File names before checking for Sub Folders, and if so it would, For Each of these Sub Folders´, “take” each folder in a run of a new copy of the second routine
    Generally , in most seen examples of this code type, we do not need to take anything “out” at the End, as more usually the code is intended just to “do something” to Folders and/ or Files, or look in them for something.
    However, in the case of this particular code example, some variables are passed as they keep track of where we are vertically and horizontally in the root structure which will be. The vertical is simply incremented by one every time the second routine is used. The Horizontal is adjusted appropriately to keep track as we “go up and down” ( shown pictorially as right and left )

    In the many published examples of such codes, the main code will always be a simple Sub( )
    The second routine would normally have a form something of this form: Function(FolderToLookIn) or Sub(FolderToLookIn)
    The difference in these versions of the second routine is usually said to be that you are able to return something with the Function and not the Sub, as it would often be seen in this form,
    Variable = Function(OneOrMoreThingsTakenInhere) , whereas the Sub would just be Called, like
    Call _ TheSubName _ (FolderToLookIn)
    That is Bollox actually!!!, but would make no difference anyway in the usual form as you do not want anything back, so just Calling either ( VBA allows you also to do that to the Function also ) in these forms sets them off, (which is all that would normally be done):
    Call _ TheSubName _ (FolderToLookIn)
    or
    Call _ TheFunctionName _ (FolderToLookIn)

    In my example I need to use the Sub(SomeThingsInHere) because in addition to “taking in” the FolderToLookIn , I want to also:
    Give a cell as Top Left of where I want my output to start
    and
    pass a variable to be used By Referring to it ( giving it ) a count of the number of times a copy of the second routine instructions is run through. This will be used to increment the row number that each Folder name or Excel File name is written in. ( This By Ref method effectively “returns” a value !!!)
    and
    pass a Value to it ( giving it ) a number for the column number that is used for output. This effectively gives an indication of the Copy Number of the second routine copy being used. This is also an indication of how far “down” or “to the right” we are in the Folder system

    The nice thing about the final output is that as you work down you can see what is going on, as different copies of the second routine start and pause or stop.
    The next post works through the code in detail.
    The over next post gives an example, using a supplied Main Folder which contains Folders and Files. I give a screenshot of what you should be able to reproduce , and on that screenshot have added some notes in orangeto show what is actually going on ( https://imgur.com/FjjUMYz )
    Attached Files Attached Files
    Last edited by DocAElstein; 03-09-2019 at 09:57 PM.

  7. #7
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,316
    Rep Power
    10

    Recursion Codes process Description example

    Recursion Codes process Description example


    Here are the two full codes with full 'Comments and the descriptions below follow that code.
    _1) Calling Sub( ) routine. https://pastebin.com/x25v3gGz
    http://www.excelfox.com/forum/showth...0419#post10419
    _2) Second routine ( routine used in recursion process, and called initially, ( once ) , from _1) ). This will usually “Call” itself many times, after it is set off by _1 )
    Sub VBALoopThroughEachFolderAndItsFile(Folder, , , __ : https://pastebin.com/x25v3gGz
    http://www.excelfox.com/forum/showth...0419#post10419

    ( ( This is a shorter simplified both codes version : http://www.excelfox.com/forum/showthread.php/2311-Recursion-Procedures-in-Excel-VBA-Recursion-technique-in-coding?p=11026&viewfull=1#post11026 ) )

    ( Codes are also in Worksheet "March2019" Code module of uploaded file: ( ‘== ' March For excelfox Blog. ) )


    Full codes description.
    This description is of the two codes. The codes should be copied to the same code module. The codes are split into a few sections for compatibility with some earlier alternative code versions, ( some of which do not use the recursion technique ) ( https://www.excelforum.com/developme...ml#post4440515 https://www.excelforum.com/developme...ml#post4440512 ),

    Calling Sub VBADoStuffInFoldersInFolderRecursion ( _ )
    Rem 1A) Worksheet info.
    Rem 2A) Initial ( Start ) Folder
    Rem 3A) System Library Object
    Rem 4A) 'Some variables for Position of Things


    Sub VBALoopThroughEachFolderAndItsFile(Folder, , , __
    Rem 5A) Doing while Sub ( Under ) Folders are still found
    __'5Ab) Doing stuff for current Folder
    __'5Ac) Doing stuff for current file
    ( Rem 6) Handling Errors )


    Rem 1A) Worksheet info.
    Often such codes make no particular reference to a worksheet, and the output to a worksheet is either not required or is simply by default to the active worksheet starting from Top left of first cell A1. In this code version the worksheet can be hard coded here, as can the Top Left cell from where the output should start.

    Rem 2A) Initial ( Start ) Folder
    For this example the example main Folder to be searched for is named " EileensFldr". It can be downloaded from the last post : Eileens Fldr.zip
    By me in Windows that downloads as a .zip File. To use the File, I store it anywhere, then I make a Folder with the name EileensFldr in the same Folder which contains the File in which I place the macros being described here.
    EileensFldr Make Empty Folder.JPG https://imgur.com/6kolxi4
    Then I copy all the files in Folder EileensFldr.zip
    EileensFldr Contents Copy.JPG https://imgur.com/hgqg64w
    And paste into the new Folder which is in the same Folder which contains the File in which I place the macros being described here.
    EileensFldr Contents Paste.JPG https://imgur.com/4qK00eI
    You may have a different method for “unzipping” a “Zipped file”, but the important thing is that you end up with both the File containing the macros and the example File in the same Main Folder.
    Example Folder and Macro File in same Folder.JPG https://imgur.com/LWSUssc
    The above requirement is only because of this code line _..
    Let strWB = ThisWorkbook.Path & "" & "EileensFldr"
    _.. That code line tells the code that the Initial Folder is in the same Folder as the file in which the code is.
    Often such codes are written such that they ask you to select a Folder to be searched through. Here it is simply hardcoded to simplify the demo code.

    Rem 3A) System Library Object, FileSystemObject Object
    An external Library is made available which allows access to a computer File system.

    Rem 4A) 'Some variables for Position of Things
    The variables that are used to keep track of “where” we are in the Tree root structure are initialised.
    We use a couple of variables:
    _ We pass a variable, rCnt, to the second routine copies which are run, to be used By Referring to it ( giving it ) a count of the number of times a copy of the second routine instructions is run through. This will be used to increment the row number that each Folder name or Excel File name is written in. It is increased by 1 just before a File Name entry is made. Just before a Folder name entry is made, it is increased by 2. The extra 1 is just done for neatness, to give an extra empty Line before each Folder. The name for any contained Files will come directly under the Folder name.
    and
    _ We also pass a Value to the second routine copies which are run, which effectively gives an indication of the Copy Number of the second routine copy being used. The logic for this needs some very careful explanation. In the initial main routine Sub( ) this is passed a variable, CopyNumber1 , which we set in this code section to = 1 . That logic is fairly easy to understand: The copy set off by the Sub( ) is the first copy
    Which variable value is passed when the second routine calls itself, and how that value is further used is very subtle, and once again, I think it is important to bear in mind that we typically will have independent copies of the second routine either running …. see –- Rem 5A)
    ( Finally in code section 4A) the main Folder Path and Name is written to the Worksheet, and then the second routine is set off for the fist time, that is to say, the first copy of that second routine is made and set off. )

    Sub VBALoopThroughEachFolderAndItsFile(Folder, , , __
    -- Rem 5A) Doing while Sub ( Under ) Folders are still found
    At the outset of the second routine, the variable keeping track of the second routine copy number is dealt with. That logic needs careful explanation. The problem is how do I know which “Copy” Routine I am in. Every successive Copy will relate to a run in a .. “the next “down” or “to the right” Folder “level”. I cannot simply add a progressively increasing count, ( as I can and do for the row for next output, rCnt ) , as in the recursion Code I will be going “back and forth” depending on if and where Sub folders are. I need a way to know at which “level” of Sub Folders I am in when in at any time. That variable is used to determine the column in which to write a Folder or File name. ( Each column in the final output represents a different Folder level )
    I achieve the necessary as follows. It demonstrates well how recursion works. Here we go:
    Inside the Routine towards the start is a variable,
    CopyNumber.
    This will be a unique variable for each “Copy” Routine. Ideally I would like to rename this at each level down/ to the right something like CopyNumber1, CopyNumber2, CopyNumber3 … etc. But, I cannot do that as VBA only allows me to type in the code window a single Master copy of the code. Effectively as the recursion process is going on, and we have a copy or the second routine, say the forth copy running, then VBA has stored, amongst other things, the following variables (in the “stack”, as it is called )….
    Routine copy 4 : CopyNumber
    Routine copy 3 : CopyNumber
    Routine copy 2 : CopyNumber
    Routine copy 1 : CopyNumber
    That is to say we have a unique CopyNumber variable which is paused or in use. (Confusingly to us, they all have the same name. But VBA holds them in a different “stack place”, so somehow can keep track and use the appropriate one ). Only one ( or none ) will be in use at any time. The one in use at any time needs to hold an integer number to indicate the copy number or “how far down” or “to the right” we are.
    Here is a working logic which is used:
    Every time the Routine is called a number is taken in at the value inside a variable in the signature line
    CopyNumberFroNxtLvl
    For the very first call , ( by the main first routine ), as mentioned, it is set to 1 in a variable whose value is taken in at its value, as a value, in the Signature line.
    Towards the start of the second routine, the local variable, is given this passed value of 1
    Subsequently, however, when the second routine “calls” itself, the value passed to CopyNumberFroNxtLvl will be given the
    = ( value of the local variable, CopyNumber , from the routine copy doing the call ) +1
    Hence as further copies are started, the integer held within the local variable, CopyNumber, will be one higher then the previous copy. This value is then either in use, or in the appropriate place in the stack, to be used when any paused copy resumes.
    This somewhat complicated process is necessary so that paused routine copies have available to use the correct integer when they resume. This is possibly demonstrated better pictorially by looking at the output produced in the worksheet, along with the extra comments in orange https://imgur.com/FjjUMYz

    The rest of section Rem5 follows a fairly standard format for this type of recursion code.
    '5Ab) The initial condition here is also the means by which “stack overflow” is avoided: The main and major part of the second ( recursion ) routine is done only For Each Sub Folder found within the current Folder taken into the routine at the signature line. ( Note here, that should there be any Files in the main initial Folder, then this routine will not catch and list them, as the routine goes straight into looking in any Sub Forums found ).
    Assuming one or more Sub Folders are found, then the code is at the classic section for … „Doing stuff for each Folder”,….. In this case the row for an output, rCnt, is increases by 2, ( 1 for a new line, and 1 to make an empty line to help make the final output a bit clearer ) , and then Folder name is pasted to a cell, whose co ordinates are given by rCnt for row, and CopyNumber for column. ( For Folders an initial column is also used for the complete full Path and Name )
    '5Ac) Doing stuff for current file. A second For Each Loop, this time for any Files in the current Folder, is nested in the previous '5Ab) For Each loop. For every File, the row for an output, rCnt, is increases by 1 and the File Name is written to the worksheet. - The cell co ordinate given by rCnt and the same value of CopyNumber used for the cell co ordinate used for the File Name of the file in which the file or files are. That way the File names are neatly written directly under their Folder name.

    Once all File names are outputted, the point is reached where the routine “calls itself”. So at that point a new copy of the second routine is made, and the Folder given is the current one , ( the one which had just had its Name and the Name of any Files within it outputted.) The variable passed to indicate the level of the folder is then given the value of
    = ( the current CopyNumber )+ 1
    Hence any further outputs made by the new copy just started will be written outputted 1 column to the right of the previous.



    _..._____________________________
    The next post shows the output that should be achieved with the given codes and sample Folder






    Ref
    http://www.excelfox.com/forum/showth...0144#post10144
    https://www.excelforum.com/excel-pro...ml#post4348630
    http://excelpoweruser.blogspot.de/20...-files-in.html
    http://www.excelforum.com/excel-prog...ubfolders.html
    http://www.excelforum.com/tips-and-t...ml#post4221356
    http://www.excelforum.com/excel-prog...ubfolders.html
    http://excelmatters.com/2013/09/23/v...-late-binding/
    http://www.mrexcel.com/forum/general...plication.html
    http://www.eileenslounge.com/viewtopic.php?f=27&t=22499
    http://www.excelfox.com/forum/showth...0419#post10419
    Attached Files Attached Files
    Last edited by DocAElstein; 03-09-2019 at 10:38 PM.

  8. #8
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,316
    Rep Power
    10
    Screenshot: EileensFolderExplainedOutput.JPG https://imgur.com/FjjUMYz
    Attachment 1945

    Using Excel 2007 32 bit
    Main Code Second routine copy 1 Second routine copy 2 Second routine copy 3
    CopyNumber1=1 CopyNumber2=2 CopyNumber3=3 Main first routine, ( Sub( ) ) , starts
    G:\Excel0202015Jan2016\ExcelForum\wbSheetMakerClsd WbADOMsQueery\EileensFldr EileensFldr ( Folder Details of Main Folder are written by Main routine ( Sub( ) ) )
    Main first routine, ( Sub( ) ) , pauses
    G:\Excel0202015Jan2016\ExcelForum\wbSheetMakerClsd WbADOMsQueery\EileensFldr\Fldr1_1 Fldr1_1 First copy of second routine starts
    File1_1a.xlsx
    File1_1b.xlsx
    First copy of second routine pauses
    G:\Excel0202015Jan2016\ExcelForum\wbSheetMakerClsd WbADOMsQueery\EileensFldr\Fldr1_1\Fldr1_1_1 Fldr1_1_1 Second copy of second routine starts
    Second copy of second routine Ends
    G:\Excel0202015Jan2016\ExcelForum\wbSheetMakerClsd WbADOMsQueery\EileensFldr\Fldr1_2 Fldr1_2 First copy of second routine resumes
    File1_2a.xlsx
    File1_2b.xlsx
    File1_2c.xlsx
    First copy of second routine pauses
    G:\Excel0202015Jan2016\ExcelForum\wbSheetMakerClsd WbADOMsQueery\EileensFldr\Fldr1_2\Fldr1_2_1 Fldr1_2_1 Another (Second) copy of second routine starts
    File1_2_1a.xlsx
    File1_2_1b.xlsx
    Second copy of second routine pauses
    G:\Excel0202015Jan2016\ExcelForum\wbSheetMakerClsd WbADOMsQueery\EileensFldr\Fldr1_2\Fldr1_2_1\Fldr1_ 2_1_1 Fldr1_2_1_1 Third copy of second routine starts
    File1_2_1_1a.xlsx
    G:\Excel0202015Jan2016\ExcelForum\wbSheetMakerClsd WbADOMsQueery\EileensFldr\Fldr1_2\Fldr1_2_1\Fldr1_ 2_1_2 Fldr1_2_1_2
    File1_2_1_2a.xlsx
    File1_2_1_2b.xlsx
    Third copy of second routine resumes and Ends
    Second copy of second routine resumes and Ends
    First copy of second routine resumes and Ends
    Main first routine, ( Sub( ) ) , resumes and Ends.
    Yellow indicates code copy currently running: The main code is copied and run once. For the example Folder shown,
    the second routine is copied and run once for the first Folder level, twice for the second level, and once for the third level.
    Worksheet: March2019

  9. #9
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,316
    Rep Power
    10
    This may be a bit clearer...


    Using Excel 2007 32 bit
    Main Code Second routine copy 1 Second routine copy 2 Second routine copy 3
    CopyNumber1=1 CopyNumber2=2 CopyNumber3=3 Main first routine, ( Sub( ) ) , starts
    G:\ExcelForum\EileensFldr EileensFldr ( Folder Details of Main Folder are written by Main routine ( Sub( ) ) )
    Main first routine, ( Sub( ) ) , pauses
    G:\ExcelForum\EileensFldr\Fldr1_1 Fldr1_1 First copy of second routine starts
    File1_1a.xlsx
    File1_1b.xlsx
    First copy of second routine pauses
    G:\ExcelForum\EileensFldr\Fldr1_1\Fldr1_1_1 Fldr1_1_1 Second copy of second routine starts
    Second copy of second routine Ends
    G:\ExcelForum\EileensFldr\Fldr1_2 Fldr1_2 First copy of second routine resumes
    File1_2a.xlsx
    File1_2b.xlsx
    File1_2c.xlsx
    First copy of second routine pauses
    G:\ExcelForum\EileensFldr\Fldr1_2\Fldr1_2_1 Fldr1_2_1 Another (Second) copy of second routine starts
    File1_2_1a.xlsx
    File1_2_1b.xlsx
    Second copy of second routine pauses
    G:\ExcelForum\EileensFldr\Fldr1_2\Fldr1_2_1\Fldr1_ 2_1_1 Fldr1_2_1_1 Third copy of second routine starts
    File1_2_1_1a.xlsx
    G:\ExcelForum\EileensFldr\Fldr1_2\Fldr1_2_1\Fldr1_ 2_1_2 Fldr1_2_1_2
    File1_2_1_2a.xlsx
    File1_2_1_2b.xlsx
    Third copy of second routine resumes and Ends
    Second copy of second routine resumes and Ends
    First copy of second routine resumes and Ends
    Main first routine, ( Sub( ) ) , resumes and Ends.



    Yellow indicates code copy currently running: The main code is copied and run once. For the example Folder shown,
    the second routine is copied and run once for the first Folder level, twice for the second level, and once for the third level.
    Last edited by DocAElstein; 03-19-2019 at 11:16 PM.
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

Similar Threads

  1. Replies: 2
    Last Post: 04-10-2015, 04:18 PM
  2. add an addition cell colour to coding
    By peter renton in forum Excel Help
    Replies: 2
    Last Post: 11-20-2014, 05:16 PM

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •