Programming The VBA Editor
Programming The VBA Editor
This page describes how to write code that modifies or reads other VBA code.
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 used 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.
y
First, you need to set an reference to the VBA Extensibililty 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.
CAUTION: Many VBA-based computer viruses propagate themselves by creating and/or modifying VBA code. Therefore, many virus scanners may automatically and without warning or confirmation delete modules that reference the VBProject object, causing a permanent and irretrievable loss of code. Consult the documentation for your anti-virus software for details. For information about using creating custom menu items in the Visual Basic Editor, see Menus In The VBA 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 code module, a
UserForm, a class module, 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.
y y y y
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. CodePane A CodePane is an open editing window of a CodeModule.
''''''''''''''''''''''''''''''''''''''''''' Set VBProj = VBAEditor.ActiveVBProject ' or Set VBProj = Application.Workbooks("Book1.xls").VBProject ''''''''''''''''''''''''''''''''''''''''''' Set VBComp = ActiveWorkbook.VBProject.VBComponents("Module1") ' or Set VBComp = VBProj.VBComponents("Module1") ''''''''''''''''''''''''''''''''''''''''''' Set CodeMod = ActiveWorkbook.VBProject.VBComponents("Module1").CodeModule ' or Set CodeMod = VBComp.CodeModule
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.
y y y y
vbext_pk_Get (3). A Property Get procedure. vbext_pk_Let (1). A Property Let procedure. vbext_pk_Set (2). A Property Set procedure. vbext_pk_Proc (0). A Sub or Function procedure.
The rest of this page describes various procedures that modify the various objects of a VBProject.
' IsEditorInSync ' This tests if the VBProject selected in the Project window, and ' therefore the ActiveVBProject is the same as the VBProject associated ' with the ActiveCodePane. If these two VBProjects are the same, ' the editor is in sync and the result is True. If these are not the ' same project, the editor is out of sync and the result is True. '=============================================================== ======== 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 theActiveCodePane. 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
This code will add new code module named NewModule to the VBProject of the active workbook. The type of VBComponent is specified by the value of the parameter passed to the Add method. Sub AddModuleToProject() Dim VBProj As VBIDE.VBProject Dim VBComp As VBIDE.VBComponent Set VBProj = ActiveWorkbook.VBProject Set VBComp = VBProj.VBComponents.Add(vbext_ct_StdModule) VBComp.Name = "NewModule" End Sub
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.
Function CopyModule(ModuleName As String, _ FromVBProject As VBIDE.VBProject, _ ToVBProject As VBIDE.VBProject, _ OverwriteExisting As Boolean) As Boolean ''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''' ' CopyModule
' This function copies a module from one VBProject to ' another. It returns True if successful or False ' if an error occurs. ' ' Parameters: ' -------------------------------' FromVBProject The VBProject that contains the module ' to be copied. ' ' ToVBProject The VBProject into which the module is ' to be copied. ' ' ModuleName The name of the module to copy. ' ' OverwriteExisting If True, the VBComponent named ModuleName ' in ToVBProject will be removed before ' importing the module. If False and ' a VBComponent named ModuleName exists ' in ToVBProject, the code will return ' False. ' ''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''' Dim Dim Dim Dim Dim Dim Dim VBComp As VBIDE.VBComponent FName As String CompName As String S As String SlashPos As Long ExtPos As Long TempVBComp As VBIDE.VBComponent
''''''''''''''''''''''''''''''''''''''''''''' ' Do some housekeeping validation. ''''''''''''''''''''''''''''''''''''''''''''' If FromVBProject Is Nothing Then CopyModule = False Exit Function End If If Trim(ModuleName) = vbNullString Then CopyModule = False
Exit Function End If If ToVBProject Is Nothing Then CopyModule = False Exit Function End If If FromVBProject.Protection = vbext_pp_locked Then CopyModule = False Exit Function End If If ToVBProject.Protection = vbext_pp_locked Then CopyModule = False Exit Function End If On Error Resume Next Set VBComp = FromVBProject.VBComponents(ModuleName) If Err.Number <> 0 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)
If VBComp Is Nothing Then ToVBProject.VBComponents.Import Filename:=FName Else If VBComp.Type = vbext_ct_Document Then ' VBComp is destination module Set TempVBComp = ToVBProject.VBComponents.Import(FName) ' TempVBComp is source module With VBComp.CodeModule .DeleteLines 1, .CountOfLines S = TempVBComp.CodeModule.Lines(1, TempVBComp.CodeModule.CountOfLines) .InsertLines 1, S End With On Error GoTo 0 ToVBProject.VBComponents.Remove TempVBComp End If End If Kill FName CopyModule = True End Function
LineNum = LineNum + 1 .InsertLines LineNum, " "Hello World" & DQUOTE End With End Sub
With CodeMod StartLine = .ProcStartLine(ProcName, vbext_pk_Proc) NumLines = .ProcCountLines(ProcName, vbext_pk_Proc) .DeleteLines StartLine:=StartLine, Count:=NumLines End With End Sub
Private Declare Function FindWindow Lib "user32" Alias "FindWindowA" _ (ByVal ClassName As String, ByVal WindowName As String) As Long Private Declare Function LockWindowUpdate Lib "user32" _ (ByVal hWndLock As Long) As Long Sub EliminateScreenFlicker() Dim VBEHwnd As Long On Error GoTo ErrH: 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
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''' ''''''''' ' This function exports the code module of a VBComponent to a text ' file. If FileName is missing, the code will be exported to ' a file with the same name as the VBComponent followed by the ' appropriate extension. '''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''' ''''''''' Dim Extension As String Dim FName As String Extension = GetFileExtension(VBComp:=VBComp) If Trim(FileName) = vbNullString Then FName = VBComp.Name & Extension Else FName = FileName If InStr(1, FName, ".", vbBinaryCompare) = 0 Then FName = FName & Extension End If End If If StrComp(Right(FolderName, 1), "\", vbBinaryCompare) = 0 Then FName = FolderName & FName Else FName = FolderName & "\" & FName End If If Dir(FName, vbNormal + vbHidden + vbSystem) <> vbNullString Then If OverwriteExisting = True Then Kill FName Else ExportVBComponent = False Exit Function End If End If VBComp.Export FileName:=FName ExportVBComponent = True End Function
Public Function GetFileExtension(VBComp As VBIDE.VBComponent) As String '''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''' ''''''' ' This returns the appropriate file extension based on the Type of ' the VBComponent. '''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''' ''''''' Select Case VBComp.Type Case vbext_ct_ClassModule GetFileExtension = ".cls" Case vbext_ct_Document GetFileExtension = ".cls" Case vbext_ct_MSForm GetFileExtension = ".frm" Case vbext_ct_StdModule GetFileExtension = ".bas" Case Else GetFileExtension = ".bas" End Select End Function
Function ComponentTypeToString(ComponentType As VBIDE.vbext_ComponentType) As String Select Case ComponentType Case vbext_ct_ActiveXDesigner ComponentTypeToString = "ActiveX Designer" Case vbext_ct_ClassModule ComponentTypeToString = "Class Module" Case vbext_ct_Document ComponentTypeToString = "Document Module" Case vbext_ct_MSForm ComponentTypeToString = "UserForm" Case vbext_ct_StdModule ComponentTypeToString = "Code Module" Case Else ComponentTypeToString = "Unknown Type: " & CStr(ComponentType) End Select End Function
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
Function ProcKindString(ProcKind As VBIDE.vbext_ProcKind) As String Select Case ProcKind Case vbext_pk_Get ProcKindString = "Property Get" Case vbext_pk_Let ProcKindString = "Property Let" Case vbext_pk_Set ProcKindString = "Property Set" Case vbext_pk_Proc ProcKindString = "Sub Or Function" Case Else ProcKindString = "Unknown Type: " & CStr(ProcKind) End Select End Function
ScopePublic = 2 ScopeFriend = 3 ScopeDefault = 4 End Enum Public Enum LineSplits LineSplitRemove = 0 LineSplitKeep = 1 LineSplitConvert = 2 End Enum Public Type ProcInfo ProcName As String ProcKind As VBIDE.vbext_ProcKind ProcStartLine As Long ProcBodyLine As Long ProcCountLines As Long ProcScope As ProcScope ProcDeclaration As String End Type Function ProcedureInfo(ProcName As String, ProcKind As VBIDE.vbext_ProcKind, _ CodeMod As VBIDE.CodeModule) As ProcInfo Dim Dim Dim Dim PInfo As ProcInfo BodyLine As Long Declaration As String FirstLine As String
BodyLine = CodeMod.ProcStartLine(ProcName, ProcKind) If BodyLine > 0 Then With CodeMod PInfo.ProcName = ProcName PInfo.ProcKind = ProcKind PInfo.ProcBodyLine = .ProcBodyLine(ProcName, ProcKind) PInfo.ProcCountLines = .ProcCountLines(ProcName, ProcKind) PInfo.ProcStartLine = .ProcStartLine(ProcName, ProcKind) 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, LineSplitKeep) End With End If ProcedureInfo = PInfo End Function
Public Function GetProcedureDeclaration(CodeMod As VBIDE.CodeModule, _ ProcName As String, ProcKind As VBIDE.vbext_ProcKind, _ Optional LineSplitBehavior As LineSplits = LineSplitRemove) '''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''' ''''''''''''''''''''' ' GetProcedureDeclaration ' This return the procedure declaration of ProcName in CodeMod. The LineSplitBehavior ' determines what to do with procedure declaration that span more than one line using ' the "_" line continuation character. If LineSplitBehavior is LineSplitRemove, the ' entire procedure declaration is converted to a single line of text. If ' LineSplitBehavior is LineSplitKeep the "_" characters are retained and the ' declaration is split with vbNewLine into multiple lines. If LineSplitBehavior is ' LineSplitConvert, the "_" characters are removed and replaced with vbNewLine. ' The function returns vbNullString if the procedure could not be found.
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''' ''''''''''''''''''''' Dim LineNum As Long Dim S As String Dim Declaration As String On Error Resume Next LineNum = CodeMod.ProcBodyLine(ProcName, ProcKind) If Err.Number <> 0 Then Exit Function End If S = CodeMod.Lines(LineNum, 1) Do While Right(S, 1) = "_" Select Case True Case LineSplitBehavior = LineSplitConvert S = Left(S, Len(S) - 1) & vbNewLine Case LineSplitBehavior = LineSplitKeep S = S & vbNewLine Case LineSplitBehavior = LineSplitRemove S = Left(S, Len(S) - 1) & " " End Select Declaration = Declaration & S LineNum = LineNum + 1 S = CodeMod.Lines(LineNum, 1) Loop Declaration = SingleSpace(Declaration & S) GetProcedureDeclaration = Declaration
End Function Private Function SingleSpace(ByVal Text As String) As String Dim Pos As String Pos = InStr(1, Text, Space(2), vbBinaryCompare) Do Until Pos = 0 Text = Replace(Text, Space(2), Space(1)) Pos = InStr(1, Text, Space(2), vbBinaryCompare) Loop SingleSpace = Text End Function
You can call the ProcedureInfo function using code like the following:
CodeMod As VBIDE.CodeModule CompName As String ProcName As String ProcKind As VBIDE.vbext_ProcKind PInfo As ProcInfo
CompName = "modVBECode" ProcName = "ProcedureInfo" ProcKind = vbext_pk_Proc Set VBProj = ActiveWorkbook.VBProject Set VBComp = VBProj.VBComponents(CompName) Set CodeMod = VBComp.CodeModule PInfo = ProcedureInfo(ProcName, ProcKind, CodeMod) Debug.Print "ProcName: " & PInfo.ProcName Debug.Print "ProcKind: " & CStr(PInfo.ProcKind) Debug.Print "ProcStartLine: " & CStr(PInfo.ProcStartLine) Debug.Print "ProcBodyLine: " & CStr(PInfo.ProcBodyLine) Debug.Print "ProcCountLines: " & CStr(PInfo.ProcCountLines) Debug.Print "ProcScope: " & CStr(PInfo.ProcScope) Debug.Print "ProcDeclaration: " & PInfo.ProcDeclaration End Sub
FindWhat As String SL As Long ' start line EL As Long ' end line SC As Long ' start column EC As Long ' end column Found As Boolean
Set VBProj = ActiveWorkbook.VBProject Set VBComp = VBProj.VBComponents("Module1") Set CodeMod = VBComp.CodeModule 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
Public Function VBComponentExists(VBCompName As String, Optional VBProj As VBIDE.VBProject = Nothing) As Boolean '''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''' '''''''''''' ' This returns True or False indicating whether a VBComponent named ' VBCompName exists in the VBProject referenced by VBProj. If VBProj ' is omitted, the VBProject of the ActiveWorkbook is used. '''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''' '''''''''''' Dim VBP As VBIDE.VBProject If VBProj Is Nothing Then Set VBP = ActiveWorkbook.VBProject Else Set VBP = VBProj End If On Error Resume Next VBComponentExists = CBool(Len(VBP.VBComponents(VBCompName).Name)) End Function
Dim S As String Dim LineCount As Long If VBComp.Collection.Parent.Protection = vbext_pp_locked Then 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
Dim VBP As VBIDE.VBProject Dim VBComp As VBIDE.VBComponent Dim LineCount As Long If VBProj Is Nothing Then Set VBP = ActiveWorkbook.VBProject Else Set VBP = VBProj End If If VBP.Protection = vbext_pp_locked Then TotalLinesInProject = -1 Exit Function End If For Each VBComp In VBP.VBComponents LineCount = LineCount + VBComp.CodeModule.CountOfLines Next VBComp TotalLinesInProject = LineCount End Function
If VBComp.Collection.Parent.Protection = vbext_pp_locked Then 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
If VBProj.Protection = vbext_pp_locked Then TotalCodeLinesInProject = -1 Exit Function End If For Each VBComp In VBProj.VBComponents LineCount = LineCount + TotalCodeLinesInVBComponent(VBComp) Next VBComp TotalCodeLinesInProject = LineCount End Function
If IsObject(WhichVBP) = True Then ' If WhichVBP is an object, it must be of the ' type VBIDE.VBProject. Any other object type ' throws an error 13 (type mismatch). On Error GoTo 0 If TypeOf WhichVBP Is VBIDE.VBProject Then Set VBP = WhichVBP Else Err.Raise 13 End If Else On Error Resume Next Err.Clear ' Here, WhichVBP is either the string name of ' the VBP or its ordinal index number. Set VBP = Application.VBE.VBProjects(WhichVBP) On Error GoTo 0 If VBP Is Nothing Then Err.Raise 9 End If End If For Each WB In Workbooks If WB.VBProject Is VBP Then Set WorkbookOfVBProject = WB Exit Function End If Next WB ' not found in workbooks, search installed add-ins. For Each AI In Application.AddIns If AI.Installed = True Then If Workbooks(AI.Name).VBProject Is VBP Then Set WorkbookOfVBProject = Workbooks(AI.Name) Exit Function End If End If Next AI End Function
Workbook and worksheet code modules The ThisWorkbook and worksheet code modules are a type of class module that are tied to instances of their class objects (the Workbook object and the worksheet objects). In the folder hierarchy, they are stored in the Microsoft Excel Objects folder. These modules generally should be reserved for event macros. As class modules, unqualified references (such as Range("A1")) refer to their class object, which is different than what happens in regular code modules (where an unqualified Range("A1") refers to the ActiveSheet at the time of evaluation). In addition, if you put your regular code into the ThisWorkbook or a sheet module, you'll have to fully qualify your macro call (e.g., Sheet1.MyMacro instead of just MyMacro). The ThisWorkbook module and Sheet modules are created automatically when you create a new workbook or insert a sheet. Regular code modules Regular, or Standard code modules are where you should put the majority of your macro code, your User Defined Functions (UDFs), and any global variables. In the folder hierarchy, they are stored in the Modules folder. These modules are accessible from everywhere in the project (unless you use Option Private), so you may put your Sub or Function in any regular code module, and you may have as many regular code modules as you wish. Unlike the workbook and worksheet code modules, unqualified references like Range("A1") will by default refer to the ActiveSheet. You can create a new regular code module in the VBE by choosing Insert/Module. Userform code modules Userform code modules, which are another type of class module, are tied to their Userform objects, and reside in the Forms folder within the folder hierarchy. Like worksheet code modules, these modules should be reserved for the event macros of the form (such as Initialize() and Terminate()) and its controls (such as
CommandButton1_Click() or Listbox1_Change()), or code which is completely internal to the form. The Userform code module is created automatically when you create a userform in the VBE by choosing Insert/Userform. Class modules Class modules can be used to create new objects, with properties and methods of their own. They may inherit events from the Application object (see Chip Pearson's treatment of Application Level Events). Class modules are created in the VBE by choosing Insert/Class Module, and they reside in the Class Modules folder in the folder hierarchy
Standard Code Modules, which contain custom macros and functions, Workbook And Sheet Code Modules, which contain event procedures for the workbook, and worksheets and chart sheets, User Forms, which contain code for the controls on a UserForm object, Class Modules, which contain Property Let, Get, and Set procedures for Objects that you create.
It matters very much where you put your code. NOTE: I must add, for the sake of accuracy, that the Sheet modules, the ThisWorkbook module, and the Userform modules are all really just different flavors of Class Modules. You can create Property Get/Let/Set procedures, and methods and functions (and events) in these classes, just as you can for "standard" class modules. Various techniques for using your forms and sheets as classes will be described in the "Advanced Form Techniques" page, coming to a server near you very soon. Standard Code Modules, also called simply Code Modules or just Modules, are where you put most of your VBA code. Your basic macros and your custom function (User Defined Functions) should be in these modules. For the novice programmer, all your code will be in standard modules. In addition to your basic procedures, the code modules should contain any Declare statements to external functions (Windows APIs or other DLLs), and custom Data Structures defined with the Type statement. Your workbook's VBA Project can contain as many standard code modules as you want. This makes it easy to split your procedure into different modules for organization and ease of maintenance. For example, you could put all your database procedures in a module named DataBase, and all your mathematical procedures in another module called Math. As long as a procedure isn't declared with the Private keyword, or the module isn't marked as private, you can call any procedure in any module from any other module without doing anything special. Workbook And Sheet Modules are special modules tied directly to the Workbook object and to each Sheet object. The module for the workbook is called ThisWorkbook, and each Sheet module has the same name as the sheet that it is part of. These modules should contain the event procedures for the object, and that's all. If you put the event procedures in a standard code
module, Excel won't find them, so they won't be executed. And if you put ordinary procedures in a workbook or sheet module, you won't be able to call them without fully qualifying the reference. User Form Modules are part of the UserForm object, and contain the event procedures for the controls on that form. For example, the Click event for a command button on a UserForm is stored in that UserForm's code module. Like workbook and sheet modules, you should put only event procedures for the UserForm controls in this module. Class Modules are used to create new objects. Class modules aren't discussed here, except to say that a class module is used to handle Application Event Procedures.
Code Names
Workbook and sheet modules have a property called CodeName, which is how the object is know internally to VBA. By default, the workbook code name is ThisWorkbook, and each sheet module is Sheet1, Sheet2, etc for Worksheets, or Chart1, Chart2, etc for ChartSheets. You can use these names in your VBA code as you would normal variables. For example Msgbox ThisWorkbook.Name or Msgbox Sheet1.Name This is useful so that you can always refer to a worksheet, for example, even if the user renames the sheet from Excel. For example, if you have a sheet called "Sheet1", both its name and code name will be Sheet1. But if the user renames the sheet to MySheet, the code Msgbox Worksheets("Sheet1").Name will fail, because there is no longer a sheet named Sheet1. However, the code Msgbox Sheet1.Name will continue to work, because VBA still knows that worksheet by its code name of Sheet1. You can change the code name of either the ThisWorkbook or a Sheet object. If you do this once you already have code in these modules, you can run into problems, so only do this if you 1) know what you're doing, and 2) need to do this. To change the code name of a module, select the module in the Project Explorer window, and the open the Properties Windows (F4 or from the View menu), and change the Name property. If you change the code name of the ThisWorkbook object, ThisWorkbook will continue to refer to the workbook object. For example, if you change the code name of the ThisWorkbook object to MyWorkbook, both of the following lines of code will work: Msgbox ThisWorkbook.Name
Msgbox MyWorkbook.Name However, if you change the code name for the Sheet1 object to MySheet, the following code will fail Msgbox Sheet1.Name because there is no longer a sheet object with a code name of Sheet1. Moreover, you can change the code name of an object with a VBA procedure. However, this can lead to many problems, so again, don't do it unless you know what you're doing and you really need to do this. To change the code name of sheet with a code name of Sheet1 to NewCodeName, use ThisWorkbook.VBProject.VBComponents("Sheet2").Name= "NewCodeName" You can change the code name of the ThisWorkbook object to "NewWBName" with ThisWorkbook.VBProject.VBComponents("ThisWorkbook").Name = "NewWBName" Just to make things more complicated, when you change the code name of the ThisWorkbook object, and you're using the VBA Extensibility library procedures, the code Msgbox ThisWorkbook.Name will continue to work, but Msgbox ThisWorkbook.VBProject.VBComponents("ThisWorkbook").Name will fail, because there is no object with a code name ThisWorkbook. In general, changing code names is not for the casual user. For more information about programming the VBA components, see Programming To The VBE.
were going through the VBE interface. This page applies only to Excel97 and above. It does not apply to Excel95 or previous versions. This pages describes a few of the objects, methods, and properties of the VBE that you can manipulate from VBA. In Excel97, these objects, methods, and properties are not described in the normal VBA help files. You need to open the file called VEENOB3.hlp. This file many not have been installed on your system when you installed the VBA help files and Office97. You can find it in the MoreHelp folder on your Excel or Office CD. You many want to have a macro, assigned to a menu item or a shortcut key to easily display this file. Sub ShowVBEHelp() Shell "c:\windows\winhelp.exe veenob3.hlp", vbNormalFocus End Sub In Excel 2000 later, these topics are included in the standard VBA help files.
VBA Editor page. Note: An additional level of security was added in Excel 2002. To manipulate the VBA Project objects as described here, you'll have to change your security setting. Go to the Tools menu, choose Macros, then Security. Click the "Trusted Sources" tab, and put a check next to the "Trust access to Visual Basic Project". NOTE: In all versions of Excel, the VBProject must not be protected. If it is, these procedures will fail. There is no programmatic way to unlock a locked project. In Excel 2002 and later, you must have "Trust Access To Visual Basic Project" enabled. To enable this setting, go to the Tools menu in Excel, choose Macros, Security, then the "Trusted Sources" tab, and put a check next to "Trust Access To Visual Basic Project". Otherwise, you will get errors. Also, you may get unpredictable results if you attempt to modify a code module's code from that same module. That is, having code in Module1 modify the contents of Module1. I recommend that you do not do this. NOTE: Many macro-based viruses propagate themselves by writing code using the methods described on this page. Therefore, many if not all virus scanning programs will automatically delete code that manipulates VBA code. Some programs will delete the entire code module. You may want to turn off your virus scanner when working with workbooks that manipulate VBA code projects.
VBE Objects
We'll be using three of these objects in our code: VBProject This is the entire set of VBA modules and references associated with a workbook. VBComponent This is the individual component within a VBProject. For example, a UserForm and a standard code module are each a VBComponent. The VBComponents collection contains each existing VBComponent object. CodeModule This object represents the actual code contained in a VBComponent. For example, when you enter code into Module1, you're entering code into the CodeModule object of the VBComponent named "Module1". We'll be programmatically "navigating" to these components through the Workbook object. You can also get to these components by going through the Application.VBE object path, but we won't be doing this. There are various types of VBComponents, identified by the Type property of the VBComponent object.
Type Constant Description
vbext_ct_ClassModuleThis is a class module, used to create your own objects. We won't be using these here. vbext_ct_Document This is the component for a worksheet, chart sheet, or ThisWorkbook. This is the component for a UserForm. The visual representation of the form in the VBE is called a desiger. This is the component for a standard code module. Most of our procedures will work with these components.
vbext_ct_MSForm
vbext_ct_StdModule
ThisWorkbook.VBProject.VBComponents.Add(vbext_ct_StdModule) VBComp.Name = "NewModule" Application.Visible = True End Sub When you run this code from Excel while the VBE is open, you will be taken to the new module's code module, and the macro will terminate. When you run this code while the VBE is not open, your Excel application will be visible, but will not have focus. The statement Application.Visible = True returns focus back to the Excel application.
End Sub Pay attention to the way in which the .InsertLines method is called. The entire procedure is passed as one argument -- a string with embedded Chr(13) characters for the line breaks. The code statement Application.Run "MyNewProcedure" will run the new procedure. You must use Application.Run rather than calling the procedure directly in order to prevent compile-time errors. This method will work only if you are adding code to another code module. If you are adding code a the same code module, you must use an Application.OnTime method, so that control is returned to Excel, and the module can be recompiled and reloaded. Using Application.OnTime may have some synchronizations problems, so you should avoid calling a procedure that you've just added to the same code module without allowing all VBA procedures to come to an end. Application.OnTime Now,"NewProcedureName"
named "NewModule" in ThisWorkbook. Sub DeleteProcedure() Dim VBCodeMod As CodeModule Dim StartLine As Long Dim HowManyLines As Long Set VBCodeMod = ThisWorkbook.VBProject.VBComponents("NewModule").CodeModule With VBCodeMod StartLine = .ProcStartLine("MyNewProcedure", vbext_pk_Proc) HowManyLines = .ProcCountLines("MyNewProcedure", vbext_pk_Proc) .DeleteLines StartLine, HowManyLines End With End Sub
Set VBCodeMod = ThisWorkbook.VBProject.VBComponents("NewModule").CodeModule With VBCodeMod StartLine = 1 HowManyLines = .CountOfLines .DeleteLines StartLine, HowManyLines End With End Sub
Dim VBComp As VBComponent Dim Msg As String For Each VBComp In ThisWorkbook.VBProject.VBComponents Msg = Msg & VBComp.Name & " Type: " & CompTypeToName(VBComp) & Chr(13) Next VBComp MsgBox Msg End Sub
Function CompTypeToName(VBComp As VBComponent) As String Select Case VBComp.Type Case vbext_ct_ActiveXDesigner CompTypeToName = "ActiveX Designer" Case vbext_ct_ClassModule CompTypeToName = "Class Module" Case vbext_ct_Document CompTypeToName = "Document" Case vbext_ct_MSForm CompTypeToName = "MS Form" Case vbext_ct_StdModule CompTypeToName = "Standard Module" Case Else End Select End Function
' ProcsToArray ' This will load an array of strings with the type and name of ' each procedure in the specified code module. This procedure ' populates the array ProcArray with the type and name of each ' procedure in the code module. ProcArray must be a dynamic array ' of strings. The existing contents of ProcArray are destroyed. ' Upon completion, each element of ProcArray will be the type ' of procedure (GET,LET,SET, or PROC) followed by a colon ' followed by the name of the proceudre. E.g., "SET:Prop1". ' You can use the Split function to separate the type from the ' name. ProcArray will be a 1-based array. ' The function returns the number of procedures listed in ProcArray. '''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''' Dim Dim Dim Dim Dim LineNumber As String ProcType As VBIDE.vbext_ProcKind ProcNdx As Long ProcName As String ProcTypeName As String
Erase ProcArray LineNumber = CodeMod.CountOfDeclarationLines + 1 ProcName = CodeMod.ProcOfLine(LineNumber, ProcType) Do Until (ProcName = vbNullString) Or (LineNumber >= CodeMod.CountOfLines) ProcNdx = ProcNdx + 1 ReDim Preserve ProcArray(1 To ProcNdx) Select Case True Case ProcType = vbext_pk_Get ProcTypeName = "GET" Case ProcType = vbext_pk_Let ProcTypeName = "LET" Case ProcType = vbext_pk_Proc ProcTypeName = "PROC" Case ProcType = vbext_pk_Set ProcTypeName = "SET" Case Else ProcTypeName = "UNK" ' unknown type End Select ProcArray(ProcNdx) = ProcTypeName & ":" & ProcName LineNumber = LineNumber + CodeMod.ProcCountLines(ProcName, ProcType) ProcName = CodeMod.ProcOfLine(LineNumber, ProcType) Loop ProcsToArray = ProcNdx End Function
Procs() As String ' array in which to store procedure information ProcName As String ' procedure name ProcType As String ' procedure type ProcCount As Long ' number of procedures found Arr As Variant ' array for Split function CodeMod As VBIDE.CodeModule Ndx As Long
Set CodeMod = ThisWorkbook.VBProject.VBComponents("Class1").CodeModule ProcCount = ProcsToArray(CodeMod, Procs) Debug.Print "Procs Found: " & CStr(ProcCount) If ProcCount > 0 Then For Ndx = LBound(Procs) To UBound(Procs) Arr = Split(Procs(Ndx), ":") ProcType = Arr(LBound(Arr)) ProcName = Arr(LBound(Arr) + 1) Debug.Print "Proc Type: " & ProcType, "Proc Name: " & ProcName Next Ndx End If End Sub
Also see Code Modules And Code Names for more information about the CodeName property of VBComponents.
ProcName As String ProcType As VBIDE.vbext_ProcKind ProcTypeString As String ProcNdx As Long ProcCounter As Long ProcString As String
If VBP.Protection = vbext_pp_locked Then Exit Function End If Erase Procs For Each VBComp In VBP.VBComponents Set CodeMod = VBComp.CodeModule LineNum = CodeMod.CountOfDeclarationLines + 1 ProcName = CodeMod.ProcOfLine(LineNum, ProcType) Do Until LineNum >= CodeMod.CountOfLines ProcNdx = ProcNdx + 1 ReDim Preserve Procs(1 To ProcNdx) Select Case True Case ProcType = vbext_pk_Get ProcTypeString = "GET" Case ProcType = vbext_pk_Let ProcTypeString = "LET" Case ProcType = vbext_pk_Proc ProcTypeString = "PROC" Case ProcType = vbext_pk_Set ProcTypeString = "SET" End Select ProcString = VBComp.Name & ":" & ProcTypeString & ":" & ProcName Procs(ProcNdx) = ProcString ProcCounter = ProcCounter + 1 LineNum = LineNum + CodeMod.ProcCountLines(ProcName, ProcType) + 1 ProcName = CodeMod.ProcOfLine(LineNum, ProcType) Loop Next VBComp ListAllProcsInProject = ProcCounter End Function
You can loop through the Procs array and use the Split function to break each string into its components, as shown in the procedure below.
Sub ListProcsInProject() Dim Dim Dim Dim Dim Dim Dim Dim Procs() As String ProcCount As Long VBP As VBIDE.VBProject Ndx As Long Arr As Variant ModuleName As String ProcType As String ProcName As String
Debug.Print "Procs Found: " & CStr(ProcCount) If ProcCount > 0 Then For Ndx = LBound(Procs) To UBound(Procs) Arr = Split(Procs(Ndx), ":") ModuleName = Arr(LBound(Arr)) ProcType = Arr(LBound(Arr) + 1) ProcName = Arr(LBound(Arr) + 2) Debug.Print "Module: " & ModuleName, "Type: " & ProcType, "Name: " & ProcName Next Ndx Else Debug.Print "No procs found" End If End Sub
' declaration is split with vbNewLine into multiple lines. If LineSplitBehavior is ' LineSplitConvert, the "_" characters are removed and replaced with vbNewLine. ' The function returns vbNullString if the procedure could not be found. '''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''' ''''''''' Dim LineNum As Long Dim S As String Dim Declaration As String On Error Resume Next LineNum = CodeMod.ProcBodyLine(ProcName, ProcKind) If Err.Number <> 0 Then Exit Function End If S = CodeMod.Lines(LineNum, 1) Do While Right(S, 1) = "_" Select Case True Case LineSplitBehavior = LineSplitConvert S = Left(S, Len(S) - 1) & vbNewLine Case LineSplitBehavior = LineSplitKeep S = S & vbNewLine Case LineSplitBehavior = LineSplitRemove S = Left(S, Len(S) - 1) & " " End Select Declaration = Declaration & S LineNum = LineNum + 1 S = CodeMod.Lines(LineNum, 1) Loop Declaration = SingleSpace(Declaration & S) GetProcedureDeclaration = Declaration End Function Private Function SingleSpace(ByVal Text As String) As String Dim Pos As String Pos = InStr(1, Text, Space(2), vbBinaryCompare) Do Until Pos = 0 Text = Replace(Text, Space(2), Space(1)) Pos = InStr(1, Text, Space(2), vbBinaryCompare) Loop SingleSpace = Text End Function
Sub ExportAllVBA() Dim VBComp As VBIDE.VBComponent Dim Sfx As String For Each VBComp In ActiveWorkbook.VBProject.VBComponents Select Case VBComp.Type Case vbext_ct_ClassModule, vbext_ct_Document Sfx = ".cls" Case vbext_ct_MSForm Sfx = ".frm" Case vbext_ct_StdModule Sfx = ".bas" Case Else Sfx = "" End Select If Sfx <> "" Then VBComp.Export _ Filename:=ActiveWorkbook.Path & "\" & VBComp.Name & Sfx End If Next VBComp End Sub
hide itself. To prevent this screen flickering, you need to use the LockWindowUpdate API function. Put the following function declares at the top of your code module, before and outside of any procedures. Note that the Declare statements below must appear outside of and above any procedure in the module. Private Declare Function FindWindow Lib "user32" Alias "FindWindowA" _ (ByVal ClassName As String, ByVal WindowName As String) As Long Private Declare Function LockWindowUpdate Lib "user32" _ (ByVal hWndLock As Long) As Long Then, in your code, use code like the following: Dim VBEHwnd As Long On Error Goto ErrH: Application.VBE.MainWindow.Visible = False VBEHwnd = FindWindow("wndclass_desked_gsk", _ Application.VBE.MainWindow.Caption) If VBEHwnd Then LockWindowUpdate VBEHwnd End If ' ' your code to write code ' Application.VBE.MainWindow.Visible = False ErrH: LockWindowUpdate 0& You may still see the title bar of Excel momentarily dim, but the VBA Editor will not be visible at all. If you already have error handling code in your procedure that writes the VBA code, you want to be sure to call LockWindowUpdate 0&.You MUST call LockWindowUpdate 0&.
The code above will work in Excel 2000 and later. It has not been tested in Excel97
An advantage of the registry is that the numbers are unlikely to be inadvertently modified or deleted. A significant disadvantage is that the registry is not designed as a database, which can retain a history, but rather is more suited to storage of a single record. Information is stored in the registry using the SaveSetting method, and retrieved using the GetSetting method. This macro, put in a template's ThisWorkbook code module, will produce an incremented sequential number each time the template is used to generate a document:
Private Sub Workbook_Open() Const sAPPLICATION As String = "Excel" Const sSECTION As String = "Invoice" Const sKEY As String = "Invoice_key" Const nDEFAULT As Long = 1& Dim nNumber As Long With ThisWorkbook.Sheets("Invoice") With .Range("B1") If IsEmpty(.Value) Then .Value = Date .NumberFormat = "dd mmm yyyy" End If End With With .Range("B2") If IsEmpty(.Value) Then nNumber = GetSetting(sAPPLICATION, sSECTION, sKEY, nDEFAULT) .NumberFormat = "@" .Value = Format(nNumber, "0000")
SaveSetting sAPPLICATION, sSECTION, sKEY, nNumber + 1& End If End With End With End Sub
Using a text file to hold sequential numbers
This method is more useful in some situations. The biggest advantage is that the sequential number is no longer tied to a particular machine - it can be stored on a common server, or even a thumb drive. Disadvantages include difficulty in keeping the file from being modified simultaneously by two users, or of the file being more easily deleted or modified. This function will return the next sequential number:
Public Function NextSeqNumber(Optional sFileName As String, Optional nSeqNumber As Long = -1) As Long Const sDEFAULT_PATH As String = "<your path here>" Const sDEFAULT_FNAME As String = "defaultseq.txt" Dim nFileNumber As Long nFileNumber = FreeFile If sFileName = "" Then sFileName = sDEFAULT_FNAME If InStr(sFileName, Application.PathSeparator) = 0 Then _ sFileName = sDEFAULT_PATH & Application.PathSeparator & sFileName If nSeqNumber = -1& Then If Dir(sFileName) <> "" Then Open sFileName For Input As nFileNumber Input #nFileNumber, nSeqNumber nSeqNumber = nSeqNumber + 1& Close nFileNumber Else nSeqNumber = 1& End If End If On Error GoTo PathError Open sFileName For Output As nFileNumber On Error GoTo 0 Print #nFileNumber, nSeqNumber Close nFileNumber NextSeqNumber = nSeqNumber Exit Function PathError: NextSeqNumber = -1& End Function
If you provide a full path in sFileName, that's where the file will be stored. If not, the file will be stored in whatever default directory you specify. You can set the sequential number by providing a value for nSeqNumber. Thus, if I'm only using one sequence I can use
Public Sub Workbook_Open() ThisWorkbook.Sheets(1).Range("B2").Value = NextSeqNumber End Sub
to return the next sequence number. If I'm using multiple sequences, I include the filename (with path, if the text file is not in the default path).
Public Sub NewClientInvoice() ThisWorkbook.Sheets(1).Range("B2").Value = NextSeqNumber("Client1.txt") End Sub
And if I want to start a new sequence, beginning at, say, 1001, include that number in the function call. If the client name were in cell B4:
Public Sub SetUpNewClient() With ThisWorkbook.Sheets(1) .Range("B2").Value = NextSeqNumber(.Range("B4").Value & ".txt", 1001) End With End Sub
=DATE(1970,1,1) + A1/86400
Writing a UDF is a little more complicated, since XL can have either of 2 base dates (0 January 1900 or 1 January 1904). This macro will convert it. Note that since VBA uses the 1900 date system, the 1904 adjustment is only made if the function is called from a worksheet.
Public Function UNIXtoXL(dUTime As Double) As Date Const cdCONVERT As Double = 86400 Const cdADJ1904 As Double = 1462 Const cdBASEDATE As Double = 25569 '1/1/1970 UNIXtoXL = cdBASEDATE + dUTime / cdCONVERT - _ (cdADJ1904 * ActiveWorkbook.Date1904 * _ (TypeName(Application.Caller) = "Range")) End Function