Skip to content

Common VBA Execution Trace service provided either by a Standard Module (mTrc) or by a Class Module (clsTrc), simply by two additional code lines in each to be traced procedure.

License

warbe-maker/VBA-Trace

Repository files navigation

Common VBA Execution Trace Services

Writes records of traced executions of procedures and code snippets to a trace-log-file as shown. Available as a Standard Module or a Class Module (see Arguments for which one to use).

Public services

Service Kind 1 Purpose
BoC S Indicates the Begin of a Code sequence to be traced.
Attention: In order to keep this service optional it is exclusively called via an BoC Interface which is to be copied in each component when used.
BoP S Indicates the Begin of the execution trace of a Procedure.
Attention: In order to keep this service optional it is exclusively called via an BoP Interface which is to be copied in each component when used.
BoP_ErH S Exclusively used by the mErH module (when installed and activated).
Continue S May be used when a a user interaction has been completed (e.g. by pressed button of a VBA.MsgBox) to continue a _Pause_ed execution trace's time taking.
Dsply S Displays the content of the trace log file. Available only when the mMsg/fMsg modules are installed and this is indicated by the Conditional Compile Argument mMsg = 1. Without mMsg/fMsg the trace result log will be viewed with any appropriate text file viewer.
EoC S Indicates the End of a Code sequence to be traced.
Attention: In order to keep this service optional it is exclusively called via an EoC Interface which is to be copied in each component when used.
EoP S Indicates the (E)nd of the execution trace of a Procedure.
Attention: In order to keep this service optional it is exclusively called via an EoP Interface which is to be copied in each component when used.
Pause S May be used when a before a user interaction is requested (e.g. by a VBA.MsgBox) to suspend the execution trace's time taking.
FileName P w String expression, specifies the name of a desired trace-log-file, defaults to "ExecTrace.log".
FileFullName P w String expression, specifies the trace-log-file's full name, defaults to Path & FileName.
Path P w String expression, specifies the folder for the trace-log-file, defaults to ThisWorkbook.Path
LogInfo P w Adds an entry to the trace log file by considering the current nesting/indentation level.
Title P w String expression, specifies the title written to the trace-log-file at the begin and the end of the execution trace (see example above).

Installation

  1. Download either mTrc.bas or clsTrc.cls
  2. Import it to your VB-Project
  3. Activate it through Conditional Compile Argument
       mTrc = 1 (when mTrc is installed and is to be used)
       clsTrc = 1 (when mTrc is installed and is to be used)
    Be aware that though both may be installed only one may be used at a time!
  4. Set a Reference to the Microsoft Scripting Runtime
    Nothing else needs to be installed. Each of the components works completely autonomous.

Activation

Writing code which may or may not be possible to be executed depending on whether a module is installed or not is a challenge. The way how this is achieved is through procedures functioning as call interface, whereby only those statements are executed of which the corresponding component is installed and activated via Conditional Compile Arguments.

Usage

The approach allows to have the services called in the code even when the servicing component is not installed or when the service is deactivated because not desired. To achieve this flexibility Conditional Compile Arguments are used with an interface dedicated to each service. When the corresponding Conditional Compile Argument are missing or set to 0 absolute nothing happens irrespective of an installed mTrc.bas or clsTrc.cls.

Service interfaces

It is essential that BoP/EoP and BoC/EoC services are always called paired with identical arguments!

BoP/EoP interface

Private Sub BoP(ByVal b_proc As String, ParamArray b_arguments() As Variant)
' ------------------------------------------------------------------------------
' Common 'Begin of Procedure' interface serving the 'Common VBA Error Services'
' and the 'Common VBA Execution Trace Service'. To be copied into any component
' using the BoP service - either through the 'Common VBA Error Services' and/or
' the 'Common VBA Execution Trace Service'.
' ------------------------------------------------------------------------------
    Dim s As String: If Not IsMissing(b_arguments) Then s = Join(b_arguments, ";")
#If mErH = 1 Then
    '~~ The error handling will also hand over to the Common VBA Execution Trace
    '~~ provided one is installed (mTrc/clsTrc) and activated.
    mErH.BoP b_proc, s
#ElseIf clsTrc = 1 Then
    '~~ mErH is not installed but the mTrc is
    Trc.BoP b_proc, s
#ElseIf mTrc = 1 Then
    '~~ mErH neither mTrc is installed but clsTrc is
    mTrc.BoP b_proc, s
#End If
End Sub

Private Sub EoP(ByVal e_proc As String, Optional ByVal e_inf As String = vbNullString)
' ------------------------------------------------------------------------------
' Common 'End of Procedure' interface serving the 'Common VBA Error Services'
' and the 'Common VBA Execution Trace Service'. To be copied into any component
' using the EoP service - either through the 'Common VBA Error Services' and/or
' the 'Common VBA Execution Trace Service'.
' ------------------------------------------------------------------------------
#If mErH = 1 Then
    '~~ The error handling will also hand over to the Common VBA Execution Trace
    '~~ provided one is installed (mTrc/clsTrc) and activated.
    mErH.EoP e_proc
#ElseIf clsTrc = 1 Then
    Trc.EoP e_proc, e_inf
#ElseIf mTrc = 1 Then
    mTrc.EoP e_proc, e_inf
#End If
End Sub

BoC/EoP interface

While BoP/EoP are services also provided by the mErH.bas component, these two services are exclusively be provided by the mTrc.bas/clsTrc.cls components.

Private Sub BoC(ByVal b_id As String, ParamArray b_arguments() As Variant)
' ------------------------------------------------------------------------------
' Common '(B)egin-(o)f-(C)ode' interface for the 'Common VBA Execution Trace
' Service'. To be copied into any module using the BoC service.
' ------------------------------------------------------------------------------
    Dim s As String: If Not IsMissing(b_arguments) Then s = Join(b_arguments, ",")
#If XcTrc_mTrc = 1 Then
    mTrc.BoC b_id, s
#ElseIf XcTrc_clsTrc = 1 Then
    Trc.BoC b_id, s
#End If
End Sub

Private Sub EoC(ByVal e_id As String, ParamArray e_arguments() As Variant)
' ------------------------------------------------------------------------------
' Common '(E)nd-(o)f-(C)ode' interface for the 'Common VBA Execution Trace
' Service'. To be copied into any module using the BoC service.
' ------------------------------------------------------------------------------
    Dim s As String
    If Not IsMissing(e_arguments) Then s = Join(e_arguments, ",")

#If XcTrc_mTrc = 1 Then
    mTrc.EoC e_id, s
#ElseIf XcTrc_clsTrc = 1 Then
    Trc.EoC e_id, s
#End If

End Sub

Using the clsTrc Class Module

In the declaration part of a component/module:

#If XcTrc_clsTrc = 1 Then
    Public Trc As clsTrc
#End If

In the start procedure:

    Set Trc = New clsTrc
    With Trc
        .Title = "...."    ' optional
        .FileName = "...." ' unless the default is fine
        .NewFile           ' when the trace is not to be appended
    End With

See the below arguments for which variant of the two components to use.

Using the BoP/EoP service

Thanks to the service interfaces and the Conditional Compile Argument which corresponds with the installed component ( mTrc = 1 (when mTrc is installed), clsTrc = 1 (when clsTrc is installed) the following will do the execution trace:

Private Sub MyProc()
    Const PROC = "MyProc"

    BoP ErrSrc(PROC)
    ' any code lines
    EoP ErrSrc(PROC)

'~~ Only if this is the 'start procedure' and when displaying the trace result is desired    
#If XcTrc_clsTrc = 1 Then
    Trc.Dsply
#ElseIf XcTrc_mTrc = 1 Then
    mTrc.Dsply
#End If

End Sub

See the below arguments for which variant of the two components to use.

Arguments for either of the two components

The variants had been implemented as a trial to see what makes the difference. While the Standard Module (mTrc.bas) is obviously more simple to be used (no extra declaration, no instantiation) the Class Module (clsTrc.cls) appears to perform a tiny bit better. Since the difference will hard to ever be recognized none is clearly recommendable. Needles to say that the implementation of a Class Module is more elegant specifically when several instances of the class are needed (not the case here) but also when working with default values. In a Standard Module it requires and explicit Initialization service to be called which is done in a Class Module implicitly when instantiated.

Download from public GitHub repo

It may appear pretty strange when downloading first from a public GitHub repo but is is quite straight forward as the below image shows.

Contribution

Contribution of any kind in any form is welcome - preferably by raising an issue.

Footnotes

  1. S=Sub/Method, P=Property (w=write/Let, r=read/Get)

About

Common VBA Execution Trace service provided either by a Standard Module (mTrc) or by a Class Module (clsTrc), simply by two additional code lines in each to be traced procedure.

Resources

License

Stars

Watchers

Forks

Releases

No releases published

Packages

No packages published

Languages