Click here to Skip to main content
15,867,756 members
Articles / Programming Languages / VBE

Deconstruction of a VBA Code Module

Rate me:
Please Sign up or sign in to vote.
4.82/5 (23 votes)
31 Dec 2013CPOL12 min read 105.9K   3.8K   35   20
This article is intended to build on the extensibility knowledge base with a focus on deconstructing a VBA code module.

Introduction

When working with VBA, a useful tool to have is a module which creates extracts of your work. If you produce frameworks, a complete listing of all components and procedures could prove useful in maintaining consistency in the model. Since the incorporation of the Visual Basic Editor into the Microsoft Office application suite, it is possible to have both.

This article is intended to build on the extensibility knowledge base with a focus on deconstructing a VBA code module. The target being a report of all procedures in the active VBA project. Included with this article is a standard VBA module which employs the deconstruction techniques and is a complete extract and reporting package.

Please note that in order to use the codebase in this article, any targeted Office application must support the VBE interface.

 Image 1

Visual Basic Editor (VBE)

The Visual Basic Editor is an interface which is used to used to create, modify, and maintain Visual Basic for Applications objects. The majority of Microsoft Office applications include a built-in VBE interface which is used to access the underlying Microsoft Visual Basic for Applications Extensibility library (VBIDE). The interface is VBE, its implementation is VBIDE, and the code is VBA.

At runtime, an instance of VBIDE is automatically made available through the VBE property of the Application object. Additional type libraries are not required to use the property or the interface it exposes. The only requirement being that the target Office application supports the interface.

As a result, this project does not early bind to the extensibility type library. All extensibility objects are dimensioned as Object and any required constants have been manually re-created in the module included with this article.

With the required objects already in place, the focus can shift to the deconstruction of a VBA code module and the VBE CodeModule object.

CodeModule Object

A VBComponent is a container which enables differentiation between code objects in a VBA project. A component can be a standard module, a class module, a user form, or a document. Each VBComponent contains one code module and the CodeModule object provides access to it.

Combine the CodeModule object with the capabilities of VBA, and the two become a powerful editor. As with most editors, lines can be inserted, deleted, and replaced. The object includes find-find next functionality and lines (or blocks of lines) can be retrieved. In the scope of this project, lines are indexed, counted, and sometimes retrieved.

The CodeModule object resolves a VBA module by lines. The Lines collection begins at line 1 and continues until CountOfLines is reached, the last line in a module. Any single line or blocks of lines can be retrieved using the collection.

A module can also be separated into declarations and procedures. The declarations section begins at line 1 and continues until it reaches CountOfDeclarationLines, the last non-procedural declaration in a module. The procedures section begins at CountOfDeclarationLines + 1 and continues until CountOfLines is reached.

 Image 2

If there are zero procedures in a module, then all lines belong to the declarations section. If there are zero declarations in a module, then all lines belong to the procedures section, providing there are procedures.

The following example will extract all of the code in the active project and display it in the immediate window. The declarations and procedures have been provided their own iterators to enable working with a module in sections. It is also using the Lines collection to display the single line with which the index represents.

VB.NET
Public Sub ListCode()

    Dim Component As Object
    Dim Index As Long

    For Each Component In Application.VBE.ActiveVBProject.VBComponents

        With Component.CodeModule

            'The Declarations
            For Index = 1 To .CountOfDeclarationLines
                Debug.Print .Lines(Index, 1)
            Next Index

            'The Procedures
            For Index = .CountOfDeclarationLines + 1 To .CountOfLines
                Debug.Print .Lines(Index, 1)
            Next Index

        End With

    Next Component

End Sub

Procedure Blocks

A procedure is defined by a developer. The Kind of procedure available is built into the programming language. The CodeModule object recognizes Property Get, Property Let, and Property Set statements as procedure Kind. It also recognizes Sub and Function but does not differentiate between the two, it collectively defines them as Proc.

To the CodeModule object, a procedure is a block of lines which has location and length. It defines location as ProcStartLine and length as ProcCountLines. It also defines ProcBodyLine which is the location of the procedural declaration within the block.

ProcStartLine and ProcBodyLine are line numbers calculated from Line 1. ProcCountLines is the line count between ProcStartLine and ProcCountLines, inclusive.

 Image 3

A procedure includes all whitespace and comments above its declaration and ends with its terminating block. The exception being the last procedure in a module as it also includes all whitespace and comments to the end of the module.

The location and length properties can be used to index procedures, but to use the properties, a procedure Name and procedure Kind are required.

In this project, the ProcOfLine property is used to determine a procedure Name and Kind at a given line number. To use ProcOfLine, a line number and the name of a long variable must be supplied. ProcOfLine will examine the line and return the name of the procedure which owns it. It will also fill the long variable with the kind of procedure it is.

Once a procedure Name and Kind have been determined, the location and length properties can be used to index into a procedure, or through all the procedures in a module.

In the following example, Index is seeded to CountOfDeclarationLines + 1, the beginning of the procedures section. A call to ProcOfLine using the Index fills both the Name and Kind variable values. Having the two values enables ProcStartLine and ProcCountLines to calculate the end of the current procedure (ProcStartLine + ProcCountLines) and then Index to the beginning of the next procedure (+1).

VB.NET
Public Sub ListNames()

    Dim Component As Object
    Dim Name As String
    Dim Kind As Long
    Dim Index As Long

    For Each Component In Application.VBE.ActiveVBProject.VBComponents

        With Component.CodeModule

            'The Procedures
            Index = .CountOfDeclarationLines + 1

            Do While Index < .CountOfLines
                Name = .ProcOfLine(Index, Kind)
                Debug.Print Component.Name & "." & Name
                Index = .ProcStartLine(Name, Kind) + .ProcCountLines(Name, Kind) + 1
            Loop

        End With

    Next Component

End Sub

ListNames will display all procedures in the active project by module. However, the list could contain duplicates within the individual modules. The duplications belong to properties which have both a Get and a Let or Set defined. To produce a unique list of procedures in a module, the procedure Kind should be incorporated into a result set.

Data Transformations

In this project, data is converted from value to meaningful name for reporting purposes. Constant values have been extracted from the VBIDE library and are used to define the component type, procedure kind, and reference kind. With the exception of the procedure kind, vanilla case statements are employed to transform a defined object from value to name.

VB.NET
'VBIDE.vbext_ComponentType
Private Const vbext_ct_ActiveXDesigner As Long = 11
Private Const vbext_ct_ClassModule As Long = 2
Private Const vbext_ct_Document As Long = 100
Private Const vbext_ct_MSForm As Long = 3
Private Const vbext_ct_StdModule As Long = 1

'VBIDE.vbext_ProcKind
Private Const vbext_pk_Get As Long = 3
Private Const vbext_pk_Let As Long = 1
Private Const vbext_pk_Set As Long = 2
Private Const vbext_pk_Proc As Long = 0

'VBIDE.vbext_RefKind
Private Const vbext_rk_Project As Long = 1
Private Const vbext_rk_TypeLib As Long = 0

As you might remember from the procedures discussion, the CodeModule object does not differentiate between Sub and Function. The object collectively defines them as Proc, or actually, VBIDE.vbext_ProcKind.vbext_pk_Proc. If the distinction between Sub and Function is required, then a workaround needs to be employed.

The following example performs a data transformation from vbext_ProcKind to a meaningful name. The function is passed a long value of vbext_ProcKind enum and the declaration text from ProcBodyLine. A best guess workaround checks if the declaration text contains the word "Function-Space". If a match is made then it assumes Function and if not, Sub.

VB.NET
Public Function GetProcKind(Kind As Long, Declaration As String) As String

    'Transform the procedure kind to text
    Select Case Kind

        Case vbext_pk_Get
            GetProcKind = "Get"

        Case vbext_pk_Let
            GetProcKind = "Let"

        Case vbext_pk_Set
            GetProcKind = "Set"

        'Best Guess
        Case vbext_pk_Proc
            If InStr(1, Declaration, "Function ", vbBinaryCompare) > 0 Then
                GetProcKind = "Func"
            Else
                GetProcKind = "Sub"
            End If

        Case Else
            GetProcKind = "Undefined"

    End Select

End Function

Using best guess as formatted has been successful, however, rarely do I comment procedural declarations in-line. But being developers and knowing what to look for makes snippets like best guess easy to change.

Procedure Report

At this point, it seems appropriate to end this brief discussion of the CodeModule object with a procedure report. This final example produces a unique list of all procedures in the active project along with a line count. The line count is a simple calculation of all lines between a procedural declaration and its terminating block.

The example also employs the GetProcKind transformation and begins to condense variable names. If you understand this bit of code, then you'll be well on the way to writing your own extensibility reports. I'll leave it with you to fill in the blanks.

VB.NET
Public Sub ReportProcNames()

    Dim Component As Object
    Dim Name As String
    Dim Kind As Long
    Dim Start As Long
    Dim Body As Long
    Dim Length As Long
    Dim BodyLines As Long
    Dim Declaration As String
    Dim ProcedureType As String
    Dim Index As Long

    For Each Component In Application.VBE.ActiveVBProject.VBComponents

        With Component.CodeModule

            'The Procedures
            Index = .CountOfDeclarationLines + 1

            Do While Index < .CountOfLines

                Name = .ProcOfLine(Index, Kind)
                Start = .ProcStartLine(Name, Kind)
                Body = .ProcBodyLine(Name, Kind)
                Length = .ProcCountLines(Name, Kind)
                BodyLines = Length - (Body - Start)
                Declaration = Trim(.Lines(Body, 1))
                ProcedureType = GetProcKind(Kind, Declaration)

                Debug.Print Component.Name & "." & Name & "." & _
                    ProcedureType & "." & CStr(BodyLines)

                Index = Start + Length + 1

            Loop

        End With

    Next Component

End Sub

MProject Setup

MProject is a standard VBA module that is available with this article. It contains a single public procedure named ExportProject which is used to extract all of the code in the active VBA project.

To use MProject, the minimum requirement is Office 2003 or later. Also, any targeted Office application must support the VBE interface. (see the support section for details)

To include MProject in your office application, please use the following steps...

  1. Create a folder
  2. Move your office project into the folder
  3. Import the MProject module into the office project
  4. Compile and save the project

It should be considered mandatory to move the office project to its own folder. A call to ExportProject automatically creates a subfolder structure named "VBA" at the current location of the office project file. The VBA folder will contain both a Code and Report subfolder as shown in the following image:

     Image 4  MyOfficeProject
       Image 5  VBA 
         Image 6  Code
         Image 7  Report

At the beginning of each extract run, the Code and Report folders are either created or cleared of all files. Components are then extracted to the Code folder. If a workbook report is requested, it is saved to the Report folder. ExportProject does not alter any other folders or files.

ExportProject Usage

To use ExportProject is easy. Type ExportProject in the immediate window and press enter. An immediate window report should appear detailing the results of the run. The report displays the VBA base folder location and ten summary values which seem the most useful.

ExportProject
BaseFolder 	    C:\Users\Mark Regal\Desktop\MyOfficeProject\VBA
Extracts 	    6
References 	    5
Components 	    5
Procedures 	    11
UniqueNames 	    11
Declarations 	    41
CodeLines 	    250
Comments 	    235
TotalCode 	    291
TotalLines 	    526
Done...

Typically, the extract and component counts will be different. The MProject module is always extracted with the active project, however, it is not included in the counts and calculations unless asked. (see the syntax section for details)

The summary definitions are as follows...

BaseFolder   VBA folder for the current office project
Extracts   Count of all code module extracts
References   Count of all project and type library references
Components   Count of all components used in calculations and counts
Procedures   Count of all procedures
UniqueNames   Count of unique procedure names from all modules
Declarations   Count of all declarations
CodeLines   Count of all lines of code
Comments   Count of all comments and whitespace
TotalCode   Sum of CodeLines + Declarations
TotalLines   Sum of CodeLines + Declarations + Comments

Please note that it should be considered a common practice to selectively comment (in or out) report lines as needed. The report lines are simple Debug.Print statements and exist in the MProject.ExportProject procedure.

Workbook Report

When requested, ExportProject will create an Excel workbook at the end of an extract run. The workbook contains detailed views of the procedures, components, and references in the active project. It also includes a worksheet of the extracted components and their file and path information.

As mentioned in MProject setup, the workbook is always saved to the Report folder in the VBA folder structure. If a workbook is not requested, then an empty Report folder should be expected as it is cleared at the beginning of every extract run.

It is important to note that both the workbook and Immediate report use the same data, displayed at varying levels of detail. Code lines and declarations are counted as actual lines of code. Comments and whitespace are counted as comments, and the total line counts are summaries of the two.

ExportProject Syntax

ExportProject([DisplayWorkbook [,OpenBaseFolder [,ExcludeModule]]])

DisplayWorkbook Optional Boolean value

True displays an Excel workbook report at the completion of a successful run
False (or no value) does not create a report
The default value is False

OpenBaseFolder Optional Boolean value

True opens the base extract folder at completion of a successful run
False (or no value) and no action is taken
The default value is False

ExcludeModule Optional Boolean value

True (or no value) will exclude MProject in all counts and calculations
False will include MProject in all counts and calculations
MProject is always part of the code extract regardless of this setting
The default value is True

*Please note that if the MProject module is renamed, the value of the Module_Name constant must be changed to match the new name.

Version History

  Version      Release Date    
  2.0      2013.11.12    
  1.0      2013.08.20    

Release Notes - Version 2.0

  • Added a unique procedure names worksheet
  • Added a scope column to the procedures worksheet
  • Reformatted the procedures worksheet
  • Reformatted messaging

Release Notes - Version 1.0

  • Initial Release

Office VBE Support

In order to use the codebase in this project, any targeted Office application must support the VBE interface. The easy way to determine if an Office application supports the interface is to use the following steps...

  1. Create a new instance of any Office application to be tested
  2. Open the VBA IDE window of the new instance
  3. Navigate to the immediate window and type Application.VBE

The IntelliSense popup window should appear and if VBE is included in the list, then there is a good chance that this project will work in that application and version. If VBE does not appear in the list, then this project will not work in the tested version of the application.

Troubleshooting Tips

During an extract run, any error will generate a detailed message and the program will exit gracefully. The error message should provide enough information to determine a root cause. Once the error has been resolved, simply re-run ExportProject.

A few tips which might prove useful...

  • Make sure the project compiles without errors
  • Close all extract files and the workbook report before an extract run
  • Verify read-write access is available to the project folder

If required, confirm "Trust access to the VBA project object model" is enabled. In Office 2003, it appears as a Macro Security setting. In Office 2007 and later, it is part of the Trust Center settings. For more information, see Microsoft Knowledge Base article KB282830.

Project References

I've been coding in the VBA language since the day it was made available, but be that as it may, there are plenty of informative sites which can improve on the discussion of the CodeModule object. Microsoft is beginning to shine with its on-line documentation and is a favorite of mine.

The following sites have been used as references for this article:

Final Thoughts

Above all else, two key concepts should be taken from this article. One, the CodeModule object is an editor of VBA code, and two, it can be used to data mine a VBA code module at runtime. With data mining and a bit of ingenuity, many advanced coding techniques are possible. Techniques such as parsing enumerations, and much more.

VBA has always been a challenging language as it is object oriented lite. But it never ceases to amaze how easy it is to use, and how useful it actually turned out to be.

License

This article, along with any associated source code and files, is licensed under The Code Project Open License (CPOL)


Written By
Software Developer
Australia Australia
Creating object models is a wonderfully dynamic process. As components begin to take shape, a model can sometimes reveal capabilities which might not have been imagined when first started.

Comments and Discussions

 
Questionexcellent! Pin
Southmountain17-Nov-20 11:49
Southmountain17-Nov-20 11:49 
PraiseMy vote of 3 Pin
Cody58-Aug-18 15:59
Cody58-Aug-18 15:59 
QuestionIssue with Modules containing compiler directives Pin
Glenn Lloyd14-Apr-17 7:37
Glenn Lloyd14-Apr-17 7:37 
AnswerRe: Issue with Modules containing compiler directives - any updates? Pin
Member 1388060622-Nov-21 13:41
Member 1388060622-Nov-21 13:41 
SuggestionReport Worksheet Count Pin
Member 1185229721-Jul-15 5:08
Member 1185229721-Jul-15 5:08 
GeneralRe: Report Worksheet Count Pin
anne arrowsmith6-Oct-16 8:57
anne arrowsmith6-Oct-16 8:57 
QuestionIt did not work with Microsoft Office 2013 Pin
User 1145144928-Feb-15 5:57
User 1145144928-Feb-15 5:57 
AnswerRe: It did not work with Microsoft Office 2013 Pin
Mark Regal28-Feb-15 7:17
Mark Regal28-Feb-15 7:17 
GeneralRe: It did not work with Microsoft Office 2013 Pin
User 114514491-Mar-15 6:52
User 114514491-Mar-15 6:52 
QuestionVery Elegant Pin
Ken Carley9-Jul-14 8:52
Ken Carley9-Jul-14 8:52 
QuestionRemarkable Sharing Pin
Member 1044796131-Jan-14 12:47
Member 1044796131-Jan-14 12:47 
AnswerRe: Remarkable Sharing Pin
Mark Regal27-Mar-14 23:52
Mark Regal27-Mar-14 23:52 
QuestionYou should mention the scope of Testing ... Pin
Member 103840616-Nov-13 4:09
Member 103840616-Nov-13 4:09 
AnswerRe: You should mention the scope of Testing ... Pin
Mark Regal6-Nov-13 21:01
Mark Regal6-Nov-13 21:01 
GeneralRe: You should mention the scope of Testing ... Pin
Member 103840617-Nov-13 7:53
Member 103840617-Nov-13 7:53 
GeneralRe: You should mention the scope of Testing ... Pin
Mark Regal8-Nov-13 2:07
Mark Regal8-Nov-13 2:07 
GeneralMy vote of 5 Pin
Prasad Khandekar28-Aug-13 18:56
professionalPrasad Khandekar28-Aug-13 18:56 
GeneralRe: My vote of 5 Pin
Mark Regal29-Aug-13 3:40
Mark Regal29-Aug-13 3:40 
GeneralMy vote of 5 Pin
Cindy Meister22-Aug-13 6:52
Cindy Meister22-Aug-13 6:52 
GeneralRe: My vote of 5 Pin
Mark Regal22-Aug-13 23:27
Mark Regal22-Aug-13 23:27 

General General    News News    Suggestion Suggestion    Question Question    Bug Bug    Answer Answer    Joke Joke    Praise Praise    Rant Rant    Admin Admin   

Use Ctrl+Left/Right to switch messages, Ctrl+Up/Down to switch threads, Ctrl+Shift+Left/Right to switch pages.