Page 1 of 6 123 ... LastLast
Results 1 to 10 of 52

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

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

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

    Link to get to Page 2 ( using 2 above right, or square with page number generally, sometimes does not work due to number at end of title ) :
    http://www.excelfox.com/forum/showth...0559#post10559

    _.__________________________

    https://excelfox.com/forum/showthrea...9877#post19877 Page 3
    https://excelfox.com/forum/showthrea...0Nula-1*/page3 Page 3


    https://www.excelfox.com/forum/showt...891&viewfull=1 page 4
    https://excelfox.com/forum/showthrea...0Nula-1*/page4 Page 4

    https://excelfox.com/forum/showthrea...ll=1#post19909 Page 5
    https://excelfox.com/forum/showthrea...0Nula-1*/page5 Page 5

    https://excelfox.com/forum/showthrea...ll=1#post19906 Page 6


    __________________________________________________ ______________________________________________


    This is post https://excelfox.com/forum/showthrea...ll=1#post10549






    Resume On Error GoTo 0 -1 GoTo Error Handling Statements, Error and VBA Error Handling in Runtime
    Erections/ arousing of Exceptional states by Error, 2018

    ORNeRe GoRoT N0Nula 1
    The Glorious State of Exception in Transalvania

    Hi
    I wrote for myself and shared some notes on this a couple of years ago.
    https://app.box.com/s/8zkhjcmbxrqnlnexqpktuy41clgqm4zo
    ( and here these current new notes in word docm format with codes also: Errors and Error Handling in VBA 2018 )

    I think they are fairly complete, but never the less , I usually end up trying test code examples to remind me of what is going on.
    It seems like an awkward subject, or is organised in a seemingly odd way, and unfortunately always seems to need a bit of thought or revision
    Some people asked me to share some simple examples_..

    _.. Here we go then, these will be a bit more practical and less theoretical than the notes, but a read of those notes as well probably does no harm. I will try a slightly different approach, just by way of a change. In the end though, I think I could end up just as long: I think this subject is not so difficult to master, its actually quite easy, bit almost nobody gets it completely correct. Possibly this is just because there are some strange syntaxes and the amount to learn is just that little too long for anyone to want read for a subject which on the face of it should be short, since for most real Object Oriented Programming, the try-catch structure would be the standard for just about everything, but instead VBA is an unholy alliance of MS Basic and sort-of-objects – ( Jay Freedman : https://eileenslounge.com/viewtopic....305700#p305700 )




    https://i.postimg.cc/L5tmj8Jc/VBA-De...or-Handler.jpg https://i.postimg.cc/L5KHq18k/VBA-De...r-Div-by-0.jpg



    https://www.youtube.com/channel/UCnxwq2aGJRbjOo_MO54oaHA
    Attached Images Attached Images
    Last edited by DocAElstein; 10-02-2023 at 12:56 PM. Reason: Jay Freedman : https://eileenslounge.com/viewtopic.php?p=305700#p305700

  2. #2
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    “Pseudo” Default VBA Error handling
    The Glorious State of Transylvania
    The first, possibly most fundamental Error handler,
    On Error GoTo LabelOrLineNumber


    Codes are in the next two posts, and in this post is some background theory and concepts needed.

    “Pseudo” Default VBA Error handling (Taping / hooking on to lower level stuff)
    Using code to mimic the default handler can possibly help in learning how to use VBA Error Handling.
    A couple of tools we need to get started on this are:
    _ some basic understanding of one of the Error Handling statements, On Error GoTo LabelOrLineNumber ;
    _ and an available VBA object associated with the exception situation, Err
    _ Sub Class a Windows Visual Basic Wonk aka mess with the Exception Software
    I expect at the heart of error handling is the first of the main two error handling statements:
    On Error GoTo LabelOrLineNumber
    Windows and Visual Basic , like Excel and VBA are related things.
    The default VBA Error Handling, like most pre determined things in Excel, can be mimicked by us as we have access to a lot of the stuff/software that it uses:
    We might be loosely called “application ( Excel ) programmers”.
    We, as application programmers, can access directly or indirectly a lot of the software used to create the application in the first place . ( A running or “open” Excel is often referred to as an application, or the Excel application. I suppose it is talking about the software being applied ).
    We might say we are working at a higher level in the computing way of things, but in actual fact we can often get at more deeper stuff and tap off, hook into it, or hang bits of our coding into the chain of events that comprises more lower level programming.
    Using code to mimic the default handler
    What does On Error GoTo LabelOrLineNumber Statement organise and do ? :
    As far as us end users are concerned, or as they experience it, this statement does as it suggests: it appears that once an exception is raised, the code continues. But it appears to do so in first being “sent” to the place of the LabelOrLineNumber, just as it would in any GoTo LabelOrLineNumber.
    That is how it appears. But it is more subtle.
    It does not simply “tell” VBA always to Go To the place indicated at every thing that causes an error:
    The code is allowed to continue further from that place indicated, which is where it is “sent to” the first time that an error occurs. ****But a very important point to bear in mind when trying to understand VBA Error Handling in Runtime is that the exception in this situation is still raised. Effectively we have hooked onto, or embedded our code now into the Exception Software which has started due to the error occurring.
    I think the way that it actually works is as follows: The code running, or execution is not really sent at any point to the place indicated.
    Initially, Passing of the On Error GoTo LabelOrLineNumber code line has the effect of doing the following: It makes a copy of the code and hangs that on the predetermined chain of events that occur when an error occurs. The start of the copy of the code is not the original routine start, but the LabelOrLineNumber point.
    A fun way of thinking about it could be to say we are transported to another World, say in The Glorious State of Exception in Transylvania. A copy of our coding is taken with us, and we continue running the coding from the place we were sent to.
    In the Glorious State of Exception.
    It is reasonable to expect that a code running in general in the exception state , (or being run now pseudo as part of the Exception software), is likely not to function completely as the same coding in the “normal” state would. In fact it appears that most things do actually work normally.
    But one thing for sure doesn’t, and that is, possibly as might be reasonably expected, the following:
    In the raised exception state, any ( further ) uses of the statements On Error GoTo LabelOrLineNumber or On Error Resume Next , ( be they other code lines or the original On Error GoTo LabelOrLineNumber such as in a looping code situation ) will be ignored. This is because the code is now part of what is sometimes referred to as a call back procedure. In simple terms the code can be thought of now as part of the Exception software code. The first use of the On Error GoTo LabelOrLineNumber effectively linked / transferred the code there, or started a copy of the code from that place, so further attempts to do that would be superfluous and so such code lines are ignored. In simple terms , once we are in the exception state then codes lines like On Error GoTo LabelOrLineNumber or On Error Resume Next are just past as if they were not there. (Not all the error “things”/ Statements wont work, that is to say do what they are supposed to in the Exception State, some will, but more to that later, …. ).
    The two main error handling statements give a complicated set of instructions, and cause all sorts of internal things to go on, as do the other two statements contain a GoTo . The significance of the GoTo is god knows fucking what. I expect it was just done for fun, to confuse, but maybe I can come up later with some fun ways that make some abstract sense





    _ Err Object.( Function..Ref.)
    Err is a function that returns an ErrObject
    This is a VBA object associated with the exception situation. It has a couple of methods ( .Clear and .Raise ) and a few Properties.
    It does not usually directly control an error situation, or at least does not have that as its main purpose. ( It is sometimes used to see If an error occurred )
    Err.Clear _ does not clear the exception. It simply empties some string variable properties containing information about the last error which occurred. In fun terms, think of it as not taking us back to the real world or place we were sent from.
    It is mainly used to hold information about the last error. But it does have a Method which pseudo can be used to fool VBA into thinking that an error occurred, ( .Raise)

    The Properties have mainly the purpose of storing information about the error that occurred. The Exception software usually passes information related to the error when the error occurs. ( When using .Raise you can additionally via the .Raise( , , , , , ) arguments effectively mess about with the coding which passes this information so as to fill the object with any relevant or irrelevant profanities of your choice)
    I use the Err object in my next codes to get the same information that the Default VBA Error handling chucks up at me: We can use Properties of the Err object to get information about the error. I don’t use the .Raise here. ( I will look at that later – It appears to be a waste of time, and no one can remember quite much about it )
    Very likely the Exception software uses this Err object in exactly the same way as I will to get its information, although it is a bit of a “Chicken and Egg” question / situation: The Exception software fills initially this object with text and number information about the error as it occurs and then uses this information itself in the message box pop up that comes up by default. At least that is my theory. No one seems to know for sure.
    We can reference these Properties ourselves and retrieve them, like, for example, in a code line to get a simple description of the error that occurred , like this:
    Dim TheErrorDescription As String
    _ Let TheErrorDescription = Err.Description


    Although the Exception software can fill the object with information, it appears that the information is , to at least a first approximation, held in a similar way that the properties of any typical VBA object such as a range might be. As such we can ourselves, with simple VBA code, assign them.
    So as example, for the last example we could do this:
    _ Let Err.Description = “Any Text I like”
    The value that the exception software had given would then be replaced / overwritten.
    I can do that at any time, but it would be overwritten if I did it before an error occurred.

    ( The same assigning could be achieved when using the .Raise to ““make” an imaginary error”, for example like:
    Err.Raise(Number:=42 , Source:= , Description:= “Any Text I like” , HelpFile:= , HelpContext:= ) _ )




    Codes to mimic VBA Default Error handling.
    See next two posts



    Ref
    https://www.eileenslounge.com/viewto...247160#p247149

    Last edited by DocAElstein; 03-25-2023 at 02:21 AM.

  3. #3
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    "Pseudo" Default VBA Error handling


    Codes to mimic VBA Default Error handling.
    The code below, using user define VBA error handling, is an approximation to part of the VBA Default Error handling. ( The line numbers are just added to help the further explanations: they are not needed for these codes. )
    Run the code.
    We can, to a first approximation say that the _ OK _ Button which appears in the pop up message box is doing similar to the _ Beenden/Stop _ Button from Default VBA Error handling.
    Code:
    ' -1    ' No Exception state before the code is run ( Ending a code clears any exception )
    Sub PseudoVBADefaultErrorhandlingPartial()
    0
    1 On Error GoTo ErrHndler ' '_- Hang hook on chain of events that signify to go to call back procedure when chain is waggled by error erection
    Dim Db As Double
    ' Coding
     Let Db = 1 / 0 '           '_- When the error occurs, the Exception software has the code from ErrHndler included in it
    ' Other Coding. In the case of an error this will never be done
    GoTo AfterErrHndler
    ErrHndler: ' =========================== ' Call back procedure. Code to be hooked on to Exception software.    User defined  pseudo VBA Error handling
     MsgBox prompt:="Laufzeitfehler '" & Err.Number & "':" & vbCr & vbLf & Err.Description & "                      ", Title:="Microsoft Visual Basic": Debug.Print "Laufzeitfehler '" & Err.Number & "':" & vbCrLf & Err.Description & "                      " ' From VB Editor , hit  Ctrl+g  to display the Immediate Window   ---      Laufzeitfehler '11': Division durch Null     Runtime Error '11': division with zero
    '
    Exit Sub ' This will clear the exception state. No exception state once code is Ended
    AfterErrHndler: '=======================
    'You never get here
    ' Other Coding ' In the case of an error this will never be done
    End Sub ' This will clear the exception state. No exception state once code is Ended
    ' -1 Sub PseudoVBADefaultErrorhandlingPartialSimplified() On Error GoTo ErrHndler ' Dim Db As Double ' Coding Let Db = 1 / 0 ' When the error occurs, the Exception software has the code from ErrHndler included in it ' Other Coding. In the case of an error this will never be done Exit Sub ErrHndler: ' Error handling code section MsgBox prompt:="Laufzeitfehler '" & Err.Number & "':" & vbCr & vbLf & Err.Description & "" End Sub
    Error handling code section
    Just to clarify what I am doing here: I am using error handling techniques to make an error handler similar to the default VBA error handler. This is just by way of a learning exercise to get familiar with VBA error situations in general.
    The code section as indicated within ==== is typically referred to as the Error handling code section. In this case the code carried out as part of the Exception Coding is within that section. But it need not be. That referral can be meant to include code lines such as GoTo LabelOrLineNumber or also the execution of any of the three resumes, which effectively bring the normal code back into action. So the term error handling code section is not clearly defined.
    To a first approximation the error handling code section is the code section as indicated within ====

    The error handling code section need not be , but often is, at the end of the main code. In either case it is necessary to organise that in normal code progressing when no error occurs, that error handling code section will be bypassed.
    If, in the last code the error handling code section were at the end, then the label AfterErrHndler: could be omitted, and the Goto AfterErrHndler replaced with Exit Sub

    Here the same code again in a more typically seen simplified form
    Code:
    ' -1
    Sub PseudoVBADefaultErrorhandlingPartialSimplified() '                                                                                       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=10551&viewfull=1#post10551
    On Error GoTo ErrHndler '
    Dim Db As Double
    ' Coding
     Let Db = 1 / 0 ' When the error occurs, the Exception software has the code from ErrHndler included in it
    ' Other Coding. In the case of an error this will never be done
    Exit Sub
    ErrHndler: ' Error handling code section
     MsgBox prompt:="Laufzeitfehler '" & Err.Number & "':" & vbCr & vbLf & Err.Description & ""
    End Sub
    Last edited by DocAElstein; 03-21-2023 at 05:53 PM.

  4. #4
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    "Pseudo" Default VBA Error handling


    Codes to mimic VBA Default Error handling
    .

    The next code comes a bit closer to replicating the default VBA Error handling, but note that it is still an approximation
    If you run the code and select _ No _ then this will be similar to selecting _ Beenden/Stop _ as before
    If you select _ Yes _ , this will be something similar to selecting _ Debug _ in the standard default VBA error handler: The code will return to and pause just before the line that errored.
    It might be easier to demo this in normal run mode, ( Click in code, and then select F5 or select play button )
    In a typical situation, the selecting to _ Debug _ will allow you manually to do something before continuing, such as dragging the yellow arrow in the left margin away from the line causing an error.
    DragDownPastErroringLine.JPG : https://imgur.com/pK01TYA
    DragDownPastErroringLine.jpg

    The code will then appear then to procede normally , but note that it the code is still running in an aroused state of erected exception###

    Code:
    ' Run this code in F5 initially to see the possibility of selecting Debug/Yes on pop up                                                              '  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=10552&viewfull=1#post10552
    ' -1    ' No Exception state before the code is run
    Sub PseudoVBADefaultErrorhandling()
    0
    1 On Error GoTo ErrHndler ' hang hook on chain of events that signify to go to call back procedure when chain is waggled by error erection
    Dim Db As Double
    ' Coding
    GoTo Eror ' up to here is "normal" code unless you drag cursor yellow in left margin back up after selecting Yes
    JustBeforeError: ' ==  Pseudo Part of error handling ==
    Stop ' ==============  Pseodo Part of error handling ==
    Eror: ' After stop, drag yellow arrow in margin down to pass error, or drag up to 0 and run
    '       If you drag down past error then code will go to normal end (but is running in exception state)                DragDownPastErroringLine.JPG : https://imgur.com/pK01TYA
    '       Draging up to 0 will cause error to be handled by VBA default error handler as after error we are always in exception state  DragUpTo 0.JPG : https://imgur.com/bdQy0xb
     Let Db = 1 / 0 ' When the error occurs, the Exception software has the code from ErrHndler included in it
    ' Other Coding. In the case of an error this will not be done
    GoTo AfterErrHndler
    ErrHndler: ' ============================= ' Call back procedure. Code to be hooked on to Exception software ==                        User defined  pseudo VBA Error handling
    Dim Answer As Long
     Let Answer = MsgBox(prompt:="Laufzeitfehler '" & Err.Number & "':" & vbCr & vbLf & Err.Description & "                        ", Title:="Microsoft Visual Basic", Buttons:=vbYesNo)
        If Answer = vbNo Then Exit Sub ' This will clear the exception state. No exception state once code is Ended
        If Answer = vbYes Then ' This is equivalent to Hitting  Debug  in the default VBA error handler
         GoTo JustBeforeError ' == Approx. what the default VBA error handler would do on selecting debug
        Else
        End If
    AfterErrHndler: '======================================
    ' You may get here if you change the code, or skip the erroring line by draging the left margin yellow cursor down past the error line
    ' Other Coding '
    ' Nornal code end
    End Sub '
    One last experiment may be worth doing on the last code above after selecting _ Yes _ : Drag the yellow arrow back up to line 1 or 0 , so that the error handling statement On Error GoTo ErrHndler is done again.
    DragUpTo 0.JPG : https://imgur.com/bdQy0xb
    DragUpTo 0.jpg

    Now continue the code in F5 or F8. You will notice that the actual default VBA Error handling is done at the error occurrence and not our user defined pseudo VBA Error handling, which in this code is organised in advance/ indicated by the code line On Error GoTo ErrHndler.
    So despite that you effectively once again passed On Error GoTo ErrHndler, our user defined pseudo VBA Error handling is no longer done after it has once been used in a running code.
    ###This is because the exception is still raised, so such statements are ignored****.


    In a round about sort of a way I think the above has got us through understanding On Error GoTo LabelOrLineNumber and a very important point is to remember that this error handling statement does not clear the exception.
    One last code is useful to re emphasise this last point.
    The codes in the next post demonstrates the classic pit fall which often what leads to many of us learning about Runtime Error and Runtime Error Handling VBA for the first time …. On Error GoTo LabelOrLineNumber only works once


    https://www.youtube.com/channel/UCnxwq2aGJRbjOo_MO54oaHA
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=UgyG714V_k7odQMrTz14AaABAg. 9h740K6COOA9iHOYYpaAbC
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=UgxuL6YCUckeUIh9hoh4AaABAg
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=UgwGTEyefOX7msIh1wZ4AaABAg. 9h4sd6Vs4qE9h7G-bVm8_-
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=Ugw3nF0C04AGt73H1BB4AaABAg. 9h6VhNCM-DZ9h7EqbG23kg
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=UgwGTEyefOX7msIh1wZ4AaABAg. 9h4sd6Vs4qE9h7KvJXmK8o
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=Ugw3nF0C04AGt73H1BB4AaABAg. 9h6VhNCM-DZ9h7E1gwg4Aq
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=UgywFtBEpkHDuK55r214AaABAg
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=UgwviLabd7r_3KpP6wh4AaABAg. 9h5lFRmix1R9h79hNGvJbu
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=UgwviLabd7r_3KpP6wh4AaABAg. 9h5lFRmix1R9h79YAfa24T
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=UgwviLabd7r_3KpP6wh4AaABAg. 9h5lFRmix1R9h79M1SYH1E
    https://www.youtube.com/watch?v=2oT4qrHmDMY&lc=UgwviLabd7r_3KpP6wh4AaABAg. 9h5lFRmix1R9h78SxhXTnR
    https://www.youtube.com/channel/UCnxwq2aGJRbjOo_MO54oaHA
    Last edited by DocAElstein; 07-09-2023 at 11:12 PM.

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

    On Error GoTo LabelOrLineNumber only works once

    On Error GoTo LabelOrLineNumber only works once

    This post demonstrates the classic pit fall which often leads to many of us learning about Runtime Error and Runtime Error Handling VBA. That is certainly how I first came across it

    On Error GoTo LabelOrLineNumber only works once
    Correct. - We know that now, don't we?
    Just to be sure …. Consider the following codes.

    In words this is what the following two codes were initially intended to do:
    The idea is to loop through 5 numbers, 1 2 0 5 0 , and each one becomes the denominator in a simple equation dividing 10 by that denominator. ( In the actual data this such a looping would be expected to do these calculations 10/1 10/2 10/0 10/5 10/0 )
    We are expecting that there may be some zeros used in the 5 numbers which would result in an error of "divide by null" ( We actually included 2 zeros in the actual test data to test this and the codes reaction to those two 0s )
    So we thought we would do this:
    We have an error handler that goes to an error handling code section. At that code section we will include a message box which will tell us that we have a problem with the current number in the denominator. ( It will tell us that our current number is 0 )… Having informed of the problem number, we go back to consider the next number. ( To facilitate this we put a label, Nxt in the code , and we send the code back to there after the informing message box.
    Sounds easy, and we wrote these codes to do it

    Code:
    Sub OnErrorGoTo_OnlyWorksOnce()  '                                                                                '  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=10553&viewfull=1#post10553
     On Error GoTo ErHndler
    Dim MyNumberStearingForNextLoop As Variant '                                 Stearing element for a For Each loop must be Variant or Object Type
         For Each MyNumberStearingForNextLoop In Array(1, 2, 0, 5, 0) '          This is read and Array(1, 2, 0, 5, 0) held the first tim in Loopp register to be accesed at each loop
          MsgBox 10 / MyNumberStearingForNextLoop: Debug.Print 10 / MyNumberStearingForNextLoop
    Nxt: Next MyNumberStearingForNextLoop
    '
    Exit Sub ' Skip the "error handling code section" for a code run without an error - this never happens for this code
    ErHndler: ' The "error handling code section" is from here until the End ==
     MsgBox "Problem with number " & MyNumberStearingForNextLoop: Debug.Print "Problem with number " & MyNumberStearingForNextLoop
     GoTo Nxt
    End Sub
    Sub OnErrorGoTo_StillOnlyWorksOnce()
     On Error GoTo ErHndler
    Dim MyNumberStearingForNextLoop As Variant '
         For Each MyNumberStearingForNextLoop In Array(1, 2, 0, 5, 0) '
          MsgBox 10 / MyNumberStearingForNextLoop: Debug.Print 10 / MyNumberStearingForNextLoop
    Nxt: Next MyNumberStearingForNextLoop
    '
    Exit Sub  ' Skip the "error handling code section" for a code run without an error - this never happens for this code
    ErHndler: ' The "error handling code section" is from here until the End ==
     MsgBox "Problem with number " & MyNumberStearingForNextLoop: Debug.Print "Problem with number " & MyNumberStearingForNextLoop
     On Error GoTo ErHndler: ' This has no effect on the overal finctioning of the coding, as I am sexually aroused already,  in the State of Exception in Transalvania
     GoTo Nxt
    End Sub

    I think anyone who knows basic VBA but is not yet familiar with how VBA organises its error handling might intuitively expect that at least one of the codes will give these results, for example in the Immediate window (From the VB Editor Ctrl+g to get that window displayed)
    Code:
    10 
     5 
    Problem with number  0 
     2
    Problem with number  0
    The code almost does this, but we find that the codes stop via the standard default VBA error handling. It does this at the second time that an attempt is made to divide by 0
    This is because the exception was raised at the first attempt at dividing by 0 . ….
    Just to refresh our memories:
    The user predefined error handler , On Error GoTo ErHndler , is responsible for "embedding" the code in the Exception Software at the time of the error, starting at ErHndler. It does not simply "tell" VBA always to Go To ErHndler at every thing that causes an error.
    So the first code has no instruction to do any "re routing" again in the exception state***. The exception software, I assume, is wired to use the standard default error handling for further errors.
    *** Note importantly for later discussions: VBA does have the user defined error handling, On Error GoTo ErHndler , stored / registered, and will continue to use that, if we could get out of the exception state, ( which we can and that will be discussed later )
    Because we are in the exceptional state of aroused erection, any further attempts to set a user defined error handler are superfluous and ignored. Hence the second code also reacts with the standard default VBA Error handling at the second attempt at divide by zero: The second On Error GoTo ErHndler code line ( the one in the error handling code section is effectively simply ignored
    Last edited by DocAElstein; 03-21-2023 at 06:47 PM.

  6. #6
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    Resume Stuff in VBA error handling
    ( On Error Resume Next )


    Resume and Resume Next and Resume LabelOrLineNumber
    It turns out that the 3 resume statements are similar, but that the On Error Resume Next is, while having some similarities, not a simple intuitive derivative of the more fundamental resumes.

    Often the word resume will generally mean a restart or somehow continuing.. In VBA, Generally, anything using the word Resume has the effect of putting VBA into a state as it had been previously. An important part of anything being done with anything using Resume will be therefore to stop the exceptional state. Often this is referred to as clearing the exception. That is the important difference between the two main error handling statements: For On Error GoTo LabelOrLineNumber we still have an exceptionally aroused erection state ****
    Once again as it is important and is not intuitive: In VBA anything using the word Resume will usually clear the exception.
    On Error GoTo LabelOrLineNumber does not clear the exception.

    I don't know if the following derived way of looking at the resumes and then finally getting to On Error Resume Next , is anything like how VBA might do it, but it might be, and I felt like a change in the way of explaining.

    The goal is to produce something pretty dangerous and very unwise to do. This is often a feature generally of Microsoft Software, and as application programmers we have access to the tools to help us break things.

    We want a "blanket" error handler that just tells VBA to carry on at the next line after any error as if nothing had happened.
    From the previous discussions we think that an error does automatically kick in the exception software, but we have a chance to pseudo hang a hook on the chain of events to call back / Hold back procedures as this is possible generally in any Windows / Visual basic coding environment…
    I will assume that in the case of a On Error Resume Next I might want to know what error had occurred. ( In the first instance, if the exception is cleared, then so is the information in the Err object, so I will need to make some extra coding to get that info available again in Err. This will help us demo more aspects of error handling )
    ( **(On Error Resume Next )
    I might be inclined to call this the second user definable types of error handling statement and put this alongside the one of the Error Handling statements we already comsidered, On Error GoTo LabelOrLineNumber. One reason why I do this is that it does not seem to logically follow what might be expected based on the Resume Next, specifically,
    On Error Resume Next does not seem to clear the registers in object Err
    , but
    Resume Next does not seem to clear the registers in object Err
    Strange. This seemingly jumbled up logic may be one reason why the subject is not always understood fully
    )


    I believe the Resume is either the most , or pen ultimately most , fundamental step in what we are trying to achieve. It is interesting that one of the less common error handling statements , On Error GoTo -1 , has little earlier documentation, so I am not sure if it may be a derivative from Resume , which seems to have a more extensive documentation history.

    Resume ( and Resume Next and Resume LabelOrLineNumber) will syntax fail ( error themselves in runtime ) if no error has occurred.

    It is a good time perhaps to explain briefly the remaining error things, as they may be relevant to the final bad thing to have, On Error Resume Next , which will let us charge through like a blind dumb Bull in a china shop causing errors, breaking things un hindered throughout any code progression.

    On Error GoTo -1
    This clears the exception. This can be passed by a running code when the code is hunged embedded in the exception software running in the aroused erection, or in the normal un aroused code run. In the latter case , of "normal" code running, it has no effect. That is reasonable. In the exception case, it will effectively make the code continue in normal VBA mode in the current state using current back up exception Buffer data info retrieval.
    I do not know if there is any reasoning behind the use of -1. Certainly it confuses most people. It does not confuse me, it makes a strange logic… I often put a fictitious '-1 on the wrong side of Sub at the top. As far as errors are concerned I think of it as meaning that the code is pseudo at its non started state, in which case no exception can have been raised. But that is not a perfect analogy, since we do not restart the coding, but rather just carry on, “back in the real world”, at a point just after where the _ On Error GoTo -1 is. _ This is like the end of the diversion, where the coding between
    _ [ where the error occurred
    , to
    _ where the _ On Error GoTo -1
    _ ]
    is the diversion.

    Because _ On Error GoTo -1 _ effectively only “works” in the exception state, we might consider it an error handling ”thing”, or a tool we can use in error handling, as part of an error handler. Therefore it would be considered a different sort of thing to the On Error Resume Next or Resume LabelOrLineNumber
    Last edited by DocAElstein; 03-21-2023 at 08:06 PM.

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

    Error Handling statement Resumes Resumes resume

    Error Handling statement Resumes
    Resumes resume

    Resumes Introduction
    The word resume may be used generally to mean one of three similar code lines:
    Resume, Resume Next, Resume LabelOrLineNumber

    I am looking to mimic these things as a learning exercise and as a prerequisite for also mimicking the On Error Resume Next, (- but important to note here is the comment from the last post, ** , that it does not quite seem to follow the logic we might expect, such that the
    Resume Next

    ,and the
    Resume Next in _ On Error Resume Next
    , would appear to be slightly different )


    As noted, all of these, Resume, Resume Next, Resume LabelOrLineNumber , clear the exceptions, so part of what they effectively “do” is a On Error GoTo -1

    The other thing they do is Go To somewhere near the erroring code line, or a label or line number.
    Resume goes just before, and Resume Next goes just after an error.
    Resume LabelOrLineNumber goes where specified by the label or line number



    Resume ( and Resume Next and Resume LabelOrLineNumber ) will syntax fail ( error themselves in runtime ) if no error has occurred. So you must have an error initially, in which case you would be using the resumes in conjunction with an initial On Error GoTo LabelOrLineNumber to take you to an error handling code section where you could use the resume options. At that code section you could determine the current error if required, but you would need to do that before passing a resume statement.. because:

    Resume, Resume Next , Resume LabelOrLineNumber and Err object
    It appears that the resumes are not intended to keep track of what error occurred as the error object, Err, appears to be cleared of information following a resume.

    ( Somewhat surprisingly the On Error Resume Next does seem to keep information about the last error )

    User error handler to mimic Resume in code example
    See next post….. What we want to do is clear exceptions, so effectively “do” On Error GoTo -1
    Then, the other thing they do is Go To somewhere near the erroring code line, or specifically where given in LabelOrLineNumber .
    Resume should go just before, and Resume Next needs to go just after.
    Resume LabelOrLineNumber will go specifically were specified to specifically go to.
    We will have to consider the case of the information in the error object, Err, also. –
    ( ** As noted, after On Error Resume Next we appear to have information about the last error, whereas the more fundamental resume statements do not. .. strange )




    https://www.youtube.com/channel/UCnxwq2aGJRbjOo_MO54oaHA
    https://www.youtube.com/watch?v=f7xZivqLZxc&lc=Ugxq4JHRza_zx3sz0fx4AaABAg
    https://www.youtube.com/watch?v=f7xZivqLZxc&lc=UgzMCQUIQgrbec400jl4AaABAg
    https://www.youtube.com/watch?v=f7xZivqLZxc&lc=UgwhVTFaD469mW9wO194AaABAg. 9gJzxwFcnPU9gORqKw5tW_
    https://www.youtube.com/watch?v=f7xZivqLZxc&lc=Ugyb8nmKKoXvcdM58gV4AaABAg
    https://www.youtube.com/watch?v=f7xZivqLZxc&lc=UgwvvXcl1oa79xS7BAV4AaABAg
    https://www.youtube.com/watch?v=f7xZivqLZxc&lc=UgxvIFArksPprylHXYZ4AaABAg
    https://www.youtube.com/watch?v=f7xZivqLZxc&lc=Ugxq4JHRza_zx3sz0fx4AaABAg
    https://www.youtube.com/channel/UCnxwq2aGJRbjOo_MO54oaHA
    Last edited by DocAElstein; 07-11-2023 at 01:00 PM.

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

    Error Handling statements Resumes .. Error Handling statement Resume

    Error Handling statements Resumes
    Error Handling statement Resume


    Pseodo Resume Code
    Below is an attempt a code that does what the actual Resume does
    In the code are two lines which error.
    At each error line the exception is raised and the code becomes part of the exception software running from GetMilkLuv:

    As Resume takes us back to where the error occurred to, as it were, "try again" , then usually some attempt in the error handling would be done to prevent the error occurring again. ( That does not have to be the case: If one was expecting something external to occur which might prevent the code line erroring, then a resume without doing anything would be an option. However this is a very unadvisable use of Resume as it has the potential for causing an infinite looping if nothing prevents the error continuingly occurring. So the fist thing done at the error handler is giving a value to the be used in the denominator other than 0, so that 10 / TNominator no longer gives us an error.
    The line of the error then needs to be noted. We use for the first time here a method, Erl(). This is not clearly defined in any documentation. I expect this is some method used internally as needed, from within the Exception State, to return the last executed line in the “real world”/ normal coding before the error. It has therefore become known as a method or function to return the line that errored.
    This cannot be done after the next line, On Error GoTo -1 , as On Error GoTo -1 appears, in addition to its main purpose of clearing the exception, to additionally prevent the Erl function from giving us the line number of the last error.
    Note that On Error GoTo -1 has also removed the information in the Err object about the last error. Hence code line 55 gives us no information.
    Note that On Error GoTo -1 does not do the action of On Error GoTo 0. That is to say, the defined error handler is still "switched on" , or "pluged in and ready to be tripped by an error" as it were. One could say that it is deactivated. But it has not been "unplugged". Possibly you could think of it as the "trap being reset".
    The last part of the error handler is to determine where to go back to. It is quite messy and requires the use of line numbers so demonstrates one good reason for having a predefined Resume.
    Code:
    Sub PseudoResumeGoToGet5ButComeBackDarling()    '     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=10556&viewfull=1#post10556
    10    On Error GoTo GetMilkLuv
    20   Dim TNominator As Long, RslTwat As Long
    30   ' Other Code
    40    Let TNominator = 0
    50    Let RslTwat = 10 / TNominator
    55 MsgBox Err.Description ' This gives blank. On Erro GoTo -1 has cleared the Err object of infomation
    60   ' other code
    70    Let TNominator = 0
    80    Let RslTwat = 10 / TNominator
    90   ' 0ther code
    100  Exit Sub
    110 GetMilkLuv:  ' "Error handling Code section" is from here until the End
    120   Let TNominator = 5 ' get 5 to take back with you
    130  Dim errLine As Long: Let errLine = Erl ' this must be done before On Error GoTo -1 , as that clears the recorded error line
    140   On Error GoTo -1
    141 ' 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 an is present, in the Err object. it has no efffect on the actual error state
    145  MsgBox prompt:="We want to go back to the erroring line " & errLine & " and try again"
    150     If errLine = 10 Then
        GoTo 10:
        ElseIf errLine = 20 Then
        GoTo 20
        ElseIf errLine = 30 Then
        GoTo 30
        ElseIf errLine = 40 Then
        GoTo 40
        ElseIf errLine = 50 Then
        GoTo 50
        ElseIf errLine = 60 Then
        GoTo 60
        ElseIf errLine = 70 Then
        GoTo 70
        ElseIf errLine = 80 Then
        GoTo 80
        ElseIf errLine = 90 Then
        GoTo 90
        ElseIf errLine = 100 Then
        GoTo 100
        ElseIf errLine = 110 Then
        GoTo 110
        ElseIf errLine = 120 Then
        GoTo 120
        ElseIf errLine = 130 Then
        GoTo 130
        ElseIf errLine = 140 Then
        GoTo 140
        ElseIf errLine = 150 Then
        GoTo 150
        End If
    End Sub
    '
    The equivalent code using the VBA Resume statement is shown below:
    Code:
    Sub VBAResume()
     On Error GoTo GetMilkLuv
    Dim TNominator As Long, RslTwat As Long
    ' Other Code
     Let TNominator = 0
     Let RslTwat = 10 / TNominator
     MsgBox Err.Description ' This gives blank. On Erro GoTo -1 has cleared the Err object of infomation
    ' Other code
     Let TNominator = 0
     Let RslTwat = 10 / TNominator
    ' 0ther code
    Exit Sub
    GetMilkLuv:  ' "Error handling Code section" is from here until the End
     Let TNominator = 5 ' get 5 to take back with you
     MsgBox prompt:="We want to go back to the erroring line and try again"
     Resume
    End Sub
    '
    Last edited by DocAElstein; 03-23-2023 at 03:26 AM.

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

    Error Handling statement Resumes... Error Handling statement Resume Next

    Error Handling statement Resumes
    Error Handling statement Resume Next
    There is very little difference between these codes and the codes from the last post. The line that the error handler goes to is just offset by 1 row. ( I use Select Case instead of ElseIf for no particular reason ) In this case the ability to change something to avoid the error again is less useful as we are not going to “try again”, ( at least not at the point which errored ). But it can be useful, for example at the error handling code section to give some information.
    In the example, the information is given about the error type ( the line number is not available in the true Resume next which we are attempting to mimic). And the user is given the opportunity to continue or abort the code.

    Pseudo Resume Next Code

    Code:
    Sub PseudoResumeNextGoToGet5ButComeBackDarling()   '     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=10557&viewfull=1#post10557
    10    On Error GoTo GetMilkLuv
    20   Dim TNominator As Long, RslTwat As Long
    30   ' Other Code
    40    Let TNominator = 0
    50    Let RslTwat = 10 / TNominator
    55 MsgBox Err.Description ' This gives blank. On Erro GoTo -1 has cleared the Err object of infomation
    60   ' other code
    70    Let TNominator = 0
    80    Let RslTwat = 10 / TNominator
    90   ' 0ther code
    100  Exit Sub
    110 GetMilkLuv:  ' "Error handling Code section" is from here until the End
    120 Dim Answer As Long ' You could build this option in if you wanted to
    122  Let Answer = MsgBox(prompt:="Your code errored: " & Err.Description & vbCrLf & "Do you want to continue?", Buttons:=vbYesNo)
    124     If Answer = vbNo Then Exit Sub 'End code if user does not want to continue after error
    130  Dim errLine As Long: Let errLine = Erl ' this must be done before On Error GoTo -1 , as that clears the recorded error line
    140   On Error GoTo -1
    141 ' 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 an is present, in the Err object. it has no efffect on the actual error state
    145   MsgBox prompt:="We want to go back to just after the erroring line " & errLine
    150     Select Case errLine:
        Case 10: GoTo 20
        Case 20: GoTo 30
        Case 30: GoTo 40
        Case 40: GoTo 50
        Case 50: GoTo 55
        Case 55: GoTo 60
        Case 60: GoTo 70
        Case 70: GoTo 80
        Case 80: GoTo 90
        Case 90: GoTo 100
        Case 100: GoTo 110
        Case 110: GoTo 120
        Case 120: GoTo 130
        Case 130: GoTo 140
        Case 140: GoTo 150
        End Select
    End Sub


    Here the code using the actual VBA Resume Next error handling statement is used to do the same as the previous code .
    Code:
    Sub VBAResumeNext()   '    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=10557&viewfull=1#post10557
     On Error GoTo GetMilkLuv
    Dim TNominator As Long, RslTwat As Long
    ' Other Code
     Let TNominator = 0
     Let RslTwat = 10 / TNominator
     MsgBox Err.Description ' This gives blank.
    ' Other code
     Let TNominator = 0
     Let RslTwat = 10 / TNominator
    ' 0ther code
    Exit Sub
    GetMilkLuv:  ' "Error handling Code section" is from here until the End
    Dim Answer As Long
     Let Answer = MsgBox(prompt:="Your code errored: " & Err.Description & vbCrLf & "Do you want to continue?", Buttons:=vbYesNo)
        If Answer = vbNo Then Exit Sub 'End code if user does not want to continue after error
     MsgBox prompt:="We want to go back to just after the erroring line, and so ignore the error"
     Resume Next
    End Sub
    Last edited by DocAElstein; 03-23-2023 at 08:42 PM.

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

    Handling statement Resumes .. Error Handling statement Resume LabelOrLineNumber

    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
    Last edited by DocAElstein; 03-23-2023 at 09:21 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
  •