Page 3 of 6 FirstFirst 12345 ... LastLast
Results 21 to 30 of 52

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

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





























































    Link to get to Page 3 ( using 3 above right from post #11, 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
    Last edited by DocAElstein; 03-24-2023 at 07:08 PM.

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

    Part 1) Err object ... Err.Raise

    Part 1) Err object. Err.Raise.
    The basic command for a custom error handler is the use of the Err object method of .Raise in such a code line:
    Err.Raise(Number:= , Source:= , Description:= , HelpFile:= , HelpContext:= , LastDllError:= )
    The basic function and usual usage is to start the default VBA Error handler, but the text properties will be mostly left empty in the uses of it usually seen.
    I say mostly as syntaxly you must give at least the first, Number:= in the above code line if you use it.

    Possibly the Err.Raise Custom Error handler has been introduced by someone for fun as some sort of Trolling. Most of what you can do with it you can do in other more intuitive ways. In addition there are a few quirks that no one quite seems to understand.


    So the basic idea is that you can force something similar to happen as to that when an error occurs. Similar…

    I think if we take another look generally at the Err object, try to work through what it, and in particular its Method .Raise does, mention a few quirks along the way, … then I think we will see that .Raise is not much more than a complicated way to bring up a Message box.

    Back to the start:
    Three codes did a demo on what goes on if you try to divide by zero. Here the simplest again:
    Code:
    Sub Error_VBADefaultErrorHandling()
    Dim Db As Double
     Let Db = 1 / 0 ' Code terminates here and VBA chucks up a meassage box
    'You never get here
    End Sub
    The result with those codes was an error, and the corresponding message was of the form:

    Laufzeitfehler '11':
    Division durch Null

    Runtime Error '11':
    division with zero




    The following codes are not much use for anything over than the discussions here. They are not much use as the main result of a simple call of the Err.Raise will be to stop the code in the typical VBA default error handling way.
    The slight difference is that VBA does not make an attempt to fully fill the Properties of the Err object. This is reasonable as it has no real error to refer to.
    So the syntax of the method allows for Property entries, with a couple of quirks:
    A number must be give;.
    If the number happens to be a number VBA recognises then VBA will add the appropriate other information
    Code:
    Sub RaiseAnyNumber()
     Err.Raise Number:=9999
    End Sub
    ErrRaise9999Help.JPG : https://imgur.com/KSlN6D7 https://i.postimg.cc/sX8dmqY0/Err-Raise9999-Help.jpg
    https://i.postimg.cc/fbzNRxW5/Err-Raise9999-Help.jpg

    ErrRaise9999Help.JPGErrRaise9999 Help.jpg

    If we use the number 11 then VBA recognises that as the error when trying to divide by zero, and adds appropriately the description
    Code:
    Sub Raise11()
     Err.Raise Number:=11
    End Sub
    ErrRaise11Help.JPG : https://imgur.com/tL6uvxN https://i.postimg.cc/R0gz6NNm/Err-Raise11-Help.jpg
    ErrRaise11Help.jpg

    We can overwrite the attempt from VBA to add the corresponding information to the Err object Properties, although it appears that number is still used by VBA
    Code:
    Sub Raise11B()
     Err.Raise Number:=11, Description:="An Error with Number 11, Bollox"
    End Sub
    ErrRaise11BolloxHelp.JPG : https://imgur.com/tDK7JwF https://i.postimg.cc/t4Hb8KLK/Err-Ra...ollox-Help.jpg
    ErrRaise11BolloxHelp.jpg






    _.......continued in next post
    Last edited by DocAElstein; 03-24-2023 at 09:16 PM.

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

    Part 1) Err object ... Err.Raise

    _..... continuing from last post

    In any practical use of the Err.Raise Method we would likely use it within one of the main two Error Handlers, On Error Resume Next or On Error GoTo LabelOrLineNumber

    Indeed to progress further with the experiments here that will be useful to use it in that form.
    I prefer to use the On Error GoTo LabelOrLineNumber , as the previous experiments showed the it was somewhat unexpected that when errors occurred with the On Error Resume Next that the information in the Err object properties were maintained. As I don’t know what extra coding is in place to make that happen, I will stick with the On Error GoTo LabelOrLineNumber as I am thinking that this may be more fundamental , which is preferable when delving down in experiments.

    The following code is the simplified typical usage of On Error GoTo LabelOrLineNumber to hook from the LabelOrLineNumber position our code Sub RaiseErection() into the Exception software, allowing normal code type progression in the aroused state.
    The purpose of the error handling code section is to give full details of the Err object Properties for different .Raise argument.
    This will be helpful as an insight into how we might want to use the Err.Raise in a “customised” error handler
    With the error handler in place, then as usual, we do not prevent an erecting to the exception state, - but the code is not ended via the default VBA error handler via a pop up with the Error description and Error Number displayed. The code in the exception state continues, that is to say the sub routine is now part of the exception software which continues allowing us to use the error object for those two properties of Error description and Error Number but also the other Properties available.
    Code:
    Sub RaiseErection()
     On Error GoTo EmBed
     Err.Raise Number:=9999
    Exit Sub ' You never come here
    EmBed: ' Error handling code section
    Dim strMsg As String
     Let strMsg = "Number:=   " & Err.Number & vbCr & vbLf & "Description:=    " & Err.Description & vbCr & vbLf & "Source:=  " & vbCrLf & "HelpFile:= """ & Err.HelpFile & """" & vbCrLf & "HelpContext:=    " & Err.HelpContext & vbCrLf & "LastDllError   " & Err.LastDllError
     MsgBox strMsg: Debug.Print strMsg
    End Sub
    
    Here the typical results displayed in a message box and also available to copy from the immediate window:

    Number:= 9999
    Description:= Anwendungs- oder objektdefinierter Fehler
    Source:=
    HelpFile:= C:\PROGRA~1\COMMON~1\MICROS~1\VBA\VBA6\1031\VbLR6. chm
    HelpContext:= 1000095
    LastDllError 0


    One useful side effect from all this latest foray is the possibility to get at a working example of the Help File Button option typically seen in Pop up boxes. As example I can get at the above help info, ( which is the default when no error is listed for the error number given ) , now using codes such as this:
    Code:
    Sub HilfeIWishIHadSeenThisBefore()
     Application.Help HelpFile:="C:\PROGRA~1\COMMON~1\MICROS~1\VBA\VBA6\1031\VbLR6.chm", HelpContextID:=1000096
     VBA.InputBox prompt:="Test a HelpFile Button", HelpFile:="C:\PROGRA~1\COMMON~1\MICROS~1\VBA\VBA6\1031\VbLR6.chm", Context:=1000095
                           'Application.InputBox Prompt:="Test a HelpFile Button", HelpFile:="C:\PROGRA~1\COMMON~1\MICROS~1\VBA\VBA6\1031\VbLR6.chm", HelpContextID:=1000096 ' Help butttons are broken on Application Input box
    End Sub
    ( I would have saved myself a lot of bother if I had seen this before I did this:
    https://www.excelforum.com/excel-new...ml#post4827566
    )

    _.....
    Using one of the resume statements it is very easy to modify the last error raising code to effectively loop through a number of options: by simply adding Resume Next at the end of the code the last exception is cleared, as is the Err object, and the code continues in normal modus at the next line. So with Resume Next added we can replace the single Err.Raise with a list which will be progressed through. Here an example code,
    Code:
    Sub RaiseErections()
    0 On Error GoTo EmBed
    1 Err.Raise Number:=9999
    2 Err.Raise Number:=11
    3 Err.Raise Number:=12
    4 Err.Raise Number:=vbObjectError        ' vbObjectError.JPG           : https://imgur.com/fdh4ymA
    5 Err.Raise Number:=-2147221504          ' -2147221504.JPG             : https://imgur.com/1kKYjzA
    6 Err.Raise Number:=vbObjectError + 1    ' vbObjectError + 1.JPG       : https://imgur.com/sc9qm8d
    7 Err.Raise Number:=vbObjectError + 500  ' vbObjectError + 500.JPG     : https://imgur.com/7DNiUnR
    8 Err.Raise Number:=vbObjectError + 11   ' vbObjectError + 11.jpg      : https://imgur.com/8rqVpYe
    Exit Sub ' You never come here
    EmBed: ' Error handling code section
    Dim strMsg As String
     Let strMsg = "Number:=   " & Err.Number & vbCr & vbLf & "Description:=    " & Err.Description & vbCr & vbLf & "Source:=  " & Err.Source & vbCrLf & "HelpFile:= """ & Err.HelpFile & """" & vbCrLf & "HelpContext:=    " & Err.HelpContext & vbCr & vbLf & "LastDllError   " & Err.LastDllError
     'MsgBox strMsg
     Debug.Print strMsg
     Debug.Print ' To make a space between each set of infomation
     Resume Next ' We clear the exceütioon, clear the Err object, and continue in normal code running mode at the next Err Raise line
    End Sub




    And here the results as seen in the Immediate window:
    Code:
    Number:=   9999
    Description:=    Anwendungs- oder objektdefinierter Fehler
    Source:=  VBAProject
    HelpFile:= "C:\PROGRA~1\COMMON~1\MICROS~1\VBA\VBA6\1031\VbLR6.chm"
    HelpContext:=    1000095
    LastDllError   0
    
    Number:=   11
    Description:=    Division durch Null
    Source:=  VBAProject
    HelpFile:= "C:\PROGRA~1\COMMON~1\MICROS~1\VBA\VBA6\1031\VbLR6.chm"
    HelpContext:=    1000011
    LastDllError   0
    
    Number:=   12
    Description:=    Anwendungs- oder objektdefinierter Fehler
    Source:=  VBAProject
    HelpFile:= "C:\PROGRA~1\COMMON~1\MICROS~1\VBA\VBA6\1031\VbLR6.chm"
    HelpContext:=    1000095
    LastDllError   0
    
    Number:=   -2147221504
    Description:=    Automatisierungsfehler
    Ungültige OLEVERB-Struktur 
    Source:=  VBAProject
    HelpFile:= "C:\PROGRA~1\COMMON~1\MICROS~1\VBA\VBA6\1031\VbLR6.chm"
    HelpContext:=    1000440
    LastDllError   0
    
    Number:=   -2147221504
    Description:=    Automatisierungsfehler
    Ungültige OLEVERB-Struktur 
    Source:=  VBAProject
    HelpFile:= "C:\PROGRA~1\COMMON~1\MICROS~1\VBA\VBA6\1031\VbLR6.chm"
    HelpContext:=    1000440
    LastDllError   0
    
    Number:=   -2147221503
    Description:=    Automatisierungsfehler
    Ungültige Advisemarken 
    Source:=  VBAProject
    HelpFile:= "C:\PROGRA~1\COMMON~1\MICROS~1\VBA\VBA6\1031\VbLR6.chm"
    HelpContext:=    1000440
    LastDllError   0
    
    Number:=   -2147221004
    Description:=    Automatisierungsfehler
    Ungültige Schnittstellenzeichenfolge 
    Source:=  VBAProject
    HelpFile:= "C:\PROGRA~1\COMMON~1\MICROS~1\VBA\VBA6\1031\VbLR6.chm"
    HelpContext:=    1000440
    LastDllError   0
    
    Number:=   -2147221493
    Description:=    Automatisierungsfehler
    Das Objekt ist statisch. Der Vorgang ist nicht erlaubt. 
    Source:=  VBAProject
    HelpFile:= "C:\PROGRA~1\COMMON~1\MICROS~1\VBA\VBA6\1031\VbLR6.chm"
    HelpContext:=    1000440
    LastDllError   0
    The initial 3, or rather 1 and 3, results show that there is a standard description and help file, ( or “page”/ Context thereof ) for any unrecognised number.

    The final 4 are associated with some vbObjectError concept.
    Wherever I have looked, vbObjectError appears to be a constant with value of -2147221504
    I expect that no one remembers what that really is and / or it is probably broken. … a typical answer given is that .. “.. it generates a unique error number… prevents conflict with any existing number and/ or prevents rewrite in the future—when later versions of Visual Basic that use more error numbers.. “
    No one really knows what they mean by conflict in this sense means. In fact it appears the answer was given to them by someone who was given it by someone… if you spend enough time following down the chain you find you come back to the same point, that is to say no one remembers where the rumour started and the original person that started the rumour forgot and later asked someone else that fell for his rumour originally.
    Clearly the results are not suggesting that a non used number is being obtained.
    The results suggest that by trial and error you can find a number that is not being looking to get the first and third error message. The Help for those options suggests that the number is not used

    So you may as well make up numbers that suit any particular logic or idea or organised list that suits you and a description you like.

    Probably the only conclusions from this post is that if I chose to .Raise an error, then I might want to first make a code something similar to the ones in this post but which also have an error of the sort or similar to the one I want to do a customised error handler for. The I can get the standard Properties which I may then chose to use either in their entirety, such as in the case of the Help File path , ( and page number ( context Property ) , or I may chose to modify then somehow, such as in the description in order to be more specific about my particular error.

    I am thinking that the Custom Error handler using the Err object .Raise method is a waste of time, and probably doing the same with Message boxes or Input boxes is probably a lot more intuitive and more versatile. But for completeness I will have a look at a simple example in the next post.
    Last edited by DocAElstein; 03-24-2023 at 09:21 PM.

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

    Part 2) Custom Error handler using Err object. Err.Raise.

    Err object. Err.Raise. Custom Error handler

    Part 2) Custom Error handler using Err object. Err.Raise.

    The conclusions from the last post are that this is just a complicated way to get a message box up to warn or inform of an error.
    The custom error handler, or rather the working part of it, .Raise is as un intuitive as most of the VBA error handling tools and concepts. One thing that does not follow obviously from the last post I that one thing that the Err.Raise effectively does is to replace any existing user defined error handling with the default VBA error handler, but with modified Properties as defined in the arguments of the .Raise:
    Err. Raise(Number:= , Source:= , Description:= , HelpFile:= , HelpContext:= , LastDllError:= )
    It appears to do this replacement even in the aroused exceptional state. So effectively we have pseudo
    _ [On Error GoTo -1 : Raise exception, use default VBA handler with these modified arguments of( 11 , , , , , ) ]

    As noted the use as in the last post of Err.Raise had little practical use. The fact that it appears to work in the Exception state would make it possible to use in such an example as below. There I use the On Error GoTo LabelOrLineNumber initially and then at the error handling code section sent to by the LabelOrLineNumber I will do the .Raise

    Consider the simple example looked at already a few times of an attempt to divide by zero.
    Based on the experiments from the last post I will decide to
    _ give an arbitrary, ( hopefully never used ), Number ,
    _ I will choose my own message ( .Description ) ,
    _ I will use the .Source always seen from the last post ( It appears to be possible to use anything at all here, - but just to be on the safe side I will use what appears the appropriate one )
    _ Use the appropriate help available for this sort of error

    The purpose of this code would be to punish the Twat that tried to divide by zero. A different error is handled more politely.
    Code:
    Sub CunstromErrorhandler()
     On Error GoTo ErrRaiseHandle
    ' An Error to be handled politely
    Dim Rng As Range
     Let Rng.Value = "AnyFink" ' Will error as my Rng has not been set so "doesn't exist"
    ' An Error to be punished
    Dim RslTwat As Double, Destrominator As Long
     Let RslTwat = 1 / 0
    '
    Exit Sub
    ErrRaiseHandle:
        If Err.Number = 11 Then
         Err.Raise Number:=42, Source:="VBAProject", Description:="You stupid Twat, you tried to divide by 0, as punishment I will end the code", HelpFile:="C:\PROGRA~1\COMMON~1\MICROS~1\VBA\VBA6\1031\VbLR6.chm", HelpContext:=1000011
        Else
         MsgBox "The error was " & Err.Description & vbCrLf & "The code will continue at the line just after the one which caused the error"
         Resume Next
        End If
    End Sub




    In the above code I can't see any major advantage of using the Err.Raise in place of a message box for a simple message, ( or if I wanted to use the Help then I could use the VBA Input box )
    If the error is not the divide by zero , then I use a more standard MsgBox using the Err Object Property information



    Here the same code again using the VBA Input box in place of the Err.Raise , that is to say doing effectively the same as far as the user is concerned. In this second code as we are not using Err.Raise at all, then we are not doing the likely pseudo _..
    _ [On Error GoTo -1 : Raise exception, use default VBA handler with these modified arguments of( , , , , , ) ]

    _.. to do later, or find it....
    Last edited by DocAElstein; 03-24-2023 at 09:31 PM.

  5. #25
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,315
    Rep Power
    10
    asljclskajcfjc
    Last edited by DocAElstein; 03-24-2023 at 09:29 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!!

  6. #26
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,315
    Rep Power
    10
    lkcslcj
    Last edited by DocAElstein; 03-21-2023 at 12:48 AM.

  7. #27
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,315
    Rep Power
    10
    ffffjjfsfa
    Last edited by DocAElstein; 03-21-2023 at 12:49 AM.
    ….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!!

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

    Final Summary table ................... VBA Error Handling ORNeRe GoRoT N0Nula 1

    Last edited by DocAElstein; 03-24-2023 at 09:51 PM.

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

    A few Miscellaneous points that might have been missed, or not explicitly stated

    Finallly….
    A few Miscellaneous points that might have been missed, or not explicitly stated
    ..


    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














    Ref
    https://msdn.microsoft.com/en-us/vba...error-handling
    https://usefulgyaan.wordpress.com/20...-error-occurs/
    https://msdn.microsoft.com/en-us/library/s6da8809.aspx
    http://www.freetutes.com/learn-vb6-a...son11/p14.html
    Binding and list stuff from snb
    Rory told me stuff and often got it right
    Here is the link again to the Notes I nade a couple of years ago. I have added the notes from this “Blog” to them. I have also changed the Word File to a .docm file and added all the codes to it : __ Errors and Error Handling in VBA 2018
    ORNeRe GoRoT N0Nula 1 : https://www.youtube.com/watch?v=6RRv35Ig2mg
    https://www.mrexcel.com/forum/genera...ml#post4357648








    Last edited by DocAElstein; 03-21-2023 at 01:20 AM.

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

    A few Miscellaneous points that might have been missed, or not explicitly stated






    Link to get to Page 4 ( using 3 above right from post #21, or the 3 below right in the page list, does not work due to number at end of title ) :
    https://www.excelfox.com/forum/showt...891&viewfull=1 page 4
    https://excelfox.com/forum/showthrea...0Nula-1*/page4 Page 4
    Last edited by DocAElstein; 03-24-2023 at 06:13 PM.

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
  •