Page 2 of 6 FirstFirst 1234 ... LastLast
Results 11 to 20 of 52

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

  1. #11
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,459
    Rep Power
    10
    Post #10 on page #1 https://excelfox.com/forum/showthrea...ll=1#post10558






    Error Handling statement Resumes
    On Error Resume Next

    The next posts will look at the second main Error handling statement , On Error Resume Next .
    Every time I look at this, I come up with a slightly different idea. To some extent I may be going back and forwards, fluctuating a bit, bit on average I am perfecting the understanding a bit better.
    If I try, as I have done in the past, to discus the more fundamental general idea of the Resume .
    And build on that, to derive user defined error handlers that works in a similar way, things don’t come outs quite as logically as one might expect. .

    In my opinion the whole VBA error handling is an unintuitive mess. In the unlikely event that you have read and understood most of my previous ramblings, then a couple logical conclusion might be the following:

    _ We might reasonably guess that there is no On Error Resume
    This is because that would imply that at an error the code tries again. And again. And again And again. And again.. … Conceivable there might be a situation where that might work if some external influence meant that the code line erroring suddenly didn't. But that is unlikely. More likely is that having such an option would cause the attempt at an infinite loop or retrying.
    In fact that assumption is correct. There is no On Error Resume

    _ We might reasonably guess that there might be a On Error Resume LabelOrLineNumber
    That would be a reasonable thing to do. But there isn’t. Perhaps this should slightly spark our suspicions.

    Indeed we find the On Error Resume Next is not quite doing _ On Error ……… then …. Resume Next. Almost it does. It does both
    _ carry on after the line causing the error
    , and
    _ it appears to not be in The State of Exception
    But here is the oddity. The error object, Err , is not cleared and so can still be used to tell us what error did occur , (and the Erl() also tells us the last line number that errored )




    On Error Resume Next is very commonly used ( badly in the opinion of most professionals) to just keep a coding going despite any errors
    This simplest use is shown in the next macro. All errors are ignored.

    Code:
    Sub OnErrorResumeNext1()  '  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=10559&viewfull=1#post10559
    0 Dim Ex As Double
    10 On Error Resume Next
    
    20 Let Ex = 1 / 0
    30 MsgBox prompt:=Err.Description & ",  at line number" & Erl(): Debug.Print Err.Description & ",  at line number" & Erl()
    
    40 Let Ex = 1 / 0
    50 MsgBox prompt:=Err.Description & ",  at line number" & Erl(): Debug.Print Err.Description & ",  at line number" & Erl()
    End Sub
    '
    The output is like
    Division durch Null, at line number20
    Division durch Null, at line number40
    Last edited by DocAElstein; 03-23-2023 at 11:41 PM.

  2. #12
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,459
    Rep Power
    10
    Codes for On Error Resume Next

    Pseudo On Error Resume Next - Considerations

    A convenient way to show this would involve the Return Next. A less convenient way would be to use a macro with line numbers , since the Return Next itself was shown using a pseudo code involving line numbers. ( https://excelfox.com/forum/showthrea...ll=1#post10557 Sub PseudoResumeNextGoToGet5ButComeBackDarling() )
    The basic thing going on is the same – we want a way to go back and carry on at the error, but as we noted there are some subtle unexpected differences in how
    On Error Resume Next , is working
    , and how we would expect perhaps something of the form
    On Error …. Do effectively at the point of error ….Resume Next
    , to work. So it may help avoid confusing the two to just do a single macro, the more fundamental one, using the code lines.

    Difference On Error Resume Next and On Error …. Do effectively at the point of error …. Resume Next
    This macro for Pseudo On Error Resume Next will be very similar to that for Pseudo Return Next ( https://excelfox.com/forum/showthrea...ll=1#post10557 Sub PseudoResumeNextGoToGet5ButComeBackDarling() ) The main difference, and the very important difference is that we must add some coding to capture the Err and Erl() information, (at least some of the Err information just as way of demonstration). It is the availability of this information after the error that makes the On Error Resume Next not as we might expect from considering it as a On Error …. Do effectively at the point of error ….Resume Next, since a Resume Next clears this information.

    For demonstration purposes, we will use the variable, errLine, to store, and then use to represent the Erl() in a true On Error Resume Next. We did this in previous macros.
    We could do the same for the property of the Err object that we are using in the demonstration, Err.Description . For example we could do something like
    Code:
    Dim Err_Description As String: Let Err_Description = Err.Description
    On Error GoTo -1  '  We want this to take us out of the  State of Exception  , but for the case of demonstrating how  On Error Resume Next  works, we don't want the extra feature of clearing the  Err  object
     Let Err.Description = Err_Description    '
    
    Thereafter, we would use in our pseudo coding for demonstration repurposes, Err_Description to represent the true property Err.Description
    However we have another possibility in the case of the error object, Err . - in the case of the error object, Err , we only need to do that temporarily until just after we do the On Error GoTo -1 , since thereafter we can re assign the Err.Description, since , perhaps strangely, the error object, Err , is not just read only, as is the Erl(), and as logically we might have similarly expected that the Err should be. So alternatively we could do something like this
    Code:
    Dim TempErrDesc As String: Let TempErrDesc = Err.Description
    On Error GoTo -1                         '  We want this to take us out of the  State of Exception  , but for the case of demonstrating how   On Error Resume Next   works, we don't want the extra feature of clearing the  Err  object
     Let Err.Description = TempErrDesc    '     in the case of the error object,  Err  , we only need temporarily store the  Err   properties until just after we do the On Error GoTo -1 , since thereafter we can re assign, for example, the   Err.Description   , since , perhaps strangely, the error object,   Err   , is not just read only, as is the   Erl()    , and as logically we might have similarly expected that the   Err   would be
    
    Thereafter we can access properties** just as previously and normally from the actual error object, Err , itself. ( ** For a simplified demonstration I am only considering the .Derscription but you could use the same way , (of temporarily storing then re assigning after the On Error Goto -1 ) , for all the properties. )



    Full pseudo code . ( ** For a simplified demonstration I am only considering the .Derscription for the Err, but you could use the same way , (of temporarily storing then re assigning after the On Error Goto -1 ) , for all the properties. )
    __ …..see next post ……_
    Last edited by DocAElstein; 03-24-2023 at 04:04 PM.

  3. #13
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,459
    Rep Power
    10
    Codes for On Error Resume Next
    ¬_.... from last post



    Full pseudo code . ( ** For a simplified demonstration I am only considering the .Derscription for the Err, but you could use the same way , (of temporarily storing then re assigning after the On Error Goto -1 ) , for all the properties. )
    Code:
    Sub PseudoOnErrorResumeNextGoToGet5ButComeBackDarling()   '      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=19875&viewfull=1#post19875
    10    On Error GoTo ResNxt
    20   Dim TNominator As Long, RslTwat As Long, errline As String
    30   ' Other Code
    40    Let TNominator = 0
    50    Let RslTwat = 10 / TNominator
    55 MsgBox Err.Description ' This does not give blank, as it would after a  Resume Next
    56 MsgBox errline         ' This effectively gives the line where the last error occured
    60   ' other code
    70    Let TNominator = 0
    80    Let RslTwat = 10 / TNominator
    90   ' 0ther code
    100  Exit Sub
    110 ResNxt:  ' "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  Let errline = Erl ' this must be done before On Error GoTo -1 , as that clears the recorded error line
    132 Dim TempErrDesc As String: Let TempErrDesc = Err.Description ' '_-In the case of the error object, Err , we only need to do that temporarily until just after we do the  On Error GoTo -1 , since thereafter we can re assign the Err.Description,  since , perhaps strangely, the error object, Err , is not just read only, as is the Erl(), and as logically we might have similarly expected that the Err should be
    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 effect on the actual error state
    143 Let Err.Description = TempErrDesc    '                         '_-In the case of the error object, Err , we only need to do that temporarily until just after we do the  On Error GoTo -1 , since thereafter we can re assign the Err.Description,  since , perhaps strangely, the error object, Err , is not just read only, as is the Erl(), and as logically we might have similarly expected that the Err should be
    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
    










    Just for the sake of comparison, and to emphasise the , perhaps unexpected required differences, I include again the previous pseudo coding for the Resume Next. In the pseudo coding done for the On Error Resume Next, above, I have made orange the most important differences. Those two most important differences are, in words,
    _(i) the Error object , Err , does not get cleared in On Error Resume Next as it does in Resume Next
    _(ii) related to (i), we can re assign the properties of the Error object , Err ( In either the normal code state or the in the State of Exception, so for the demo coding can use the real Err after, getting properties from it, rather than assigning, and using, variables for the various Err properties )

    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
    Last edited by DocAElstein; 03-24-2023 at 05:17 PM.

  4. #14
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,459
    Rep Power
    10
    Some Notes on On Error Resume Next usage
    On Error Resume Next is bad
    It is like a dumb blind Bull in a china shop, with the exception that some coding at least notes what error was last hidden.
    Usually the advice is to only use an On Error Resume Next when you are expecting an error but can’t think of any other way to check for it that does not raise an exception . Further you should then use the On Error GoTo 0 as soon as possible after to remove the error handler ( “turn it off”, “un plug it”, disable it )
    Remember we can do this On Error GoTo 0 at any point even after the On Error Resume Next has been used, as the exception is cleared by On Error Resume Next (Actually, On Error GoTo 0 can also be used in the exception state and also disables the error handler but has no noticeable effect if the exception is still raised )
    Both On Error GoTo -1 and On Error GoTo 0 clear the Err object
    It was perhaps reasonable to expect that On Error GoTo -1 cleared the information from the Err object. It may not be so obvious that On Error GoTo 0 also does this. So if you wanted to use a check on the Err properties after an On Error Resume Next in order to ascertain if and what error had been “hidden” , then you must do that before any On Error GoTo 0 or On Error GoTo -1.

    On Error GoTo -1 and Err.Clear clear the Err object of information
    As we noted above, initially one might think that On Error GoTo -1 has no useful function when a On Error Resume Next is in place, as effectively any resume type statement effectively does On Error GoTo -1, but for the unique case of On Error Resume Next which maintains the Err properties of the last error, the use of On Error GoTo -1 gives the possibility to clear the properties of the Err object, without disabling the error handler. But note, that the method Clear, that is to say Err.Clear, can also be used to do that.
    But you never know, some crazy combination of all the statements might best suit some messy system



    On Error Resume Next is bad. In most cases there is a better alternative to using On Error Resume Next .
    Often it is a quick workaround. That tends to be how I have used it.
    I don’t think I should have used it in such cases.
    _a) By definition a work a round is bad.
    _ b) Often it is jus ignorance as I don’t know ( yet ) the alternatives

    In the next posts are some example of how I am using it. Maybe I will add to them, or give the better alternative not using error handling, if I ever figure it out.
    Maybe from time to time I will add other examples of error handling generally, and welcome any comments or additions
    Last edited by DocAElstein; 03-24-2023 at 06:59 PM.

  5. #15
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,459
    Rep Power
    10
    hhh
    Last edited by DocAElstein; 03-24-2023 at 05:41 PM.

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

    Some Notes on On Error Resume Next usage

    Late Early Binding.
    Only very rarely there are advantages in using Early Binding in preference to late Binding in a final shared File. For development the Early Binding is often preferable as this somehow seems to make an initial link or reference such that intellisense knows what is available. This requires however the checking of a library in the _ VB Editor – - - Tools – - - references _ list
    The Late Binding alternative uses the CreateObject Method whose (“string”) argument , ignored by compile , is used at run time to “find” the library of the given name.
    Well… I had some existing files which had a lot of Early Binding, and for the time being I did not want to change them.
    The current problem example had an Early Binding reference to Word, done on a Office 2007 machine.
    I got broken reference errors then on 2010 office versions. I also wanted the File to work in Excel 2003

    I found by a bit of experimenting and Forum involvement _..
    https://www.excelforum.com/developme...ml#post4820111
    https://www.excelforum.com/excel-pro...ml#post4821675
    _.. that a Globally Unique Identifier (GUID) appeared a fairly reliable to reference the appropriate libraries. A short code I found could be reliably used to check the reference programmatically via its GUID.
    I don’t know yet if there is a good reference list for all GUIDs, but a simple code I could use to get a list of my checked references. For my example I checked the reference to Word on different Office versions and ran this code:




    Code:
    Sub RefItsGUIDsAndStuff()
    Dim It As Variant
      For Each It In ThisWorkbook.VBProject.References
      Dim strIts As String
       Let strIts = strIts & "Description:" & vbTab & It.Description & vbCr & "Name:" & vbTab & vbTab & It.Name & vbCr & "Buitin:" & vbTab & vbTab & It.BuiltIn & vbCr & "Minor:" & vbTab & vbTab & It.minor & vbCr & "Major:" & vbTab & vbTab & It.major & vbCr & "FullPath:" & vbTab & vbTab & It.fullpath & vbCr & "GUID:" & vbTab & vbTab & It.GUID & vbCr & "Type:" & vbTab & vbTab & It.Type & vbCr & "Isbroken:" & vbTab & vbTab & It.isbroken & vbCr & vbCr
      Next It
    Debug.Print strIts ' From  VB Editor Ctrl+g  to Immediate Window
    End Sub
    Some results for different Excel Versions

    Code:
    Excel 2007
    Description:    Visual Basic For Applications
    Name:       VBA
    Buitin:     Wahr
    Minor:      0
    Major:      4
    FullPath:       C:\Program Files\Common Files\Microsoft Shared\VBA\VBA6\VBE6.DLL
    GUID:       {000204EF-0000-0000-C000-000000000046}
    Type:       0
    Isbroken:       Falsch
    
    Description:    Microsoft Excel 12.0 Object Library
    Name:       Excel
    Buitin:     Wahr
    Minor:      6
    Major:      1
    FullPath:       C:\Program Files\Microsoft Office\Office12\EXCEL.EXE
    GUID:       {00020813-0000-0000-C000-000000000046}
    Type:       0
    Isbroken:       Falsch
    
    Description:    OLE Automation
    Name:       stdole
    Buitin:     Falsch
    Minor:      0
    Major:      2
    FullPath:       C:\Windows\system32\stdole2.tlb
    GUID:       {00020430-0000-0000-C000-000000000046}
    Type:       0
    Isbroken:       Falsch
    
    Description:    Microsoft Office 12.0 Object Library
    Name:       Office
    Buitin:     Falsch
    Minor:      4
    Major:      2
    FullPath:       C:\Program Files\Common Files\Microsoft Shared\OFFICE12\MSO.DLL
    GUID:       {2DF8D04C-5BFA-101B-BDE5-00AA0044DE52}
    Type:       0
    Isbroken:       Falsch
    
    Description:    Microsoft Forms 2.0 Object Library
    Name:       MSForms
    Buitin:     Falsch
    Minor:      0
    Major:      2
    FullPath:       C:\Windows\system32\FM20.DLL
    GUID:       {0D452EE1-E08F-101A-852E-02608C4D0BB4}
    Type:       0
    Isbroken:       Falsch
    
    Description:    Microsoft Scripting Runtime
    Name:       Scripting
    Buitin:     Falsch
    Minor:      0
    Major:      1
    FullPath:       C:\Windows\system32\scrrun.dll
    GUID:       {420B2830-E718-11CF-893D-00A0C9054228}
    Type:       0
    Isbroken:       Falsch
    
    Description:    Microsoft Word 12.0 Object Library
    Name:       Word
    Buitin:     Falsch
    Minor:      4
    Major:      8
    FullPath:       C:\Program Files\Microsoft Office\Office12\MSWORD.OLB
    GUID:       {00020905-0000-0000-C000-000000000046}
    Type:       0
    Isbroken:       Falsch
    
    Excel 2003
    
    Description:    Visual Basic For Applications
    Name:       VBA
    Buitin:     Wahr
    Minor:      0
    Major:      4
    FullPath:       C:\Program Files\Common Files\Microsoft Shared\VBA\VBA6\VBE6.DLL
    GUID:       {000204EF-0000-0000-C000-000000000046}
    Type:       0
    Isbroken:       Falsch
    
    Description:    Microsoft Excel 11.0 Object Library
    Name:       Excel
    Buitin:     Wahr
    Minor:      5
    Major:      1
    FullPath:       C:\Program Files\Microsoft Office\OFFICE11\EXCEL.EXE
    GUID:       {00020813-0000-0000-C000-000000000046}
    Type:       0
    Isbroken:       Falsch
    
    Description:    OLE Automation
    Name:       stdole
    Buitin:     Falsch
    Minor:      0
    Major:      2
    FullPath:       C:\Windows\system32\stdole2.tlb
    GUID:       {00020430-0000-0000-C000-000000000046}
    Type:       0
    Isbroken:       Falsch
    
    Description:    Microsoft Office 11.0 Object Library
    Name:       Office
    Buitin:     Falsch
    Minor:      3
    Major:      2
    FullPath:       C:\Program Files\Common Files\Microsoft Shared\OFFICE11\MSO.DLL
    GUID:       {2DF8D04C-5BFA-101B-BDE5-00AA0044DE52}
    Type:       0
    Isbroken:       Falsch
    
    Description:    Microsoft Word 12.0 Object Library
    Name:       Word
    Buitin:     Falsch
    Minor:      4
    Major:      8
    FullPath:       C:\Program Files\Microsoft Office\Office12\MSWORD.OLB
    GUID:       {00020905-0000-0000-C000-000000000046}
    Type:       0
    Isbroken:       Falsch
    
    
    Excel 2010
    Description:    Visual Basic For Applications
    Name:       VBA
    Buitin:     Wahr
    Minor:      1
    Major:      4
    FullPath:       C:\PROGRA~2\COMMON~1\MICROS~1\VBA\VBA7\VBE7.DLL
    GUID:       {000204EF-0000-0000-C000-000000000046}
    Type:       0
    Isbroken:       Falsch
     
    Description:    Microsoft Excel 14.0 Object Library
    Name:       Excel
    Buitin:     Wahr
    Minor:      7
    Major:      1
    FullPath:       C:\Program Files (x86)\Microsoft Office\Office14\EXCEL.EXE
    GUID:       {00020813-0000-0000-C000-000000000046}
    Type:       0
    Isbroken:       Falsch
     
    Description:    OLE Automation
    Name:       stdole
    Buitin:     Falsch
    Minor:      0
    Major:      2
    FullPath:       C:\Windows\SysWOW64\stdole2.tlb
    GUID:       {00020430-0000-0000-C000-000000000046}
    Type:       0
    Isbroken:       Falsch
     
    Description:    Microsoft Office 14.0 Object Library
    Name:       Office
    Buitin:     Falsch
    Minor:      5
    Major:      2
    FullPath:       C:\Program Files (x86)\Common Files\Microsoft Shared\OFFICE14\MSO.DLL
    GUID:       {2DF8D04C-5BFA-101B-BDE5-00AA0044DE52}
    Type:       0
    Isbroken:       Falsch
     
    Description:    Microsoft Word 14.0 Object Library
    Name:       Word
    Buitin:     Falsch
    Minor:      5
    Major:      8
    FullPath:       C:\Program Files (x86)\Microsoft Office\Office14\MSWORD.OLB
    GUID:       {00020905-0000-0000-C000-000000000046}
    Type:       0
    Isbroken:       Falsch
    
    I use the following codes to add programmatically the reference. ( The codes are in the ThisWorkbook code module). The reason for the error handler is that I cannot know if the check has already be made where the File might be in use. I think I can only check references that are made. The code would error at the attempt to check a reference already checked.
    I could do the following which would be very simple: _ ….
    Code:
       With ThisWorkbook.VBProject.References
        On Error Resume Next '
        .AddFromguid GUID:="{00020905-0000-0000-C000-000000000046}", major:=8, minor:=4 ' Office 2003
        .AddFromguid GUID:="{00020905-0000-0000-C000-000000000046}", major:=8, minor:=4 ' Office 2007
        .AddFromguid GUID:="{00020905-0000-0000-C000-000000000046}", major:=8, minor:=5 ' Office 2010
        On Error GoTo 0
       End With
    _.. Typically, and a bad habit, is to use On Error Resume Next for convenience as above


    With this following code, I have at least narrowed the chances of the code errorong
    Code:
       With ThisWorkbook.VBProject.References
        On Error Resume Next '
           Select Case CLng(Val(Application.Version))
            Case 9: ' Excel 2000
            Case 10: ' Excel 2002
            Case 11: .AddFromguid GUID:="{00020905-0000-0000-C000-000000000046}", major:=8, minor:=4 ' Office 2003
            Case 12: .AddFromguid GUID:="{00020905-0000-0000-C000-000000000046}", major:=8, minor:=4 ' Office 2007
            Case 14: .AddFromguid GUID:="{00020905-0000-0000-C000-000000000046}", major:=8, minor:=5 ' Office 2010
            Case 15: temp = "Excel 2013"
            Case 16: temp = "Excel 2016 (Windows)"
            Case Else: temp = "Unknown"
           End Select
        On Error GoTo 0
       End With
    Last edited by DocAElstein; 03-24-2023 at 07:06 PM.

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

    Some Notes on On Error Resume Next usage

    hchchc
    Last edited by DocAElstein; 03-21-2023 at 12:44 AM.
    A Folk, A Forum, A Fuhrer ….

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

    Some Notes on On Error Resume Next usage

    mv yvmvm
    Last edited by DocAElstein; 03-21-2023 at 12:45 AM.
    A Folk, A Forum, A Fuhrer ….

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

    Some Notes on On Error Resume Next usage

    cjjcc
    Last edited by DocAElstein; 03-21-2023 at 12:45 AM.
    A Folk, A Forum, A Fuhrer ….

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

    Err object. Err.Raise. Custom Error handler

    Here is a link to the second but last post in Page 2, #19 ,
    https://excelfox.com/forum/showthrea...ll=1#post19889

    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






    Err object. Err.Raise. Custom Error handler


    One possible last area of VBA error things that can be considered is the possibility to raise an exception without actually having a code line that causes an error to occur, and possibly to modify the responses, or rather the given details of the error from the VBA default error handler pop up message
    I am guessing that this means that you can cause the Exception software to start, or start that software running in a similar way to which it would automatically be triggered by an actual error occurring.
    It seems that a few Blogs are not quite clear on exactly what this is about. I don’t think anyone quite remembers anymore exactly what it does. Certainly no one knows the things about the arguments that I think I do and probably don’t.
    It is probably therefore a good idea to tackle this in two parts. First Part 1), an investigation into what the Err object and in particulate the Method .Raise is, and then Part 2), using it in a “Custom Error handler”
    Last edited by DocAElstein; 03-24-2023 at 07:12 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
  •