Error-Handling Class and Logging for VBA











up vote
3
down vote

favorite
1












I've been reusing an error class in Excel VBA projects for a few years now and I'd like to see if there are ways to improve it. Any suggestions for style, code, etc. are all welcome.



The 2 procedures I'd like to focus on are:




  • Error_Handler.DisplayMessage

  • Error_Handler.Log


The log file is usually written to a file server so multiple users can access it. I have changed the log path to C:Temp for this example. I use BareTail to read the log file.



I use Custom Document Properties to store settings for the file/Add-in




An example of a project I use the Error Handler class and logging in is on GitHub. For reference, I am using Excel 2016 on Windows 7.






Error_Handler Class



Attribute VB_Name = "Error_Handler"
'====================================================================================================================
' Purpose: Error trapping class
'====================================================================================================================
Option Explicit

Public App As MyAppInfo

Public Type MyAppInfo
Name As String
ReleaseDate As Date
Version As String
End Type

Private Const MyModule As String = "Error_Handler"

Public Sub Load()
On Error GoTo ErrTrap

App.Name = ThisWorkbook.CustomDocumentProperties("App_Name").Value
App.ReleaseDate = ThisWorkbook.CustomDocumentProperties("App_ReleaseDate").Value
App.Version = ThisWorkbook.CustomDocumentProperties("App_Version").Value

ExitProcedure:
On Error Resume Next
Exit Sub

ErrTrap:
Select Case Err.number
Case Is <> 0
Error_Handler.DisplayMessage "Load", MyModule, Err.number, Err.description
Resume ExitProcedure
Case Else
Resume ExitProcedure
End Select

End Sub

Public Sub DisplayMessage( _
ByVal procedure As String _
, ByVal module As String _
, ByVal number As Double _
, ByVal description As String _
, Optional ByVal line As Variant = 0 _
, Optional ByVal title As String = "Unexpected Error" _
, Optional ByVal createLog As Boolean = True)
'====================================================================================================================
' Purpose: Global error message for all procedures
' Example: Error_Handler.DisplayMessage "Assembly_Info", "Load", 404, "Error Message Here...", 1, "Error Description"
'====================================================================================================================
On Error Resume Next
Dim msg As String

msg = "Contact your system administrator."
msg = msg & vbCrLf & "Module: " & module
msg = msg & vbCrLf & "Procedure: " & procedure
msg = msg & IIf(line = 0, "", vbCrLf & "Error Line: " & line)
msg = msg & vbCrLf & "Error #: " & number
msg = msg & vbCrLf & "Error Description: " & description
If createLog Then
Log module, procedure, number, description
End If
MsgBox msg, vbCritical, title

End Sub

Public Sub Log( _
ByVal module As String _
, ByVal procedure As String _
, ByVal number As Variant _
, ByVal description As String)
'====================================================================================================================
' Purpose: Creates a log file and record of the error
' Example: Error_Handler.Log "Assembly_Info", "Load", "404", "Error Message Here..."
'====================================================================================================================
On Error GoTo ErrTrap
Dim fileSizeMax As Double: fileSizeMax = 1024 ^ 2 'archive the file over 1mb
Dim AppName As String: AppName = LCase(Replace(App.Name, " ", "_"))
Dim fileName As String: fileName = "C:tempexcel_addin." & AppName & ".log"
Dim fileNumber As Variant: fileNumber = FreeFile
Const dateFormat As String = "yyyy.mm.dd_hh.nn.ss"

If Dir(fileName) <> "" Then
If FileLen(fileName) > fileSizeMax Then 'archive the file when it's too big
FileCopy fileName, Replace(fileName, ".log", Format(Now, "_" & dateFormat & ".log"))
Kill fileName
End If
End If

Open fileName For Append As #fileNumber
Print #fileNumber, CStr(Format(Now, dateFormat)) & _
"," & Environ("UserName") & _
"," & Environ("ComputerName") & _
"," & Application.OperatingSystem & _
"," & Application.Version & _
"," & App.Version & _
"," & Format(App.ReleaseDate, "yyyy.mm.dd_hh.nn.ss") & _
"," & ThisWorkbook.FullName & _
"," & module & _
"," & procedure & _
"," & number & _
"," & description

ExitProcedure:
On Error Resume Next
Close #fileNumber
Exit Sub

ErrTrap:
Select Case Err.number
Case Is <> 0
Debug.Print "Module: " & module & " |Procedure: " & procedure & " |Error #: " & number & " |Error Description: " & description
Resume ExitProcedure
Case Else
Resume ExitProcedure
End Select

End Sub


Usage Example:



Public Function GetItem(ByVal col As Variant, ByVal key As Variant) As Variant
On Error GoTo ErrTrap

Set GetItem = col(key)

ExitProcedure:
On Error Resume Next
Exit Function

ErrTrap:
Select Case Err.number
Case Is = 9 'subscript out of range = this column does not exist in the active table
Set GetItem = Nothing
Resume ExitProcedure
Case Is <> 0
Error_Handler.DisplayMessage "GetItem", "Example_Module", Err.number, Err.description
Set GetItem = Nothing
Resume ExitProcedure
Case Else
Resume ExitProcedure
End Select

End Function









share|improve this question




























    up vote
    3
    down vote

    favorite
    1












    I've been reusing an error class in Excel VBA projects for a few years now and I'd like to see if there are ways to improve it. Any suggestions for style, code, etc. are all welcome.



    The 2 procedures I'd like to focus on are:




    • Error_Handler.DisplayMessage

    • Error_Handler.Log


    The log file is usually written to a file server so multiple users can access it. I have changed the log path to C:Temp for this example. I use BareTail to read the log file.



    I use Custom Document Properties to store settings for the file/Add-in




    An example of a project I use the Error Handler class and logging in is on GitHub. For reference, I am using Excel 2016 on Windows 7.






    Error_Handler Class



    Attribute VB_Name = "Error_Handler"
    '====================================================================================================================
    ' Purpose: Error trapping class
    '====================================================================================================================
    Option Explicit

    Public App As MyAppInfo

    Public Type MyAppInfo
    Name As String
    ReleaseDate As Date
    Version As String
    End Type

    Private Const MyModule As String = "Error_Handler"

    Public Sub Load()
    On Error GoTo ErrTrap

    App.Name = ThisWorkbook.CustomDocumentProperties("App_Name").Value
    App.ReleaseDate = ThisWorkbook.CustomDocumentProperties("App_ReleaseDate").Value
    App.Version = ThisWorkbook.CustomDocumentProperties("App_Version").Value

    ExitProcedure:
    On Error Resume Next
    Exit Sub

    ErrTrap:
    Select Case Err.number
    Case Is <> 0
    Error_Handler.DisplayMessage "Load", MyModule, Err.number, Err.description
    Resume ExitProcedure
    Case Else
    Resume ExitProcedure
    End Select

    End Sub

    Public Sub DisplayMessage( _
    ByVal procedure As String _
    , ByVal module As String _
    , ByVal number As Double _
    , ByVal description As String _
    , Optional ByVal line As Variant = 0 _
    , Optional ByVal title As String = "Unexpected Error" _
    , Optional ByVal createLog As Boolean = True)
    '====================================================================================================================
    ' Purpose: Global error message for all procedures
    ' Example: Error_Handler.DisplayMessage "Assembly_Info", "Load", 404, "Error Message Here...", 1, "Error Description"
    '====================================================================================================================
    On Error Resume Next
    Dim msg As String

    msg = "Contact your system administrator."
    msg = msg & vbCrLf & "Module: " & module
    msg = msg & vbCrLf & "Procedure: " & procedure
    msg = msg & IIf(line = 0, "", vbCrLf & "Error Line: " & line)
    msg = msg & vbCrLf & "Error #: " & number
    msg = msg & vbCrLf & "Error Description: " & description
    If createLog Then
    Log module, procedure, number, description
    End If
    MsgBox msg, vbCritical, title

    End Sub

    Public Sub Log( _
    ByVal module As String _
    , ByVal procedure As String _
    , ByVal number As Variant _
    , ByVal description As String)
    '====================================================================================================================
    ' Purpose: Creates a log file and record of the error
    ' Example: Error_Handler.Log "Assembly_Info", "Load", "404", "Error Message Here..."
    '====================================================================================================================
    On Error GoTo ErrTrap
    Dim fileSizeMax As Double: fileSizeMax = 1024 ^ 2 'archive the file over 1mb
    Dim AppName As String: AppName = LCase(Replace(App.Name, " ", "_"))
    Dim fileName As String: fileName = "C:tempexcel_addin." & AppName & ".log"
    Dim fileNumber As Variant: fileNumber = FreeFile
    Const dateFormat As String = "yyyy.mm.dd_hh.nn.ss"

    If Dir(fileName) <> "" Then
    If FileLen(fileName) > fileSizeMax Then 'archive the file when it's too big
    FileCopy fileName, Replace(fileName, ".log", Format(Now, "_" & dateFormat & ".log"))
    Kill fileName
    End If
    End If

    Open fileName For Append As #fileNumber
    Print #fileNumber, CStr(Format(Now, dateFormat)) & _
    "," & Environ("UserName") & _
    "," & Environ("ComputerName") & _
    "," & Application.OperatingSystem & _
    "," & Application.Version & _
    "," & App.Version & _
    "," & Format(App.ReleaseDate, "yyyy.mm.dd_hh.nn.ss") & _
    "," & ThisWorkbook.FullName & _
    "," & module & _
    "," & procedure & _
    "," & number & _
    "," & description

    ExitProcedure:
    On Error Resume Next
    Close #fileNumber
    Exit Sub

    ErrTrap:
    Select Case Err.number
    Case Is <> 0
    Debug.Print "Module: " & module & " |Procedure: " & procedure & " |Error #: " & number & " |Error Description: " & description
    Resume ExitProcedure
    Case Else
    Resume ExitProcedure
    End Select

    End Sub


    Usage Example:



    Public Function GetItem(ByVal col As Variant, ByVal key As Variant) As Variant
    On Error GoTo ErrTrap

    Set GetItem = col(key)

    ExitProcedure:
    On Error Resume Next
    Exit Function

    ErrTrap:
    Select Case Err.number
    Case Is = 9 'subscript out of range = this column does not exist in the active table
    Set GetItem = Nothing
    Resume ExitProcedure
    Case Is <> 0
    Error_Handler.DisplayMessage "GetItem", "Example_Module", Err.number, Err.description
    Set GetItem = Nothing
    Resume ExitProcedure
    Case Else
    Resume ExitProcedure
    End Select

    End Function









    share|improve this question


























      up vote
      3
      down vote

      favorite
      1









      up vote
      3
      down vote

      favorite
      1






      1





      I've been reusing an error class in Excel VBA projects for a few years now and I'd like to see if there are ways to improve it. Any suggestions for style, code, etc. are all welcome.



      The 2 procedures I'd like to focus on are:




      • Error_Handler.DisplayMessage

      • Error_Handler.Log


      The log file is usually written to a file server so multiple users can access it. I have changed the log path to C:Temp for this example. I use BareTail to read the log file.



      I use Custom Document Properties to store settings for the file/Add-in




      An example of a project I use the Error Handler class and logging in is on GitHub. For reference, I am using Excel 2016 on Windows 7.






      Error_Handler Class



      Attribute VB_Name = "Error_Handler"
      '====================================================================================================================
      ' Purpose: Error trapping class
      '====================================================================================================================
      Option Explicit

      Public App As MyAppInfo

      Public Type MyAppInfo
      Name As String
      ReleaseDate As Date
      Version As String
      End Type

      Private Const MyModule As String = "Error_Handler"

      Public Sub Load()
      On Error GoTo ErrTrap

      App.Name = ThisWorkbook.CustomDocumentProperties("App_Name").Value
      App.ReleaseDate = ThisWorkbook.CustomDocumentProperties("App_ReleaseDate").Value
      App.Version = ThisWorkbook.CustomDocumentProperties("App_Version").Value

      ExitProcedure:
      On Error Resume Next
      Exit Sub

      ErrTrap:
      Select Case Err.number
      Case Is <> 0
      Error_Handler.DisplayMessage "Load", MyModule, Err.number, Err.description
      Resume ExitProcedure
      Case Else
      Resume ExitProcedure
      End Select

      End Sub

      Public Sub DisplayMessage( _
      ByVal procedure As String _
      , ByVal module As String _
      , ByVal number As Double _
      , ByVal description As String _
      , Optional ByVal line As Variant = 0 _
      , Optional ByVal title As String = "Unexpected Error" _
      , Optional ByVal createLog As Boolean = True)
      '====================================================================================================================
      ' Purpose: Global error message for all procedures
      ' Example: Error_Handler.DisplayMessage "Assembly_Info", "Load", 404, "Error Message Here...", 1, "Error Description"
      '====================================================================================================================
      On Error Resume Next
      Dim msg As String

      msg = "Contact your system administrator."
      msg = msg & vbCrLf & "Module: " & module
      msg = msg & vbCrLf & "Procedure: " & procedure
      msg = msg & IIf(line = 0, "", vbCrLf & "Error Line: " & line)
      msg = msg & vbCrLf & "Error #: " & number
      msg = msg & vbCrLf & "Error Description: " & description
      If createLog Then
      Log module, procedure, number, description
      End If
      MsgBox msg, vbCritical, title

      End Sub

      Public Sub Log( _
      ByVal module As String _
      , ByVal procedure As String _
      , ByVal number As Variant _
      , ByVal description As String)
      '====================================================================================================================
      ' Purpose: Creates a log file and record of the error
      ' Example: Error_Handler.Log "Assembly_Info", "Load", "404", "Error Message Here..."
      '====================================================================================================================
      On Error GoTo ErrTrap
      Dim fileSizeMax As Double: fileSizeMax = 1024 ^ 2 'archive the file over 1mb
      Dim AppName As String: AppName = LCase(Replace(App.Name, " ", "_"))
      Dim fileName As String: fileName = "C:tempexcel_addin." & AppName & ".log"
      Dim fileNumber As Variant: fileNumber = FreeFile
      Const dateFormat As String = "yyyy.mm.dd_hh.nn.ss"

      If Dir(fileName) <> "" Then
      If FileLen(fileName) > fileSizeMax Then 'archive the file when it's too big
      FileCopy fileName, Replace(fileName, ".log", Format(Now, "_" & dateFormat & ".log"))
      Kill fileName
      End If
      End If

      Open fileName For Append As #fileNumber
      Print #fileNumber, CStr(Format(Now, dateFormat)) & _
      "," & Environ("UserName") & _
      "," & Environ("ComputerName") & _
      "," & Application.OperatingSystem & _
      "," & Application.Version & _
      "," & App.Version & _
      "," & Format(App.ReleaseDate, "yyyy.mm.dd_hh.nn.ss") & _
      "," & ThisWorkbook.FullName & _
      "," & module & _
      "," & procedure & _
      "," & number & _
      "," & description

      ExitProcedure:
      On Error Resume Next
      Close #fileNumber
      Exit Sub

      ErrTrap:
      Select Case Err.number
      Case Is <> 0
      Debug.Print "Module: " & module & " |Procedure: " & procedure & " |Error #: " & number & " |Error Description: " & description
      Resume ExitProcedure
      Case Else
      Resume ExitProcedure
      End Select

      End Sub


      Usage Example:



      Public Function GetItem(ByVal col As Variant, ByVal key As Variant) As Variant
      On Error GoTo ErrTrap

      Set GetItem = col(key)

      ExitProcedure:
      On Error Resume Next
      Exit Function

      ErrTrap:
      Select Case Err.number
      Case Is = 9 'subscript out of range = this column does not exist in the active table
      Set GetItem = Nothing
      Resume ExitProcedure
      Case Is <> 0
      Error_Handler.DisplayMessage "GetItem", "Example_Module", Err.number, Err.description
      Set GetItem = Nothing
      Resume ExitProcedure
      Case Else
      Resume ExitProcedure
      End Select

      End Function









      share|improve this question















      I've been reusing an error class in Excel VBA projects for a few years now and I'd like to see if there are ways to improve it. Any suggestions for style, code, etc. are all welcome.



      The 2 procedures I'd like to focus on are:




      • Error_Handler.DisplayMessage

      • Error_Handler.Log


      The log file is usually written to a file server so multiple users can access it. I have changed the log path to C:Temp for this example. I use BareTail to read the log file.



      I use Custom Document Properties to store settings for the file/Add-in




      An example of a project I use the Error Handler class and logging in is on GitHub. For reference, I am using Excel 2016 on Windows 7.






      Error_Handler Class



      Attribute VB_Name = "Error_Handler"
      '====================================================================================================================
      ' Purpose: Error trapping class
      '====================================================================================================================
      Option Explicit

      Public App As MyAppInfo

      Public Type MyAppInfo
      Name As String
      ReleaseDate As Date
      Version As String
      End Type

      Private Const MyModule As String = "Error_Handler"

      Public Sub Load()
      On Error GoTo ErrTrap

      App.Name = ThisWorkbook.CustomDocumentProperties("App_Name").Value
      App.ReleaseDate = ThisWorkbook.CustomDocumentProperties("App_ReleaseDate").Value
      App.Version = ThisWorkbook.CustomDocumentProperties("App_Version").Value

      ExitProcedure:
      On Error Resume Next
      Exit Sub

      ErrTrap:
      Select Case Err.number
      Case Is <> 0
      Error_Handler.DisplayMessage "Load", MyModule, Err.number, Err.description
      Resume ExitProcedure
      Case Else
      Resume ExitProcedure
      End Select

      End Sub

      Public Sub DisplayMessage( _
      ByVal procedure As String _
      , ByVal module As String _
      , ByVal number As Double _
      , ByVal description As String _
      , Optional ByVal line As Variant = 0 _
      , Optional ByVal title As String = "Unexpected Error" _
      , Optional ByVal createLog As Boolean = True)
      '====================================================================================================================
      ' Purpose: Global error message for all procedures
      ' Example: Error_Handler.DisplayMessage "Assembly_Info", "Load", 404, "Error Message Here...", 1, "Error Description"
      '====================================================================================================================
      On Error Resume Next
      Dim msg As String

      msg = "Contact your system administrator."
      msg = msg & vbCrLf & "Module: " & module
      msg = msg & vbCrLf & "Procedure: " & procedure
      msg = msg & IIf(line = 0, "", vbCrLf & "Error Line: " & line)
      msg = msg & vbCrLf & "Error #: " & number
      msg = msg & vbCrLf & "Error Description: " & description
      If createLog Then
      Log module, procedure, number, description
      End If
      MsgBox msg, vbCritical, title

      End Sub

      Public Sub Log( _
      ByVal module As String _
      , ByVal procedure As String _
      , ByVal number As Variant _
      , ByVal description As String)
      '====================================================================================================================
      ' Purpose: Creates a log file and record of the error
      ' Example: Error_Handler.Log "Assembly_Info", "Load", "404", "Error Message Here..."
      '====================================================================================================================
      On Error GoTo ErrTrap
      Dim fileSizeMax As Double: fileSizeMax = 1024 ^ 2 'archive the file over 1mb
      Dim AppName As String: AppName = LCase(Replace(App.Name, " ", "_"))
      Dim fileName As String: fileName = "C:tempexcel_addin." & AppName & ".log"
      Dim fileNumber As Variant: fileNumber = FreeFile
      Const dateFormat As String = "yyyy.mm.dd_hh.nn.ss"

      If Dir(fileName) <> "" Then
      If FileLen(fileName) > fileSizeMax Then 'archive the file when it's too big
      FileCopy fileName, Replace(fileName, ".log", Format(Now, "_" & dateFormat & ".log"))
      Kill fileName
      End If
      End If

      Open fileName For Append As #fileNumber
      Print #fileNumber, CStr(Format(Now, dateFormat)) & _
      "," & Environ("UserName") & _
      "," & Environ("ComputerName") & _
      "," & Application.OperatingSystem & _
      "," & Application.Version & _
      "," & App.Version & _
      "," & Format(App.ReleaseDate, "yyyy.mm.dd_hh.nn.ss") & _
      "," & ThisWorkbook.FullName & _
      "," & module & _
      "," & procedure & _
      "," & number & _
      "," & description

      ExitProcedure:
      On Error Resume Next
      Close #fileNumber
      Exit Sub

      ErrTrap:
      Select Case Err.number
      Case Is <> 0
      Debug.Print "Module: " & module & " |Procedure: " & procedure & " |Error #: " & number & " |Error Description: " & description
      Resume ExitProcedure
      Case Else
      Resume ExitProcedure
      End Select

      End Sub


      Usage Example:



      Public Function GetItem(ByVal col As Variant, ByVal key As Variant) As Variant
      On Error GoTo ErrTrap

      Set GetItem = col(key)

      ExitProcedure:
      On Error Resume Next
      Exit Function

      ErrTrap:
      Select Case Err.number
      Case Is = 9 'subscript out of range = this column does not exist in the active table
      Set GetItem = Nothing
      Resume ExitProcedure
      Case Is <> 0
      Error_Handler.DisplayMessage "GetItem", "Example_Module", Err.number, Err.description
      Set GetItem = Nothing
      Resume ExitProcedure
      Case Else
      Resume ExitProcedure
      End Select

      End Function






      vba excel error-handling logging






      share|improve this question















      share|improve this question













      share|improve this question




      share|improve this question








      edited 6 hours ago

























      asked Oct 22 at 4:52









      aduguid

      2901317




      2901317






















          1 Answer
          1






          active

          oldest

          votes

















          up vote
          4
          down vote



          accepted










          Amount of boilerplate code



          As it is, there are lot of boilerplate that we must provide to set up everything. At a minimum, we need the following code:



          <Procedure> SomeProcedure
          On Error GoTo ErrTrap

          'Actual Code

          ExitProcedure:
          On Error Resume Next
          Exit Function

          ErrTrap:
          Select Case Err.number
          <specific Case handlers as needed>
          Case Is <> 0
          Error_Handler.DisplayMessage "SomeProcedure", "SomeModule", Err.number, Err.description
          Resume ExitProcedure
          Case Else
          Resume ExitProcedure
          End Select
          End <Procedure>


          Using third party tools like MZ-Tools can help with setting up the template, but this is non-trival code. Of more significant concerns is the fact that we are forced to hard-code the names of the modules and procedures. I have seen far too many codebases where the error message reported an error in procedure "Foo" but actually came from "Bar" because it was copied'n'pasted or because the procedure got renamed but the error handler wasn't updated, and so on.



          For a shrinkwrapped application where it is very important to have a high quality error handling, that is non-trivial undertaking. In this scenario, I would consider paying for a third party product such as vbWatchDog which provide you access to the names of modules & procedures and also the stack trace as well. This can reduce the amount of boilerplate code considerably.



          But buying a third party option is not always an option, unfortunately. In that scenario, there is very little we can do to avoid the amount but we could at least allay the naming problems by consistently using constants for both module and procedure names:



          Const ModuleName As String = "SomeModule"

          <Procedure> SomeProcedure1
          Const ProcedureName As String = "SomeProcedure1"

          ...

          Error_Handler.DisplayMessage ProcedureName, ModuleName, Err.number, Err.description

          ...

          End <Procedure>

          <Procedure> SomeProcedure2
          Const ProcedureName As String = "SomeProcedure2"

          ...

          Error_Handler.DisplayMessage ProcedureName, ModuleName, Err.number, Err.description

          ...

          End <Procedure>


          Even though it paradoxically means more boilerplate, this gives you 2 benefits:




          1. Names are now closer to the declarations, so it's less likely to get forgotten when copying'n'pasting.

          2. Because they are consistently declared, it's now possible to automate this dreary task using VBE's API to fix up the names before shipping and the code will still work.


          Lack of live debugging support



          When analyzing an existing procedure that once worked but is now acting up,
          it is very useful to be able to go directly to the offending line, especially when it is a large procedure1. A common technique to make it easy to find the offending line is to make use of unreachable Resume as demonstrated in this simplified error handler:



          Select Case Err.Number
          Case 91
          ...
          Resume ExitProcedure
          Case Else
          MsgBox "derp"
          End Select
          Resume ExitProcedure
          Resume 'for debugging


          The key is that when you get a messagebox with derp, you would type Ctrl + Break. This will interrupt the MsgBox and you will be left at the End Select. You can then drag the yellow execution arrow over to the line where Resume is, then press F8 once and you'll be on the line that caused the error. This is also useful in cases where the procedure may be called several times but errors only under certain circumstances. Instead of stepping through every single invocation, you can simply react to the fallthrough in the error handling and work from that context.



          Use of Environ function



          While Environ function provide quick and easy method for getting user's and computer's name, they can be tampered with and if the log is used in any manner of security auditing, this is a weak point. Therefore, if you have a scenario where being able to accurately point the blame (and not necessarily to actually blame but also to train or diagnose underlying hardware problems), you might want to consider using windows management classes instead, which provides similar level of convenience (e.g. it works on both 32/64 bit without needing to write conditional compilation switches and Declare statements).



          FreeFile As Variant



          You have this declaration:



          Dim fileNumber   As Variant: fileNumber = FreeFile


          But FreeFile function returns an Integer. Why not declare it so? Note that the primary reason why FreeFile returns an variant is for support in VBScript which cannot have strong-typed variables. But we're using VBA, not VBScript, so we should strong-type even when we take the value from a variant-returning functions since it's documented to return an Integer.



          Unusual date/time formatting



          I applaud the eschewing of localized date/time format and using a format that will sort correctly even in the filesystem. However, I trip over the use of a underscore to separate the days from hours. Why not use ISO formats, which would be usually yyyy-mm-dd hh-nn-ss or yyyymmddThhnnss? Using ISO formats also means it can be easily parsed2 whereas custom formats may require additional VBA code and string manipulation to parse.



          The usage of Is in Select Case expression



          I'm not a big fan of the optional Is mainly because it's superficial. It doesn't hurt to leave it in. The main reason to not make use of it would to be avoid confusion with the Is operator which actually doesn't apply here because the switch is on Err.Number, an integer, not an object. However, for consistency sake, it looks nicer to have all Select Case use the simplified Case 4, 5, 10-15 rather than Case Is 4, 5, 10-15 which will look good along with Case foo Is bar.



          Case Is <> 0 and Case Else



          I feel this 2 predicates are almost redundant and actually ends up hiding a bigger flaw. As a rule, we should be in the error handler when Err.Number <> 0. However if we are here and Err.Number = 0, then something has seriously gone wrong -- we either forgot a Exit <procedure> before the definition of the error handler, or we inadvertently did a GoTo that jumped us into inside the error handler. If you really want to guard against those serious programming errors, I don't think the Resume ExitProcedure is the correct action. I'd rather be more explicit and do this:



          Case 0
          Debug.Assert False 'We should not be here without an actual error
          Case Else
          'Generic error handling


          That said, I'd probably just leave it at Case Else and be done with that. Less boilerplate that way and in the case where we accidentally enter there, the Case Else will display a error message with Error 0, which will be enough to tell us that we made a boneheaded mistake and need to fix the code.



          Unnecessary tie-in to the host



          Your error handling code is forever bound to Excel VBA projects because of dependencies on Application.CustomProperties. But is it really the responsibility of the error handler to know those details? I say no. I would prefer that the Load method took those as a parameters with a reasonable default that can be gotten from VBA (e.g. using VBA's project name in lieu of document's path which isn't as great but it is still a default that has no external dependencies). The same concerns applies to other properties obtained from Application. Why not just call Load at your application's startup and provide it with the values? Then the modules becomes a simple drop-in and will work in any VBA hosts, not just Excel; it's now a matter of configuring it from outside.



          No indication of whether a log failed.



          In the DisplayMessage, you have a Resume Next. You then have this block:



          If createLog Then
          Log module, procedure, number, description
          End If
          MsgBox msg, vbCritical, title


          We don't know if the Log actually succeeded or not. Heck, we don't even know if we have a meaningful msg! Why can't we do something like...



          If createLog Then
          If Log(...) Then
          msg = msg & "The error has been logged."
          End If
          If Err.Number Then
          msg = msg & "An error occurred during building the message and logging. Some information may be missing. A restart of the application is strongly recommended."
          End If
          End If
          End If


          The idea is that your error message should always accurately reflect the state. If you can't log, then you're likely in a very bad state and it does not make much sense for users to keep going. Perhaps the disk is full, or there's serious lack of memory and by some miracles, the OS has not yet realized it's time to panic. It's now a total chaos, so your message need to convey that information to the user, so they can panic before the kernel panics. ;-)



          Lack of handling around file lock conflicts



          You open the file for Append but that's it. What happens if 2 instances of Excel are running and they both attempt to log at same time? The last one to log would probably lose out and the log is lost. Since the log is usually quick (it should not take much more than few milliseconds), it makes sense to have a wait + retry as a simple mechanism to ensure that your log is successfully written. Or, you can opt to make log files not shared by appending an unique identifier so that everyone is making their own files even when writing to the shared folder. Either way, you need a way to handle this contingency.



          Name ... As Instead of FileCopy & Kill



          Consider using Name statement3 in VBA to rename the file, which would allow you to do this as a single operation rather than FileCopy followed by Kill. This ensures that nobody else can smuggle in one more log message to the file being copied before it gets deleted.






          1. A large procedure is also a potential code smell and may need some refactoring instead of better error handling.

          2. To be fair, VBA does not understand the ISO 8601 format out of the build but it does understand the ODBC canonical formats. For that reason, I use ODBC canonical formats (that's yyyy-mm-dd hh-nn-ss). In other contexts, both formats are widely recognized and understood, however.

          3. Easily one of worst name for a statement. Who'd thunk to rename a file by Nameing it?






          share|improve this answer





















          • Wow, that gives me a lot to look at. Thank you so much for such a detailed analysis.
            – aduguid
            Oct 22 at 20:15






          • 1




            I've started applying a lot of the suggestions you gave me. Thanks again. github.com/Office-projects/Excel-Timesheet/releases
            – aduguid
            Oct 23 at 5:42













          Your Answer





          StackExchange.ifUsing("editor", function () {
          return StackExchange.using("mathjaxEditing", function () {
          StackExchange.MarkdownEditor.creationCallbacks.add(function (editor, postfix) {
          StackExchange.mathjaxEditing.prepareWmdForMathJax(editor, postfix, [["\$", "\$"]]);
          });
          });
          }, "mathjax-editing");

          StackExchange.ifUsing("editor", function () {
          StackExchange.using("externalEditor", function () {
          StackExchange.using("snippets", function () {
          StackExchange.snippets.init();
          });
          });
          }, "code-snippets");

          StackExchange.ready(function() {
          var channelOptions = {
          tags: "".split(" "),
          id: "196"
          };
          initTagRenderer("".split(" "), "".split(" "), channelOptions);

          StackExchange.using("externalEditor", function() {
          // Have to fire editor after snippets, if snippets enabled
          if (StackExchange.settings.snippets.snippetsEnabled) {
          StackExchange.using("snippets", function() {
          createEditor();
          });
          }
          else {
          createEditor();
          }
          });

          function createEditor() {
          StackExchange.prepareEditor({
          heartbeatType: 'answer',
          convertImagesToLinks: false,
          noModals: true,
          showLowRepImageUploadWarning: true,
          reputationToPostImages: null,
          bindNavPrevention: true,
          postfix: "",
          imageUploader: {
          brandingHtml: "Powered by u003ca class="icon-imgur-white" href="https://imgur.com/"u003eu003c/au003e",
          contentPolicyHtml: "User contributions licensed under u003ca href="https://creativecommons.org/licenses/by-sa/3.0/"u003ecc by-sa 3.0 with attribution requiredu003c/au003e u003ca href="https://stackoverflow.com/legal/content-policy"u003e(content policy)u003c/au003e",
          allowUrls: true
          },
          onDemand: true,
          discardSelector: ".discard-answer"
          ,immediatelyShowMarkdownHelp:true
          });


          }
          });














           

          draft saved


          draft discarded


















          StackExchange.ready(
          function () {
          StackExchange.openid.initPostLogin('.new-post-login', 'https%3a%2f%2fcodereview.stackexchange.com%2fquestions%2f206017%2ferror-handling-class-and-logging-for-vba%23new-answer', 'question_page');
          }
          );

          Post as a guest















          Required, but never shown

























          1 Answer
          1






          active

          oldest

          votes








          1 Answer
          1






          active

          oldest

          votes









          active

          oldest

          votes






          active

          oldest

          votes








          up vote
          4
          down vote



          accepted










          Amount of boilerplate code



          As it is, there are lot of boilerplate that we must provide to set up everything. At a minimum, we need the following code:



          <Procedure> SomeProcedure
          On Error GoTo ErrTrap

          'Actual Code

          ExitProcedure:
          On Error Resume Next
          Exit Function

          ErrTrap:
          Select Case Err.number
          <specific Case handlers as needed>
          Case Is <> 0
          Error_Handler.DisplayMessage "SomeProcedure", "SomeModule", Err.number, Err.description
          Resume ExitProcedure
          Case Else
          Resume ExitProcedure
          End Select
          End <Procedure>


          Using third party tools like MZ-Tools can help with setting up the template, but this is non-trival code. Of more significant concerns is the fact that we are forced to hard-code the names of the modules and procedures. I have seen far too many codebases where the error message reported an error in procedure "Foo" but actually came from "Bar" because it was copied'n'pasted or because the procedure got renamed but the error handler wasn't updated, and so on.



          For a shrinkwrapped application where it is very important to have a high quality error handling, that is non-trivial undertaking. In this scenario, I would consider paying for a third party product such as vbWatchDog which provide you access to the names of modules & procedures and also the stack trace as well. This can reduce the amount of boilerplate code considerably.



          But buying a third party option is not always an option, unfortunately. In that scenario, there is very little we can do to avoid the amount but we could at least allay the naming problems by consistently using constants for both module and procedure names:



          Const ModuleName As String = "SomeModule"

          <Procedure> SomeProcedure1
          Const ProcedureName As String = "SomeProcedure1"

          ...

          Error_Handler.DisplayMessage ProcedureName, ModuleName, Err.number, Err.description

          ...

          End <Procedure>

          <Procedure> SomeProcedure2
          Const ProcedureName As String = "SomeProcedure2"

          ...

          Error_Handler.DisplayMessage ProcedureName, ModuleName, Err.number, Err.description

          ...

          End <Procedure>


          Even though it paradoxically means more boilerplate, this gives you 2 benefits:




          1. Names are now closer to the declarations, so it's less likely to get forgotten when copying'n'pasting.

          2. Because they are consistently declared, it's now possible to automate this dreary task using VBE's API to fix up the names before shipping and the code will still work.


          Lack of live debugging support



          When analyzing an existing procedure that once worked but is now acting up,
          it is very useful to be able to go directly to the offending line, especially when it is a large procedure1. A common technique to make it easy to find the offending line is to make use of unreachable Resume as demonstrated in this simplified error handler:



          Select Case Err.Number
          Case 91
          ...
          Resume ExitProcedure
          Case Else
          MsgBox "derp"
          End Select
          Resume ExitProcedure
          Resume 'for debugging


          The key is that when you get a messagebox with derp, you would type Ctrl + Break. This will interrupt the MsgBox and you will be left at the End Select. You can then drag the yellow execution arrow over to the line where Resume is, then press F8 once and you'll be on the line that caused the error. This is also useful in cases where the procedure may be called several times but errors only under certain circumstances. Instead of stepping through every single invocation, you can simply react to the fallthrough in the error handling and work from that context.



          Use of Environ function



          While Environ function provide quick and easy method for getting user's and computer's name, they can be tampered with and if the log is used in any manner of security auditing, this is a weak point. Therefore, if you have a scenario where being able to accurately point the blame (and not necessarily to actually blame but also to train or diagnose underlying hardware problems), you might want to consider using windows management classes instead, which provides similar level of convenience (e.g. it works on both 32/64 bit without needing to write conditional compilation switches and Declare statements).



          FreeFile As Variant



          You have this declaration:



          Dim fileNumber   As Variant: fileNumber = FreeFile


          But FreeFile function returns an Integer. Why not declare it so? Note that the primary reason why FreeFile returns an variant is for support in VBScript which cannot have strong-typed variables. But we're using VBA, not VBScript, so we should strong-type even when we take the value from a variant-returning functions since it's documented to return an Integer.



          Unusual date/time formatting



          I applaud the eschewing of localized date/time format and using a format that will sort correctly even in the filesystem. However, I trip over the use of a underscore to separate the days from hours. Why not use ISO formats, which would be usually yyyy-mm-dd hh-nn-ss or yyyymmddThhnnss? Using ISO formats also means it can be easily parsed2 whereas custom formats may require additional VBA code and string manipulation to parse.



          The usage of Is in Select Case expression



          I'm not a big fan of the optional Is mainly because it's superficial. It doesn't hurt to leave it in. The main reason to not make use of it would to be avoid confusion with the Is operator which actually doesn't apply here because the switch is on Err.Number, an integer, not an object. However, for consistency sake, it looks nicer to have all Select Case use the simplified Case 4, 5, 10-15 rather than Case Is 4, 5, 10-15 which will look good along with Case foo Is bar.



          Case Is <> 0 and Case Else



          I feel this 2 predicates are almost redundant and actually ends up hiding a bigger flaw. As a rule, we should be in the error handler when Err.Number <> 0. However if we are here and Err.Number = 0, then something has seriously gone wrong -- we either forgot a Exit <procedure> before the definition of the error handler, or we inadvertently did a GoTo that jumped us into inside the error handler. If you really want to guard against those serious programming errors, I don't think the Resume ExitProcedure is the correct action. I'd rather be more explicit and do this:



          Case 0
          Debug.Assert False 'We should not be here without an actual error
          Case Else
          'Generic error handling


          That said, I'd probably just leave it at Case Else and be done with that. Less boilerplate that way and in the case where we accidentally enter there, the Case Else will display a error message with Error 0, which will be enough to tell us that we made a boneheaded mistake and need to fix the code.



          Unnecessary tie-in to the host



          Your error handling code is forever bound to Excel VBA projects because of dependencies on Application.CustomProperties. But is it really the responsibility of the error handler to know those details? I say no. I would prefer that the Load method took those as a parameters with a reasonable default that can be gotten from VBA (e.g. using VBA's project name in lieu of document's path which isn't as great but it is still a default that has no external dependencies). The same concerns applies to other properties obtained from Application. Why not just call Load at your application's startup and provide it with the values? Then the modules becomes a simple drop-in and will work in any VBA hosts, not just Excel; it's now a matter of configuring it from outside.



          No indication of whether a log failed.



          In the DisplayMessage, you have a Resume Next. You then have this block:



          If createLog Then
          Log module, procedure, number, description
          End If
          MsgBox msg, vbCritical, title


          We don't know if the Log actually succeeded or not. Heck, we don't even know if we have a meaningful msg! Why can't we do something like...



          If createLog Then
          If Log(...) Then
          msg = msg & "The error has been logged."
          End If
          If Err.Number Then
          msg = msg & "An error occurred during building the message and logging. Some information may be missing. A restart of the application is strongly recommended."
          End If
          End If
          End If


          The idea is that your error message should always accurately reflect the state. If you can't log, then you're likely in a very bad state and it does not make much sense for users to keep going. Perhaps the disk is full, or there's serious lack of memory and by some miracles, the OS has not yet realized it's time to panic. It's now a total chaos, so your message need to convey that information to the user, so they can panic before the kernel panics. ;-)



          Lack of handling around file lock conflicts



          You open the file for Append but that's it. What happens if 2 instances of Excel are running and they both attempt to log at same time? The last one to log would probably lose out and the log is lost. Since the log is usually quick (it should not take much more than few milliseconds), it makes sense to have a wait + retry as a simple mechanism to ensure that your log is successfully written. Or, you can opt to make log files not shared by appending an unique identifier so that everyone is making their own files even when writing to the shared folder. Either way, you need a way to handle this contingency.



          Name ... As Instead of FileCopy & Kill



          Consider using Name statement3 in VBA to rename the file, which would allow you to do this as a single operation rather than FileCopy followed by Kill. This ensures that nobody else can smuggle in one more log message to the file being copied before it gets deleted.






          1. A large procedure is also a potential code smell and may need some refactoring instead of better error handling.

          2. To be fair, VBA does not understand the ISO 8601 format out of the build but it does understand the ODBC canonical formats. For that reason, I use ODBC canonical formats (that's yyyy-mm-dd hh-nn-ss). In other contexts, both formats are widely recognized and understood, however.

          3. Easily one of worst name for a statement. Who'd thunk to rename a file by Nameing it?






          share|improve this answer





















          • Wow, that gives me a lot to look at. Thank you so much for such a detailed analysis.
            – aduguid
            Oct 22 at 20:15






          • 1




            I've started applying a lot of the suggestions you gave me. Thanks again. github.com/Office-projects/Excel-Timesheet/releases
            – aduguid
            Oct 23 at 5:42

















          up vote
          4
          down vote



          accepted










          Amount of boilerplate code



          As it is, there are lot of boilerplate that we must provide to set up everything. At a minimum, we need the following code:



          <Procedure> SomeProcedure
          On Error GoTo ErrTrap

          'Actual Code

          ExitProcedure:
          On Error Resume Next
          Exit Function

          ErrTrap:
          Select Case Err.number
          <specific Case handlers as needed>
          Case Is <> 0
          Error_Handler.DisplayMessage "SomeProcedure", "SomeModule", Err.number, Err.description
          Resume ExitProcedure
          Case Else
          Resume ExitProcedure
          End Select
          End <Procedure>


          Using third party tools like MZ-Tools can help with setting up the template, but this is non-trival code. Of more significant concerns is the fact that we are forced to hard-code the names of the modules and procedures. I have seen far too many codebases where the error message reported an error in procedure "Foo" but actually came from "Bar" because it was copied'n'pasted or because the procedure got renamed but the error handler wasn't updated, and so on.



          For a shrinkwrapped application where it is very important to have a high quality error handling, that is non-trivial undertaking. In this scenario, I would consider paying for a third party product such as vbWatchDog which provide you access to the names of modules & procedures and also the stack trace as well. This can reduce the amount of boilerplate code considerably.



          But buying a third party option is not always an option, unfortunately. In that scenario, there is very little we can do to avoid the amount but we could at least allay the naming problems by consistently using constants for both module and procedure names:



          Const ModuleName As String = "SomeModule"

          <Procedure> SomeProcedure1
          Const ProcedureName As String = "SomeProcedure1"

          ...

          Error_Handler.DisplayMessage ProcedureName, ModuleName, Err.number, Err.description

          ...

          End <Procedure>

          <Procedure> SomeProcedure2
          Const ProcedureName As String = "SomeProcedure2"

          ...

          Error_Handler.DisplayMessage ProcedureName, ModuleName, Err.number, Err.description

          ...

          End <Procedure>


          Even though it paradoxically means more boilerplate, this gives you 2 benefits:




          1. Names are now closer to the declarations, so it's less likely to get forgotten when copying'n'pasting.

          2. Because they are consistently declared, it's now possible to automate this dreary task using VBE's API to fix up the names before shipping and the code will still work.


          Lack of live debugging support



          When analyzing an existing procedure that once worked but is now acting up,
          it is very useful to be able to go directly to the offending line, especially when it is a large procedure1. A common technique to make it easy to find the offending line is to make use of unreachable Resume as demonstrated in this simplified error handler:



          Select Case Err.Number
          Case 91
          ...
          Resume ExitProcedure
          Case Else
          MsgBox "derp"
          End Select
          Resume ExitProcedure
          Resume 'for debugging


          The key is that when you get a messagebox with derp, you would type Ctrl + Break. This will interrupt the MsgBox and you will be left at the End Select. You can then drag the yellow execution arrow over to the line where Resume is, then press F8 once and you'll be on the line that caused the error. This is also useful in cases where the procedure may be called several times but errors only under certain circumstances. Instead of stepping through every single invocation, you can simply react to the fallthrough in the error handling and work from that context.



          Use of Environ function



          While Environ function provide quick and easy method for getting user's and computer's name, they can be tampered with and if the log is used in any manner of security auditing, this is a weak point. Therefore, if you have a scenario where being able to accurately point the blame (and not necessarily to actually blame but also to train or diagnose underlying hardware problems), you might want to consider using windows management classes instead, which provides similar level of convenience (e.g. it works on both 32/64 bit without needing to write conditional compilation switches and Declare statements).



          FreeFile As Variant



          You have this declaration:



          Dim fileNumber   As Variant: fileNumber = FreeFile


          But FreeFile function returns an Integer. Why not declare it so? Note that the primary reason why FreeFile returns an variant is for support in VBScript which cannot have strong-typed variables. But we're using VBA, not VBScript, so we should strong-type even when we take the value from a variant-returning functions since it's documented to return an Integer.



          Unusual date/time formatting



          I applaud the eschewing of localized date/time format and using a format that will sort correctly even in the filesystem. However, I trip over the use of a underscore to separate the days from hours. Why not use ISO formats, which would be usually yyyy-mm-dd hh-nn-ss or yyyymmddThhnnss? Using ISO formats also means it can be easily parsed2 whereas custom formats may require additional VBA code and string manipulation to parse.



          The usage of Is in Select Case expression



          I'm not a big fan of the optional Is mainly because it's superficial. It doesn't hurt to leave it in. The main reason to not make use of it would to be avoid confusion with the Is operator which actually doesn't apply here because the switch is on Err.Number, an integer, not an object. However, for consistency sake, it looks nicer to have all Select Case use the simplified Case 4, 5, 10-15 rather than Case Is 4, 5, 10-15 which will look good along with Case foo Is bar.



          Case Is <> 0 and Case Else



          I feel this 2 predicates are almost redundant and actually ends up hiding a bigger flaw. As a rule, we should be in the error handler when Err.Number <> 0. However if we are here and Err.Number = 0, then something has seriously gone wrong -- we either forgot a Exit <procedure> before the definition of the error handler, or we inadvertently did a GoTo that jumped us into inside the error handler. If you really want to guard against those serious programming errors, I don't think the Resume ExitProcedure is the correct action. I'd rather be more explicit and do this:



          Case 0
          Debug.Assert False 'We should not be here without an actual error
          Case Else
          'Generic error handling


          That said, I'd probably just leave it at Case Else and be done with that. Less boilerplate that way and in the case where we accidentally enter there, the Case Else will display a error message with Error 0, which will be enough to tell us that we made a boneheaded mistake and need to fix the code.



          Unnecessary tie-in to the host



          Your error handling code is forever bound to Excel VBA projects because of dependencies on Application.CustomProperties. But is it really the responsibility of the error handler to know those details? I say no. I would prefer that the Load method took those as a parameters with a reasonable default that can be gotten from VBA (e.g. using VBA's project name in lieu of document's path which isn't as great but it is still a default that has no external dependencies). The same concerns applies to other properties obtained from Application. Why not just call Load at your application's startup and provide it with the values? Then the modules becomes a simple drop-in and will work in any VBA hosts, not just Excel; it's now a matter of configuring it from outside.



          No indication of whether a log failed.



          In the DisplayMessage, you have a Resume Next. You then have this block:



          If createLog Then
          Log module, procedure, number, description
          End If
          MsgBox msg, vbCritical, title


          We don't know if the Log actually succeeded or not. Heck, we don't even know if we have a meaningful msg! Why can't we do something like...



          If createLog Then
          If Log(...) Then
          msg = msg & "The error has been logged."
          End If
          If Err.Number Then
          msg = msg & "An error occurred during building the message and logging. Some information may be missing. A restart of the application is strongly recommended."
          End If
          End If
          End If


          The idea is that your error message should always accurately reflect the state. If you can't log, then you're likely in a very bad state and it does not make much sense for users to keep going. Perhaps the disk is full, or there's serious lack of memory and by some miracles, the OS has not yet realized it's time to panic. It's now a total chaos, so your message need to convey that information to the user, so they can panic before the kernel panics. ;-)



          Lack of handling around file lock conflicts



          You open the file for Append but that's it. What happens if 2 instances of Excel are running and they both attempt to log at same time? The last one to log would probably lose out and the log is lost. Since the log is usually quick (it should not take much more than few milliseconds), it makes sense to have a wait + retry as a simple mechanism to ensure that your log is successfully written. Or, you can opt to make log files not shared by appending an unique identifier so that everyone is making their own files even when writing to the shared folder. Either way, you need a way to handle this contingency.



          Name ... As Instead of FileCopy & Kill



          Consider using Name statement3 in VBA to rename the file, which would allow you to do this as a single operation rather than FileCopy followed by Kill. This ensures that nobody else can smuggle in one more log message to the file being copied before it gets deleted.






          1. A large procedure is also a potential code smell and may need some refactoring instead of better error handling.

          2. To be fair, VBA does not understand the ISO 8601 format out of the build but it does understand the ODBC canonical formats. For that reason, I use ODBC canonical formats (that's yyyy-mm-dd hh-nn-ss). In other contexts, both formats are widely recognized and understood, however.

          3. Easily one of worst name for a statement. Who'd thunk to rename a file by Nameing it?






          share|improve this answer





















          • Wow, that gives me a lot to look at. Thank you so much for such a detailed analysis.
            – aduguid
            Oct 22 at 20:15






          • 1




            I've started applying a lot of the suggestions you gave me. Thanks again. github.com/Office-projects/Excel-Timesheet/releases
            – aduguid
            Oct 23 at 5:42















          up vote
          4
          down vote



          accepted







          up vote
          4
          down vote



          accepted






          Amount of boilerplate code



          As it is, there are lot of boilerplate that we must provide to set up everything. At a minimum, we need the following code:



          <Procedure> SomeProcedure
          On Error GoTo ErrTrap

          'Actual Code

          ExitProcedure:
          On Error Resume Next
          Exit Function

          ErrTrap:
          Select Case Err.number
          <specific Case handlers as needed>
          Case Is <> 0
          Error_Handler.DisplayMessage "SomeProcedure", "SomeModule", Err.number, Err.description
          Resume ExitProcedure
          Case Else
          Resume ExitProcedure
          End Select
          End <Procedure>


          Using third party tools like MZ-Tools can help with setting up the template, but this is non-trival code. Of more significant concerns is the fact that we are forced to hard-code the names of the modules and procedures. I have seen far too many codebases where the error message reported an error in procedure "Foo" but actually came from "Bar" because it was copied'n'pasted or because the procedure got renamed but the error handler wasn't updated, and so on.



          For a shrinkwrapped application where it is very important to have a high quality error handling, that is non-trivial undertaking. In this scenario, I would consider paying for a third party product such as vbWatchDog which provide you access to the names of modules & procedures and also the stack trace as well. This can reduce the amount of boilerplate code considerably.



          But buying a third party option is not always an option, unfortunately. In that scenario, there is very little we can do to avoid the amount but we could at least allay the naming problems by consistently using constants for both module and procedure names:



          Const ModuleName As String = "SomeModule"

          <Procedure> SomeProcedure1
          Const ProcedureName As String = "SomeProcedure1"

          ...

          Error_Handler.DisplayMessage ProcedureName, ModuleName, Err.number, Err.description

          ...

          End <Procedure>

          <Procedure> SomeProcedure2
          Const ProcedureName As String = "SomeProcedure2"

          ...

          Error_Handler.DisplayMessage ProcedureName, ModuleName, Err.number, Err.description

          ...

          End <Procedure>


          Even though it paradoxically means more boilerplate, this gives you 2 benefits:




          1. Names are now closer to the declarations, so it's less likely to get forgotten when copying'n'pasting.

          2. Because they are consistently declared, it's now possible to automate this dreary task using VBE's API to fix up the names before shipping and the code will still work.


          Lack of live debugging support



          When analyzing an existing procedure that once worked but is now acting up,
          it is very useful to be able to go directly to the offending line, especially when it is a large procedure1. A common technique to make it easy to find the offending line is to make use of unreachable Resume as demonstrated in this simplified error handler:



          Select Case Err.Number
          Case 91
          ...
          Resume ExitProcedure
          Case Else
          MsgBox "derp"
          End Select
          Resume ExitProcedure
          Resume 'for debugging


          The key is that when you get a messagebox with derp, you would type Ctrl + Break. This will interrupt the MsgBox and you will be left at the End Select. You can then drag the yellow execution arrow over to the line where Resume is, then press F8 once and you'll be on the line that caused the error. This is also useful in cases where the procedure may be called several times but errors only under certain circumstances. Instead of stepping through every single invocation, you can simply react to the fallthrough in the error handling and work from that context.



          Use of Environ function



          While Environ function provide quick and easy method for getting user's and computer's name, they can be tampered with and if the log is used in any manner of security auditing, this is a weak point. Therefore, if you have a scenario where being able to accurately point the blame (and not necessarily to actually blame but also to train or diagnose underlying hardware problems), you might want to consider using windows management classes instead, which provides similar level of convenience (e.g. it works on both 32/64 bit without needing to write conditional compilation switches and Declare statements).



          FreeFile As Variant



          You have this declaration:



          Dim fileNumber   As Variant: fileNumber = FreeFile


          But FreeFile function returns an Integer. Why not declare it so? Note that the primary reason why FreeFile returns an variant is for support in VBScript which cannot have strong-typed variables. But we're using VBA, not VBScript, so we should strong-type even when we take the value from a variant-returning functions since it's documented to return an Integer.



          Unusual date/time formatting



          I applaud the eschewing of localized date/time format and using a format that will sort correctly even in the filesystem. However, I trip over the use of a underscore to separate the days from hours. Why not use ISO formats, which would be usually yyyy-mm-dd hh-nn-ss or yyyymmddThhnnss? Using ISO formats also means it can be easily parsed2 whereas custom formats may require additional VBA code and string manipulation to parse.



          The usage of Is in Select Case expression



          I'm not a big fan of the optional Is mainly because it's superficial. It doesn't hurt to leave it in. The main reason to not make use of it would to be avoid confusion with the Is operator which actually doesn't apply here because the switch is on Err.Number, an integer, not an object. However, for consistency sake, it looks nicer to have all Select Case use the simplified Case 4, 5, 10-15 rather than Case Is 4, 5, 10-15 which will look good along with Case foo Is bar.



          Case Is <> 0 and Case Else



          I feel this 2 predicates are almost redundant and actually ends up hiding a bigger flaw. As a rule, we should be in the error handler when Err.Number <> 0. However if we are here and Err.Number = 0, then something has seriously gone wrong -- we either forgot a Exit <procedure> before the definition of the error handler, or we inadvertently did a GoTo that jumped us into inside the error handler. If you really want to guard against those serious programming errors, I don't think the Resume ExitProcedure is the correct action. I'd rather be more explicit and do this:



          Case 0
          Debug.Assert False 'We should not be here without an actual error
          Case Else
          'Generic error handling


          That said, I'd probably just leave it at Case Else and be done with that. Less boilerplate that way and in the case where we accidentally enter there, the Case Else will display a error message with Error 0, which will be enough to tell us that we made a boneheaded mistake and need to fix the code.



          Unnecessary tie-in to the host



          Your error handling code is forever bound to Excel VBA projects because of dependencies on Application.CustomProperties. But is it really the responsibility of the error handler to know those details? I say no. I would prefer that the Load method took those as a parameters with a reasonable default that can be gotten from VBA (e.g. using VBA's project name in lieu of document's path which isn't as great but it is still a default that has no external dependencies). The same concerns applies to other properties obtained from Application. Why not just call Load at your application's startup and provide it with the values? Then the modules becomes a simple drop-in and will work in any VBA hosts, not just Excel; it's now a matter of configuring it from outside.



          No indication of whether a log failed.



          In the DisplayMessage, you have a Resume Next. You then have this block:



          If createLog Then
          Log module, procedure, number, description
          End If
          MsgBox msg, vbCritical, title


          We don't know if the Log actually succeeded or not. Heck, we don't even know if we have a meaningful msg! Why can't we do something like...



          If createLog Then
          If Log(...) Then
          msg = msg & "The error has been logged."
          End If
          If Err.Number Then
          msg = msg & "An error occurred during building the message and logging. Some information may be missing. A restart of the application is strongly recommended."
          End If
          End If
          End If


          The idea is that your error message should always accurately reflect the state. If you can't log, then you're likely in a very bad state and it does not make much sense for users to keep going. Perhaps the disk is full, or there's serious lack of memory and by some miracles, the OS has not yet realized it's time to panic. It's now a total chaos, so your message need to convey that information to the user, so they can panic before the kernel panics. ;-)



          Lack of handling around file lock conflicts



          You open the file for Append but that's it. What happens if 2 instances of Excel are running and they both attempt to log at same time? The last one to log would probably lose out and the log is lost. Since the log is usually quick (it should not take much more than few milliseconds), it makes sense to have a wait + retry as a simple mechanism to ensure that your log is successfully written. Or, you can opt to make log files not shared by appending an unique identifier so that everyone is making their own files even when writing to the shared folder. Either way, you need a way to handle this contingency.



          Name ... As Instead of FileCopy & Kill



          Consider using Name statement3 in VBA to rename the file, which would allow you to do this as a single operation rather than FileCopy followed by Kill. This ensures that nobody else can smuggle in one more log message to the file being copied before it gets deleted.






          1. A large procedure is also a potential code smell and may need some refactoring instead of better error handling.

          2. To be fair, VBA does not understand the ISO 8601 format out of the build but it does understand the ODBC canonical formats. For that reason, I use ODBC canonical formats (that's yyyy-mm-dd hh-nn-ss). In other contexts, both formats are widely recognized and understood, however.

          3. Easily one of worst name for a statement. Who'd thunk to rename a file by Nameing it?






          share|improve this answer












          Amount of boilerplate code



          As it is, there are lot of boilerplate that we must provide to set up everything. At a minimum, we need the following code:



          <Procedure> SomeProcedure
          On Error GoTo ErrTrap

          'Actual Code

          ExitProcedure:
          On Error Resume Next
          Exit Function

          ErrTrap:
          Select Case Err.number
          <specific Case handlers as needed>
          Case Is <> 0
          Error_Handler.DisplayMessage "SomeProcedure", "SomeModule", Err.number, Err.description
          Resume ExitProcedure
          Case Else
          Resume ExitProcedure
          End Select
          End <Procedure>


          Using third party tools like MZ-Tools can help with setting up the template, but this is non-trival code. Of more significant concerns is the fact that we are forced to hard-code the names of the modules and procedures. I have seen far too many codebases where the error message reported an error in procedure "Foo" but actually came from "Bar" because it was copied'n'pasted or because the procedure got renamed but the error handler wasn't updated, and so on.



          For a shrinkwrapped application where it is very important to have a high quality error handling, that is non-trivial undertaking. In this scenario, I would consider paying for a third party product such as vbWatchDog which provide you access to the names of modules & procedures and also the stack trace as well. This can reduce the amount of boilerplate code considerably.



          But buying a third party option is not always an option, unfortunately. In that scenario, there is very little we can do to avoid the amount but we could at least allay the naming problems by consistently using constants for both module and procedure names:



          Const ModuleName As String = "SomeModule"

          <Procedure> SomeProcedure1
          Const ProcedureName As String = "SomeProcedure1"

          ...

          Error_Handler.DisplayMessage ProcedureName, ModuleName, Err.number, Err.description

          ...

          End <Procedure>

          <Procedure> SomeProcedure2
          Const ProcedureName As String = "SomeProcedure2"

          ...

          Error_Handler.DisplayMessage ProcedureName, ModuleName, Err.number, Err.description

          ...

          End <Procedure>


          Even though it paradoxically means more boilerplate, this gives you 2 benefits:




          1. Names are now closer to the declarations, so it's less likely to get forgotten when copying'n'pasting.

          2. Because they are consistently declared, it's now possible to automate this dreary task using VBE's API to fix up the names before shipping and the code will still work.


          Lack of live debugging support



          When analyzing an existing procedure that once worked but is now acting up,
          it is very useful to be able to go directly to the offending line, especially when it is a large procedure1. A common technique to make it easy to find the offending line is to make use of unreachable Resume as demonstrated in this simplified error handler:



          Select Case Err.Number
          Case 91
          ...
          Resume ExitProcedure
          Case Else
          MsgBox "derp"
          End Select
          Resume ExitProcedure
          Resume 'for debugging


          The key is that when you get a messagebox with derp, you would type Ctrl + Break. This will interrupt the MsgBox and you will be left at the End Select. You can then drag the yellow execution arrow over to the line where Resume is, then press F8 once and you'll be on the line that caused the error. This is also useful in cases where the procedure may be called several times but errors only under certain circumstances. Instead of stepping through every single invocation, you can simply react to the fallthrough in the error handling and work from that context.



          Use of Environ function



          While Environ function provide quick and easy method for getting user's and computer's name, they can be tampered with and if the log is used in any manner of security auditing, this is a weak point. Therefore, if you have a scenario where being able to accurately point the blame (and not necessarily to actually blame but also to train or diagnose underlying hardware problems), you might want to consider using windows management classes instead, which provides similar level of convenience (e.g. it works on both 32/64 bit without needing to write conditional compilation switches and Declare statements).



          FreeFile As Variant



          You have this declaration:



          Dim fileNumber   As Variant: fileNumber = FreeFile


          But FreeFile function returns an Integer. Why not declare it so? Note that the primary reason why FreeFile returns an variant is for support in VBScript which cannot have strong-typed variables. But we're using VBA, not VBScript, so we should strong-type even when we take the value from a variant-returning functions since it's documented to return an Integer.



          Unusual date/time formatting



          I applaud the eschewing of localized date/time format and using a format that will sort correctly even in the filesystem. However, I trip over the use of a underscore to separate the days from hours. Why not use ISO formats, which would be usually yyyy-mm-dd hh-nn-ss or yyyymmddThhnnss? Using ISO formats also means it can be easily parsed2 whereas custom formats may require additional VBA code and string manipulation to parse.



          The usage of Is in Select Case expression



          I'm not a big fan of the optional Is mainly because it's superficial. It doesn't hurt to leave it in. The main reason to not make use of it would to be avoid confusion with the Is operator which actually doesn't apply here because the switch is on Err.Number, an integer, not an object. However, for consistency sake, it looks nicer to have all Select Case use the simplified Case 4, 5, 10-15 rather than Case Is 4, 5, 10-15 which will look good along with Case foo Is bar.



          Case Is <> 0 and Case Else



          I feel this 2 predicates are almost redundant and actually ends up hiding a bigger flaw. As a rule, we should be in the error handler when Err.Number <> 0. However if we are here and Err.Number = 0, then something has seriously gone wrong -- we either forgot a Exit <procedure> before the definition of the error handler, or we inadvertently did a GoTo that jumped us into inside the error handler. If you really want to guard against those serious programming errors, I don't think the Resume ExitProcedure is the correct action. I'd rather be more explicit and do this:



          Case 0
          Debug.Assert False 'We should not be here without an actual error
          Case Else
          'Generic error handling


          That said, I'd probably just leave it at Case Else and be done with that. Less boilerplate that way and in the case where we accidentally enter there, the Case Else will display a error message with Error 0, which will be enough to tell us that we made a boneheaded mistake and need to fix the code.



          Unnecessary tie-in to the host



          Your error handling code is forever bound to Excel VBA projects because of dependencies on Application.CustomProperties. But is it really the responsibility of the error handler to know those details? I say no. I would prefer that the Load method took those as a parameters with a reasonable default that can be gotten from VBA (e.g. using VBA's project name in lieu of document's path which isn't as great but it is still a default that has no external dependencies). The same concerns applies to other properties obtained from Application. Why not just call Load at your application's startup and provide it with the values? Then the modules becomes a simple drop-in and will work in any VBA hosts, not just Excel; it's now a matter of configuring it from outside.



          No indication of whether a log failed.



          In the DisplayMessage, you have a Resume Next. You then have this block:



          If createLog Then
          Log module, procedure, number, description
          End If
          MsgBox msg, vbCritical, title


          We don't know if the Log actually succeeded or not. Heck, we don't even know if we have a meaningful msg! Why can't we do something like...



          If createLog Then
          If Log(...) Then
          msg = msg & "The error has been logged."
          End If
          If Err.Number Then
          msg = msg & "An error occurred during building the message and logging. Some information may be missing. A restart of the application is strongly recommended."
          End If
          End If
          End If


          The idea is that your error message should always accurately reflect the state. If you can't log, then you're likely in a very bad state and it does not make much sense for users to keep going. Perhaps the disk is full, or there's serious lack of memory and by some miracles, the OS has not yet realized it's time to panic. It's now a total chaos, so your message need to convey that information to the user, so they can panic before the kernel panics. ;-)



          Lack of handling around file lock conflicts



          You open the file for Append but that's it. What happens if 2 instances of Excel are running and they both attempt to log at same time? The last one to log would probably lose out and the log is lost. Since the log is usually quick (it should not take much more than few milliseconds), it makes sense to have a wait + retry as a simple mechanism to ensure that your log is successfully written. Or, you can opt to make log files not shared by appending an unique identifier so that everyone is making their own files even when writing to the shared folder. Either way, you need a way to handle this contingency.



          Name ... As Instead of FileCopy & Kill



          Consider using Name statement3 in VBA to rename the file, which would allow you to do this as a single operation rather than FileCopy followed by Kill. This ensures that nobody else can smuggle in one more log message to the file being copied before it gets deleted.






          1. A large procedure is also a potential code smell and may need some refactoring instead of better error handling.

          2. To be fair, VBA does not understand the ISO 8601 format out of the build but it does understand the ODBC canonical formats. For that reason, I use ODBC canonical formats (that's yyyy-mm-dd hh-nn-ss). In other contexts, both formats are widely recognized and understood, however.

          3. Easily one of worst name for a statement. Who'd thunk to rename a file by Nameing it?







          share|improve this answer












          share|improve this answer



          share|improve this answer










          answered Oct 22 at 16:41









          this

          1,432418




          1,432418












          • Wow, that gives me a lot to look at. Thank you so much for such a detailed analysis.
            – aduguid
            Oct 22 at 20:15






          • 1




            I've started applying a lot of the suggestions you gave me. Thanks again. github.com/Office-projects/Excel-Timesheet/releases
            – aduguid
            Oct 23 at 5:42




















          • Wow, that gives me a lot to look at. Thank you so much for such a detailed analysis.
            – aduguid
            Oct 22 at 20:15






          • 1




            I've started applying a lot of the suggestions you gave me. Thanks again. github.com/Office-projects/Excel-Timesheet/releases
            – aduguid
            Oct 23 at 5:42


















          Wow, that gives me a lot to look at. Thank you so much for such a detailed analysis.
          – aduguid
          Oct 22 at 20:15




          Wow, that gives me a lot to look at. Thank you so much for such a detailed analysis.
          – aduguid
          Oct 22 at 20:15




          1




          1




          I've started applying a lot of the suggestions you gave me. Thanks again. github.com/Office-projects/Excel-Timesheet/releases
          – aduguid
          Oct 23 at 5:42






          I've started applying a lot of the suggestions you gave me. Thanks again. github.com/Office-projects/Excel-Timesheet/releases
          – aduguid
          Oct 23 at 5:42




















           

          draft saved


          draft discarded



















































           


          draft saved


          draft discarded














          StackExchange.ready(
          function () {
          StackExchange.openid.initPostLogin('.new-post-login', 'https%3a%2f%2fcodereview.stackexchange.com%2fquestions%2f206017%2ferror-handling-class-and-logging-for-vba%23new-answer', 'question_page');
          }
          );

          Post as a guest















          Required, but never shown





















































          Required, but never shown














          Required, but never shown












          Required, but never shown







          Required, but never shown

































          Required, but never shown














          Required, but never shown












          Required, but never shown







          Required, but never shown







          Popular posts from this blog

          404 Error Contact Form 7 ajax form submitting

          How to know if a Active Directory user can login interactively

          TypeError: fit_transform() missing 1 required positional argument: 'X'