Error Handling statement Resumes
Error Handling statement Resume LabelOrLineNumber
This would be used in a similar situation to the last resume type codes, but differing in that when after any error the code should always resume in the same place.
In such code examples, the pseudo coding is easier, since there is no ambiguity on where exactly we go to . It can be seen the error statements of
On Error GoTo -1 : GoTo xxxx
and
Resume xxxx
are exactly the same.
In the code examples below, there are a couple of places where the code can error based on the value of a number variable, TNominator. The purpose of the error handling code section is to adjust that variable value until the whole code is passed.
Therefore in the error handling code section the value “held in” Nominator is adjusted on an error , and then the code restarts from near the start, regardless of where the error occurred. The code will only be completed when a value held in TNominator does not cause an error anywhere in the code.
Code:
Sub PseudoResumeLabelOrLineNumberGoToGet5ButComeBackDarling()
0
1 On Error GoTo GetMilkLuv ' I only need to do this once. VBA has this registered and once the exception is cleared with On Error GoTo -1 , then this user defined error handle will be used again should an error occur
Dim TNominator As Long, RslTwat As Long
2 Let TNominator = 1
3
Let RslTwat = 10 / (TNominator - 1)
MsgBox Err.Description ' This always gives blank, even when an error had occured because On Erro GoTo -1 has clears the Err object of any infomation it might have ever beeen given
Let RslTwat = 10 / (TNominator - 2)
MsgBox prompt:="The code did not error anywhere for TNominator = " & TNominator
Exit Sub
GetMilkLuv: ' "Error handling Code section" is from here until the End
MsgBox prompt:="The number " & TNominator & " causes problems Matey-Boy, (or GirlieOh)"
Let TNominator = TNominator + 1
' Err.Clear ' I do not need to do this, as it is effectively done as part of On Error GoTo -1 Note: Err.Clear removes the infomation, if any is present, in the Err object. it has no efffect on the actual error state
On Error GoTo -1: GoTo 3 ' ' Direct equivalent of Resume 3
End Sub
'
Code:
Sub VBAResumeLabelOrLineNumber() ' ' ' https://excelfox.com/forum/showthread.php/2239-Resume-On-Error-GoTo-0-1-GoTo-Error-Handling-Statements-Runtime-VBA-Err-Handling-ORNeRe-GoRoT-N0Nula-1?p=10558&viewfull=1#post10558
0
1 On Error GoTo GetMilkLuv ' I only need to do this once. VBA has this registered and once the exception is cleared with On Error GoTo -1 , then this user defined error handle will be used again should an error occur
Dim TNominator As Long, RslTwat As Long
2 Let TNominator = 1
3
Let RslTwat = 10 / (TNominator - 1)
MsgBox Err.Description ' This always gives blank, even when an error had occured because On Error GoTo -1 has clears the Err object of any infomation it might have ever beeen given
Let RslTwat = 10 / (TNominator - 2)
MsgBox prompt:="The code did not error anywhere for TNominator = " & TNominator
Exit Sub
GetMilkLuv: ' "Error handling Code section" is from here until the End
MsgBox prompt:="The number " & TNominator & " causes problems Matey-Boy, (or GirlieOh)"
Let TNominator = TNominator + 1
Resume 3 ' Direct equivalent of On Error GoTo -1: GoTo 3
End Sub
Side Issue
On Error GoTo 0 “works” in both the aroused state and the “normal” code running state
It is convenient using codes similar to the last to address this point.
The next two codes are a slight variation of the last one. After the first error an On Error GoTo 0 is done. This disables the initial error handle, On Error GoTo GetMilkLuv , and so the second error is handled by the VBA default error handler and we do not get a chance to adjust the TNominator so as to prevent the second error. The codes terminate with the default VBA error handler
They demonstrate one point in particular: The On Error GoTo 0 “works” in both the aroused state and the “normal” code running state:
The first code has the On Error GoTo 0 in the error handling code section before the resume so the code is at that point effectively part of the exception software;
The second code has the On Error GoTo 0 in the “main” code which due to the “ “On Error GoTo -1 “ effect “ of the Resume done in the error handler , is in normal code modus ( no exception state of aroused erection).
The effect of the On Error GoTo 0 is the same in both codes: It disables ( removes from VBA’s memory ) the user defined error handler after the first error any VBA defaults back to the default VBA error handler. The codes terminate therefore with the default VBA error handler on the second error in both codes.
Code:
' OnErrorGoTo0 In Stiffy : With an erection I remove the user error handler
Sub VBAResumeLabelOrLineNumberOnErrorGoTo0InStiffyModus()
0
1 On Error GoTo GetMilkLuv '
Dim TNominator As Long, RslTwat As Long
2 Let TNominator = 1
3
Let RslTwat = 10 / (TNominator - 1)
' The above line when erroring was "handled by GetMilkLuv:" The line below is handled by the VBA deafault error handler when it causes an error
Let RslTwat = 10 / (TNominator - 2)
' you never get here !
MsgBox prompt:="The code did not error anywhere for TNominator = " & TNominator
Exit Sub
GetMilkLuv: ' "Error handling Code section" is from here until the End
On Error GoTo 0 ' VBA effectively disables/ removes the On Error GoTo GetMilkLuv instruction from its memory. I do it here while I have an erection
MsgBox prompt:="The number " & TNominator & " causes problems Matey-Boy, (or GirlieOh)"
Let TNominator = TNominator + 1
Resume 3
End Sub
'
' OnErrorGoTo0 Schlappschwanz : "Normal" code run disabling of user defined error handler
Sub VBAResumeLabelOrLineNumberOnErrorGoTo0Schlappschwanz()
0
1 On Error GoTo GetMilkLuv '
Dim TNominator As Long, RslTwat As Long
2 Let TNominator = 1
3
Let RslTwat = 10 / (TNominator - 1)
' The above line when erroring was "handled by GetMilkLuv:" The second line below is handled by the VBA deafault error handler when it causes an error
On Error GoTo 0 ' VBA effectively disables/ removes the On Error GoTo GetMilkLuv instruction from its memory
Let RslTwat = 10 / (TNominator - 2)
' you never get here !
MsgBox prompt:="The code did not error anywhere for TNominator = " & TNominator
Exit Sub
GetMilkLuv: ' "Error handling Code section" is from here until the End
MsgBox prompt:="The number " & TNominator & " causes problems Matey-Boy, (or GirlieOh)"
Let TNominator = TNominator + 1
Resume 3
End Sub
Link to get to Page 2 ( using 2 above right from post #1, or the 2 below right in the page list, does not work due to number at end of title ) :
http://www.excelfox.com/forum/showth...0559#post10559
Bookmarks