Page 4 of 6 FirstFirst ... 23456 LastLast
Results 31 to 40 of 52

Thread: Resume On Error GoTo 0 -1 GoTo Error Handling Statements Runtime VBA Err Handling ORNeRe GoRoT N0Nula 1

  1. #31
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,315
    Rep Power
    10
    Links that might work to get to Page 3 ( using 3 above right from post #31, or the 3 below right in the page list, does not work due to number at end of title ) :
    https://excelfox.com/forum/showthrea...9877#post19877 Page 3
    https://excelfox.com/forum/showthrea...0Nula-1*/page3 Page 3
    https://excelfox.com/forum/showthrea...ll=1#post10565 - perhaps close to bottom of page 3
    Last edited by DocAElstein; 03-24-2023 at 06:17 PM.

  2. #32
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,315
    Rep Power
    10

    Miscellaneous points that might have been missed, or not explicitly stated, or just added.


    A few Miscellaneous points that might have been missed, or not explicitly stated, or just added much later, to clarify, or revise things…..
    around March 2023
    ..


    On Error GoTo 0 “works” in both normal and aroused states .. but
    An error handler can be replaced in normal state without using On Error GoTo 0

    _ If we have an error handler enabled but not active, then we know that On Error GoTo 0 will take us back to the default VBA error handling situation. That code line removes or disables or unplugs the error handler. So just to be clear: On Error GoTo 0 will also remove the error handler from VBA’s memory of it even if the error handler is active and has put us in the aroused exception state/ given us an erecting. So if the On Error GoTo 0 is used in the aroused exception state, then after a resume or On Error GoTo -1 , we will go back to the default VBA error handling situation
    What may not be obvious or intuitive is that in the inactive state, we can effectively replace the error handler with a new one by passing either a On Error Resume Next or On Error Resume LabelOrLineNumber error handler statement code line

    Ending a code effectively does On Error GoTo -1 and On Error GoTo 0
    As far as errors are concerned, then , at least theoretically , the ending of a routine removes the exception and returns error handling to the default VBA error handler. ( There are occasionally reports that after occurrence of errors, a full system restart may be advisable due to some bugs resulting in “something being left over” after an exception has been raised and theoretically cleared )

    On Error GoTo -1 followed by a resume:
    Probably not of much practical use: just an observation. As noted, the resumes effectively do a On Error GoTo -1 . There would not be a lot of use in including that in the error handling code section if you were then going to use any of the resumes.
    But if you did then, curiously the resumes no longer take you to where you might expect: they all take you to the On Error GoTo -1.
    In the demo code below, without the On Error GoTo -1 , any of the resumes will allow for another try of the formula, with a modified value of the variable Destrominator, which should work due to us adding a value which would mean that if it had been zero, then the addition of 1 will prevent it from being zero for the next try. However the On Error GoTo -1 causes any resume to go to the On Error GoTo -1 code line
    Code:
    Sub OnErrorGoTo_1resume()
     On Error GoTo GetMilk ' Don't come back .. you're not welcome here  ..  stay away  ..  https://imgur.com/MKMjW0b  ..  FOB
    '
    Dim Destrominator As Long: Let Destrominator = 0
    Dim RslTwat As Long
    '
    Try: Let RslTwat = 10 / Destrominator  '  Will error due divide by zero, unless Destrominator is changed in error to a value other than zero
     Let RslTwat = 10 / Destrominator ' for an attempt after  Resume Next
    ' you never come here
    Exit Sub
    GetMilk:
    Dim cnt
     On Error GoTo -1 ' this causes any of the resumes to bring you here
     Let cnt = cnt + 1 ' Count how many times I come here
     MsgBox prompt:="This is the " & cnt & " time you were here" ' You come here three times
        If cnt = 3 Then Exit Sub ' without this you loop infinitely
     Let Destrominator = Destrominator + 1
     Resume Try '  or  Resume Next  or  Resume    In this code these all have the same effect
    End Sub














    resumes “work” in the procedure that they are in.
    If an error occurs in a called routine or function, then the call line is treated as a single line: the resuming will take place just before or just after the call line or at the specified line in the main code. To allow error handling within the function at the error occurrence, an error handler must be placed within function.
    The first code below to demo how resume works in the case of a called routine , only has an error handler in the main code, but the error occurs in a called routine.
    Resume Next is used at the end of the error handling code section in the main routine , which means we resume just after the called routine, and never get to the end of the called routine.
    Code:
    Sub ErrorInFunctionWithNoFunctionErrorHandler() ' Main routine
     On Error GoTo Bed
    '
    Dim Rng As Range ' Preparing the variable for the range type object. I have not assigned a specific range to it yet.
     Let Rng.Value = "AnyFink" ' Errors, as I have no range assigned to the variable Rng and so cannot give a non existant range a .Value
    '
     Call EmBed(0)
    ' You come here after Resume Next
    Exit Sub
    Bed:
     MsgBox prompt:="An error occured in the main routine or the Called routine" & vbCrLf & "If the error was in the called routine then I will resume just after the Call line" & vbCrLf & " if using Resume Next"
     Resume Next
    End Sub
    Sub EmBed(ByVal Destructinator As Long) ' Called routine
    '
    Dim RslTwat As Double
     Let RslTwat = 10 / Destructinator
    ' You never come here
     MsgBox prompt:="You will never see this", Title:="Purgatory"
    End Sub





























    The code below includes an error handler in the called routine.
    Note also that in this code I have included a second error in the main code after the Call of the called routine. Once the second routine is ended, the same error handler as that which handled the first error in the main routine, once again kicks in to handle the third overall error which is the second error in the main routine. I assume VBA somehow stores “on hold” , as they say “in the stack” , everything about the main routine, including any registered user error handler. It does this as the main routine is “put on hold” / pauses / “freezes”, at the time that the function starts. Then when the function ends ( in the first effectively code after the error and the second code at the normal function End ) the main code restarts “unfreezes” as it was left.

    Code:
    Sub GoInBed() ' main routine
    Dim cnt As Long ' to count how many times I was  at the error handler in this main routine
     On Error GoTo Bed
    '
    Dim Rng As Range ' Preparing the variable for the range type object. I have not assigned a specific range to it yet.
     Let Rng.Value = "AnyFink" ' Errors, as I have no range assigned to the variable Rng and so cannot give a non existant range a .Value
    '
     Call InBed(0)
    ' You come here after the error in this main code.
     Let Rng.Value = "AnyFink" ' Errors, as I have no range assigned to the variable Rng and so cannot give a non existant range a .Value
    '
     MsgBox prompt:="You are leaving the main code now" & vbCrLf & "You used the error handler in the main code " & cnt & " times."
    Exit Sub
    Bed:
     Let cnt = cnt + 1 ' Increase the count of how many times you were here
     MsgBox prompt:="An error occured in the main routine of" & vbCrLf & Err.Description & vbCrLf & "The count of how many times you were here is " & cnt
     Resume Next
    End Sub
    Sub InBed(ByVal Destructinator As Long) ' Called routine
    On Error GoTo EmBed
    Dim RslTwat As Double
     Let RslTwat = 10 / Destructinator
    ' come here after error in this called routine
    Exit Sub
    EmBed:
     MsgBox prompt:="You have an error in the Called routine of " & vbCrLf & Err.Description
     Resume Next
    End Sub
    Last edited by DocAElstein; 03-25-2023 at 12:48 PM.

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

    Further discussion points

    :CC<C<YCN
    Last edited by DocAElstein; 03-24-2023 at 10:20 PM.

  4. #34
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,315
    Rep Power
    10

    Further discussion points Ideas from March 2023

    Some extra notes in support of this main forum Post
    https://www.excelforum.com/excel-pro...ml#post5803728
    http://www.eileenslounge.com/viewtopic.php?f=30&t=39437





    The __Resumes versus the error handler On Error Resume Next
    __On Error GoTo -1

    Some re thoughts around March 2023
    Slightly compacter way to do simple error handling in VBA


    The threads referenced above got me into one of my annual re thinks about these things.


    __Resumes versus the error handler On Error Resume Next
    I already made the point in this Thread that we have two different things,
    _ the 3 Resumes ( Resume and Resume Next and Resume LabelOrLineNumber )
    , and the perhaps confusingly* named
    _ On Error Resume Next
    *The second thing is perhaps confusingly named, since the similarities with one of the Resumes are not as much as one might think.

    In previous posts we did detailed pseudo codes. Here we will just summarise them, ( and add a link to the full pseudo codings ).
    What is a new idea specific to what I am saying here is like… how about this, just a suggestion: The first thing that happens when an error occurs is not an immediate Exception State. Instead, the coding pauses. The Err object gets filled. Possibly the Erl() , is a more fundamental original Visual Basic thing, and is first given the information about the line that was last executed, the erroring code line. But the important new suggestion here is that the macro is paused and information about the error is registered. This will be _(i) in the pseudo codings below,
    Then a decision is made

    **Before considering first the Resumes ( Resume and Resume Next and Resume LabelOrLineNumber ) , we must remind ourselves that they only work in the exception State. They only come into play, that is to say, have a possible use, after a On Error GoTo LabelOrLineNumber.

    _ The 3 Resumes
    Resume ( https://excelfox.com/forum/showthrea...ll=1#post10556 )
    _(i) An error occurs. (Assume we have a On Error GoTo LabelOrLineNumber ). The macro is paused. Information relating to the error is registered/ registers get filled in. The macro continues at the place specified by LabelOrLineNumber. Code lines are carried out mostly normally , but we are in the Exception State
    The decision on what to do for if a Resume is encountered will be:
    _(ii) On Error GoTo -1 ' ( This will clear Err and Erl() and takes us out of the exception State, and so back to normal code running.)
    _(iii) we continue to run the coding at the same line that caused the error

    Resume Next ( https://excelfox.com/forum/showthrea...ll=1#post10557 )
    _(i) An error occurs. (Assume we have a On Error GoTo LabelOrLineNumber ). The macro is paused. Information relating to the error is registered/ registers get filled in. The macro continues at the place specified by LabelOrLineNumber. Code lines are carried out mostly normally , but we are in the Exception State
    The decision on what to do for if a Resume is encountered will be:
    _(ii) On Error GoTo -1 ' ( This will clear Err and Erl() and takes us out of the exception State, and so back to normal code running.)
    _(iii) we continue to run the coding at the line after the line that caused the error

    Resume LabelOrLineNumber ( https://excelfox.com/forum/showthrea...ll=1#post10558 )
    _(i) An error occurs. (Assume we have a On Error GoTo LabelOrLineNumber ). The macro is paused. Information relating to the error is registered/ registers get filled in. The macro continues at the place specified by LabelOrLineNumber. Code lines are carried out mostly normally , but we are in the Exception State
    The decision on what to do for if a Resume is encountered will be:
    _(ii) On Error GoTo -1 ' ( This will clear Err and Erl() and takes us out of the exception State, and so back to normal code running.)
    _(iii) we continue to run the coding at the line specified

    So That’s the 3 resumes out of the way. They are very similar, differing only on where the coding finally continues in the normal state. There is nothing new there. I have been preaching that for many years. Others have also, all be it, often a bit patchy, rarely complete guide.


    _ On Error Resume Next Some new thoughts
    Previously I considered pseudo coding using the On Error GoTo -1 at some point. Just now I am wondering about that. Perhaps the exception state is never reached. The following is just a new suggestion:
    ( We assume that an On Error Resume Next has been passed somewhere )
    _(i) An error occurs. The macro is paused. Information relating to the error is registered.
    _(ii) we continue at the next code line after the one that caused the error.

    The slight difference in this new suggestion is that we never go into an exception state, or if we do it is somehow very quickly removed, but not in the same way as any of the Resumes are….



    Another suggestion:
    Just an idea.
    _ On Error Resume Next :- this means we never go into The State of Exception. For no particular reason Microsoft limit us to carry on at the line after that erroring. One might wonder why they did not allow us to do something like ____On Error Resume .. at some other place of your convenience..

    _ On Error GoTo LabelOrLineNumber:- this means we go into exception (when an error occurs). We can choose where we want a copy of the macro to continue (all be it in the State of Exception )








    Some new neat ideas arising from the referenced thread, Slightly compacter way to do simple error handling in VBA
    http://www.eileenslounge.com/viewtop...305642#p305642
    Last edited by DocAElstein; 03-28-2023 at 03:08 PM.

  5. #35
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,315
    Rep Power
    10
    s.cjscsaj
    Last edited by DocAElstein; 03-24-2023 at 09:59 PM.

  6. #36
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,315
    Rep Power
    10
    -LFCASLCJD
    Last edited by DocAElstein; 03-24-2023 at 10:00 PM.

  7. #37
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,315
    Rep Power
    10
    -LLSCJSAJCSALK
    Last edited by DocAElstein; 03-24-2023 at 10:00 PM.

  8. #38
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,315
    Rep Power
    10
    ÖVJLJVFY::FJLKADS
    Last edited by DocAElstein; 03-24-2023 at 10:01 PM.

  9. #39
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,315
    Rep Power
    10
    <KCJLKXJCo





































































    These may take you to page #5, if one does not get you there, then try the other
    https://excelfox.com/forum/showthrea...ll=1#post19909 Page 5
    https://excelfox.com/forum/showthrea...0Nula-1*/page5 Page 5
    Last edited by DocAElstein; 03-28-2023 at 03:21 PM.

  10. #40
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,315
    Rep Power
    10
    .vnvnnvn
    Last edited by DocAElstein; 03-21-2023 at 01:10 AM.

Similar Threads

  1. Replies: 8
    Last Post: 09-01-2015, 01:50 AM
  2. Difference Between 'On Error GoTo 0' And 'On Error GoTo -1'
    By Transformer in forum Familiar with Commands and Formulas
    Replies: 7
    Last Post: 07-02-2015, 04:07 PM
  3. Replies: 2
    Last Post: 05-14-2013, 01:02 AM
  4. Runtime Error 481 invalid figure when PNG
    By Tony in forum Excel Help
    Replies: 0
    Last Post: 02-12-2013, 12:59 AM
  5. Replies: 10
    Last Post: 04-07-2012, 05:33 AM

Posting Permissions

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