Programming the VBA Editor
Programming the VBA Editor
aspx
-->
Introduction
You can write code in VBA that reads or modifies other VBA projects, modules, or procedures. This is called
extensibility because extends the editor -- you can use VBA code to create new VBA code. You can use these
features to write custom procedures that create, change, or delete VBA modules and code procedures.
In order to use the code on this page in your projects, you must change two settings.
First, you need to set an reference to the VBA Extensibility library. The library contains the definitions of
the objects that make up the VBProject. In the VBA editor, go the the Tools menu and choose References.
In that dialog, scroll down to and check the entry for Microsoft Visual Basic For Applications Extensibility
5.3. If you do not set this reference, you will receive a User-defined type not defined compiler error.
Next, you need to enable programmatic access to the VBA Project. In Excel 2003 and earlier, go the Tools
menu (in Excel, not in the VBA editor), choose Macros and then the Security item. In that dialog, click on
the Trusted Publishers tab and check the Trust access to the Visual Basic Project setting.
In Excel 2007, click the Developer item on the main Ribbon and then click the Macro Security item in the
Code panel. In that dialog, choose Macro Settings and check the Trust access to the VBA project object
model.
The VBA Project that you are going to change with these procedures must be unlocked. There is no programmatic way to unlock a VBA project (other
than using SendKeys). If the project is locked, you must manually unlock. Otherwise, the procedures will not work.
For information about using creating custom menu items in the Visual Basic Editor, see Menus In The VBA
Editor.
VBIDE
The VBIDE is the object library that defines all the objects and values that make up VBProject and the Visual
Basic Editor. You must reference this library to use the VBA Extensibility objects. To add this reference, open the
VBA editor, open your VBProject in the editor, and go to the Tools menu. There, choose References . In the
References dialog, scroll down to Microsoft Visual Basic for Applications Extensibility 5.3 and check that item in
the list. You can add the reference programmatically with code like:
ThisWorkbook.VBProject.References.AddFromGuid _
GUID:="{0002E157-0000-0000-C000-000000000046}", _
Major:=5, Minor:=3
VBE
The VBE refers to the Visual Basic Editor, which includes all the windows and projects that make up the editor.
VBProject
A VBProject contains all the code modules and components of a single workbook. One workbook has exactly one VBProject. The
VBProject is made up of 1 or more VBComponent objects.
VBComponent
A VBComponent is one object within the VBProject. A VBComponent is a regular code module, a UserForm, a class module, any one
of the Sheet modules, or the ThisWorkbook module (together, the Sheet modules and the ThisWorkbook module are called Document Type modules).
A VBComponent is of one of the following types, identified by the Type property. The following constants are used to identify the Type. The
numeric value of each constant is shown in parentheses.
vbext_ct_ClassModule (2): A class module to create your own objects. See Class Modules for details
about classes and objects.
vbext_ct_Document (100): One of the Sheet modules or the ThisWorkbook module.
vbext_ct_MSForm (3): A UserForm. The visual component of a UserForm in the VBA Editor is called a
Designer.
vbext_ct_StdModule (1): A regular code module. Most of the procedures on this page will work with
these types of components.
CodeModule
A CodeModule is the VBA source code of a VBComponent. You use the CodeModule object to access the code associated with a
VBComponent. A VBComponent has exactly one CodeModule which contains all the code for that component.
CodePane
A CodePane is an open editing window of a CodeModule. When you are typing code, you are entering code into the CodePane.
In the code and descriptions on this page, the term Procedure means a Sub, Function, Property Get,
Property Let, or Property Set procedure. The Extensibility library defines four procedures types, identified
by the following constants. The numeric value of each constant is shown within parentheses.
The rest of this page describes various procedures that modify the various objects of a VBProject.
You can test whether the editor in in sync with code like the following.
With Application.VBE
IsEditorInSync = .ActiveVBProject Is _
.ActiveCodePane.CodeModule.Parent.Collection.Parent
End With
End Function
You can force synchronization with code like the following. This will set the ActiveVBProject to the project
associated with the ActiveCodePane.
Sub SyncVBAEditor()
'=======================================================================
' SyncVBAEditor
' This syncs the editor with respect to the ActiveVBProject and the
' VBProject containing the ActiveCodePane. This makes the project
' that conrains the ActiveCodePane the ActiveVBProject.
'=======================================================================
With Application.VBE
If Not .ActiveCodePane Is Nothing Then
Set .ActiveVBProject = .ActiveCodePane.CodeModule.Parent.Collection.Parent
End If
End With
End Sub
Sub AddModuleToProject()
Dim VBProj As VBIDE.VBProject
Dim VBComp As VBIDE.VBComponent
Sub AddProcedureToModule()
Dim VBProj As VBIDE.VBProject
Dim VBComp As VBIDE.VBComponent
Dim CodeMod As VBIDE.CodeModule
Dim LineNum As Long
Const DQUOTE = """" ' one " character
With CodeMod
LineNum = .CountOfLines + 1
.InsertLines LineNum, "Public Sub SayHello()"
LineNum = LineNum + 1
.InsertLines LineNum, " MsgBox " & DQUOTE & "Hello World" & DQUOTE
LineNum = LineNum + 1
.InsertLines LineNum, "End Sub"
End With
End Sub
You can also build up a String variable with the content of the procedure and insert that string with one call to
InsertLines. For example,
FromVBProject As VBIDE.VBProject, _
ToVBProject As VBIDE.VBProject, _
OverwriteExisting As Boolean) As Boolean
ModuleName is the name of the module you want to copy from one project to another.
FromVBProject is the VBProject that contains the module to be copied. This is the source VBProject.
ToVBProject is the VBProject in to which the module is to be copied. This is the destination VBProject.
OverwriteExisting indicates what to do if ModuleName already exists in the ToVBProject. If this is True
the existing VBComponent will be removed from the ToVBProject. If this is False and the VBComponent
already exists, the function does nothing and returns False.
The function returns True if successful or False is an error occurs. The function will return False if any of the
following are true:
FromVBProject is nothing.
ToVBProject is nothing.
ModuleName is blank.
FromVBProject is locked.
ToVBProject is locked.
ModuleName does not exist in FromVBProject.
ModuleName exists in ToVBProject and OverwriteExisting is False.
The complete code is shown below:
'''''''''''''''''''''''''''''''''''''''''''''
' Do some housekeeping validation.
'''''''''''''''''''''''''''''''''''''''''''''
If FromVBProject Is Nothing Then
CopyModule = False
Exit Function
End If
''''''''''''''''''''''''''''''''''''''''''''''''''''
' FName is the name of the temporary file to be
' used in the Export/Import code.
''''''''''''''''''''''''''''''''''''''''''''''''''''
FName = Environ("Temp") & "\" & ModuleName & ".bas"
If OverwriteExisting = True Then
''''''''''''''''''''''''''''''''''''''
' If OverwriteExisting is True, Kill
' the existing temp file and remove
' the existing VBComponent from the
' ToVBProject.
''''''''''''''''''''''''''''''''''''''
If Dir(FName, vbNormal + vbHidden + vbSystem) <> vbNullString Then
Err.Clear
Kill FName
If Err.Number <> 0 Then
CopyModule = False
Exit Function
End If
End If
With ToVBProject.VBComponents
.Remove .Item(ModuleName)
End With
Else
'''''''''''''''''''''''''''''''''''''''''
' OverwriteExisting is False. If there is
' already a VBComponent named ModuleName,
' exit with a return code of False.
''''''''''''''''''''''''''''''''''''''''''
Err.Clear
Set VBComp = ToVBProject.VBComponents(ModuleName)
If Err.Number <> 0 Then
If Err.Number = 9 Then
' module doesn't exist. ignore error.
Else
' other error. get out with return value of False
CopyModule = False
Exit Function
End If
End If
End If
''''''''''''''''''''''''''''''''''''''''''''''''''''
' Do the Export and Import operation using FName
' and then Kill FName.
''''''''''''''''''''''''''''''''''''''''''''''''''''
FromVBProject.VBComponents(ModuleName).Export Filename:=FName
'''''''''''''''''''''''''''''''''''''
' Extract the module name from the
' export file name.
'''''''''''''''''''''''''''''''''''''
SlashPos = InStrRev(FName, "\")
ExtPos = InStrRev(FName, ".")
CompName = Mid(FName, SlashPos + 1, ExtPos - SlashPos - 1)
''''''''''''''''''''''''''''''''''''''''''''''
' Document modules (SheetX and ThisWorkbook)
' cannot be removed. So, if we are working with
' a document object, delete all code in that
' component and add the lines of FName
' back in to the module.
''''''''''''''''''''''''''''''''''''''''''''''
Set VBComp = Nothing
Set VBComp = ToVBProject.VBComponents(CompName)
Sub CreateEventProcedure()
Dim VBProj As VBIDE.VBProject
Dim VBComp As VBIDE.VBComponent
With CodeMod
LineNum = .CreateEventProc("Open", "Workbook")
LineNum = LineNum + 1
.InsertLines LineNum, " MsgBox " & DQUOTE & "Hello World" & DQUOTE
End With
End Sub
Creating A Procedure
You can use code to create code in a module. The code below creates a simple "Hello World" Sub procedure.
You can either create a new VBComponent to hold the procedure or you can use an existing module. Comment
out the appropriate lines of code.
Sub CreateProcedure()
Dim VBComp As VBIDE.VBComponent
Dim CodeMod As VBIDE.CodeModule
Dim S As String
Dim LineNum As Long
' Use the next two lines to create a new module for the code
'Set VBComp = ThisWorkbook.VBProject.VBComponents.Add(vbext_ct_StdModule)
'VBComp.Name = "NewModule"
' OR use the following line to use an existing module for the code
'Set VBComp = ThisWorkbook.VBProject.VBComponents("Module2")
Sub HelloWorld()
MsgBox "Hello, World"
End Sub
Sub DeleteModule()
Dim VBProj As VBIDE.VBProject
Dim VBComp As VBIDE.VBComponent
Renaming A Module
You can manually rename a module by displaying the Properties window (press F4) for the module and changing
the Name property. You can do this programmatically with
ActiveWorkbook.VBProject.VBComponents("OldName").Name = "NewName"
Sub DeleteProcedureFromModule()
Dim VBProj As VBIDE.VBProject
Dim VBComp As VBIDE.VBComponent
Dim CodeMod As VBIDE.CodeModule
Dim StartLine As Long
Dim NumLines As Long
Dim ProcName As String
ProcName = "DeleteThisProc"
With CodeMod
StartLine = .ProcStartLine(ProcName, vbext_pk_Proc)
NumLines = .ProcCountLines(ProcName, vbext_pk_Proc)
.DeleteLines StartLine:=StartLine, Count:=NumLines
End With
End Sub
Sub DeleteAllVBACode()
Dim VBProj As VBIDE.VBProject
Dim VBComp As VBIDE.VBComponent
Dim CodeMod As VBIDE.CodeModule
Application.VBE.MainWindow.Visible = False
This will hide the VBE window, but you may still see it flicker. To prevent this, you must use the
LockWindowUpdate Windows API function.
Sub EliminateScreenFlicker()
Dim VBEHwnd As Long
Application.VBE.MainWindow.Visible = False
VBEHwnd = FindWindow("wndclass_desked_gsk", _
Application.VBE.MainWindow.Caption)
If VBEHwnd Then
LockWindowUpdate VBEHwnd
End If
'''''''''''''''''''''''''
' your code here
'''''''''''''''''''''''''
Application.VBE.MainWindow.Visible = False
ErrH:
LockWindowUpdate 0&
End Sub
VBComp.Export FileName:=FName
ExportVBComponent = True
End Function
End Function
Sub ListModules()
Dim VBProj As VBIDE.VBProject
Dim VBComp As VBIDE.VBComponent
Dim WS As Worksheet
Dim Rng As Range
This code will list all the procedures in Module1, beginning the listing in cell A1.
Sub ListProcedures()
Dim VBProj As VBIDE.VBProject
Dim VBComp As VBIDE.VBComponent
Dim CodeMod As VBIDE.CodeModule
Dim LineNum As Long
Dim NumLines As Long
Dim WS As Worksheet
Dim Rng As Range
Dim ProcName As String
Dim ProcKind As VBIDE.vbext_ProcKind
Set WS = ActiveWorkbook.Worksheets("Sheet1")
Set Rng = WS.Range("A1")
With CodeMod
LineNum = .CountOfDeclarationLines + 1
Do Until LineNum >= .CountOfLines
ProcName = .ProcOfLine(LineNum, ProcKind)
Rng.Value = ProcName
Rng(1, 2).Value = ProcKindString(ProcKind)
LineNum = .ProcStartLine(ProcName, ProcKind) + _
.ProcCountLines(ProcName, ProcKind) + 1
Set Rng = Rng(2, 1)
Loop
End With
End Sub
FirstLine = .Lines(PInfo.ProcBodyLine, 1)
If StrComp(Left(FirstLine, Len("Public")), "Public", vbBinaryCompare) = 0 Then
PInfo.ProcScope = ScopePublic
ElseIf StrComp(Left(FirstLine, Len("Private")), "Private", vbBinaryCompare) = 0 Then
PInfo.ProcScope = ScopePrivate
ElseIf StrComp(Left(FirstLine, Len("Friend")), "Friend", vbBinaryCompare) = 0 Then
PInfo.ProcScope = ScopeFriend
Else
PInfo.ProcScope = ScopeDefault
End If
PInfo.ProcDeclaration = GetProcedureDeclaration(CodeMod, ProcName, ProcKind, LineSpli
End With
End If
ProcedureInfo = PInfo
End Function
End Function
You can call the ProcedureInfo function using code like the following:
Sub ShowProcedureInfo()
Dim VBProj As VBIDE.VBProject
Dim VBComp As VBIDE.VBComponent
Dim CodeMod As VBIDE.CodeModule
Dim CompName As String
Dim ProcName As String
Dim ProcKind As VBIDE.vbext_ProcKind
Dim PInfo As ProcInfo
CompName = "modVBECode"
ProcName = "ProcedureInfo"
ProcKind = vbext_pk_Proc
Sub SearchCodeModule()
Dim VBProj As VBIDE.VBProject
Dim VBComp As VBIDE.VBComponent
Dim CodeMod As VBIDE.CodeModule
Dim FindWhat As String
Dim SL As Long ' start line
Dim EL As Long ' end line
Dim SC As Long ' start column
Dim EC As Long ' end column
Dim Found As Boolean
FindWhat = "findthis"
With CodeMod
SL = 1
EL = .CountOfLines
SC = 1
EC = 255
Found = .Find(target:=FindWhat, StartLine:=SL, StartColumn:=SC, _
EndLine:=EL, EndColumn:=EC, _
wholeword:=True, MatchCase:=False, patternsearch:=False)
Do Until Found = False
Debug.Print "Found at: Line: " & CStr(SL) & " Column: " & CStr(SC)
EL = .CountOfLines
SC = EC + 1
EC = 255
Found = .Find(target:=FindWhat, StartLine:=SL, StartColumn:=SC, _
EndLine:=EL, EndColumn:=EC, _
wholeword:=True, MatchCase:=False, patternsearch:=False)
Loop
End With
End Sub
End Function
TotalCodeLinesInVBComponent = -1
Exit Function
End If
With VBComp.CodeModule
For N = 1 To .CountOfLines
S = .Lines(N, 1)
If Trim(S) = vbNullString Then
' blank line, skip it
ElseIf Left(Trim(S), 1) = "'" Then
' comment line, skip it
Else
LineCount = LineCount + 1
End If
Next N
End With
TotalCodeLinesInVBComponent = LineCount
End Function
TotalLinesInProject = LineCount
End Function
With VBComp.CodeModule
For N = 1 To .CountOfLines
S = .Lines(N, 1)
If Trim(S) = vbNullString Then
' blank line, skip it
ElseIf Left(Trim(S), 1) = "'" Then
' comment line, skip it
Else
LineCount = LineCount + 1
End If
Next N
End With
TotalCodeLinesInVBComponent = LineCount
End Function
This function will return the total number of code lines in all the components of a VBProject. It ignores blank lines
and comment lines. It will return -1 if the project is locked.
TotalCodeLinesInProject = LineCount
End Function
Dim WB As Workbook
Dim AI As AddIn
Dim VBP As VBIDE.VBProject
End Function
The world's choice for creating NET-based Commercial Quality Add-Ins for Office
Add-In Express Is The Most Important Tool For Creating Commerical Level Components
Learn more about Excel and VBA (Visual Basic for Applications).
Cite this page as:
Source: www.cpearson.com/excel/vbe.aspx Copyright 2018, Charles H. Pearson Citation Information
This site created with Microsoft Visual Studio 2013 Premium and ASP.NET 4