Chapter 28: Manipulating Visual Basic Components

IN THIS CHAPTER

Getting an overview of the VBA Integrated Development Environment (IDE) and its object model

Using VBA to add and remove modules from a project

Writing VBA code that creates more VBA code

Using VBA to help create UserForms

Creating a UserForm on the fly

Introducing the IDE

This chapter covers a topic that some readers might find extremely useful: writing Visual Basic for Applications (VBA) code that manipulates components in a VBA project. The VBA IDE contains an object model that exposes key elements of your VBA projects, including the Visual Basic Editor (VBE) itself. This object model enables you to write VBA code that adds or removes modules, generates other VBA code, or even creates UserForms on the fly.

The IDE is essentially an Object Linking and Embedding (OLE) automation interface for the Visual Basic Editor. After you establish a reference to the object, you have access to all the VBE's objects, properties, and methods, and you can also declare objects from the IDE's member classes.

Use the VBE's ToolsReferences command to display the References dialog box, where you can add a reference to the Microsoft Visual Basic for Applications Extensibility Library (see Figure 28-1). This gives you access to an object called VBIDE. Creating a reference to VBIDE enables you to declare object variables contained in the VBIDE and also gives you access to a number of predefined constants that relate to the IDE. Actually, you can access the objects in the IDE without creating a reference, but you won't be able to use the constants in your code, nor will you be able to declare specific objects that refer to IDE components.

475355-fg2801.eps

FIGURE 28-1: Adding a reference to the Microsoft Visual Basic for Applications Extensibility Library.

cross_ref.eps Refer to Chapter 20 for background information about OLE automation.

After you understand how the IDE object model works, you can write code to perform a variety of operations, including the following:

Adding and removing VBA modules

Inserting VBA code

Creating UserForms

Adding controls to a UserForm

The IDE Object Model

Programming the IDE requires an understanding of its object model. The top object in the object hierarchy is the VBE (Visual Basic Environment). As with Excel's object model, the VBE contains other objects. A simplified version of the IDE object hierarchy is as follows:

VBE

VBProject

VBComponent

CodeModule

Designer

Property

Reference

Window

CommandBar

note.eps This chapter ignores the Extensibility Library's Windows collection and CommandBars collection, which aren't all that useful for Excel developers. Rather, the chapter focuses on the VBProject object, which can be very useful for developers — but make sure that you read the “An important security note” sidebar.

The VBProjects collection

Every open workbook or add-in is represented by a VBProject object. To access the VBProject object for a workbook using early binding, make sure that you've established a reference to the Microsoft Visual Basic for Applications Extensibility Library (see “Introducing the IDE,” earlier in this chapter).

The VBProject property of the Workbook object returns a VBProject object. The following instructions, for example, create an object variable that represents the VBProject object for the active workbook:

Dim VBP As VBProject

Set VBP = ActiveWorkbook.VBProject

note.eps If you get an error message when VBA encounters the Dim statement, make sure that you've added a reference to Microsoft Visual Basic for Applications Extensibility Library.

Each VBProject object contains a collection of the VBA component objects in the project (UserForms, modules, class modules, and document modules). Not surprisingly, this collection is called VBComponents. A VBProject object also contains a References collection for the project, representing the libraries being referenced currently by the project.

You can't add a new member to the VBProjects collection directly. Rather, you do so indirectly by opening or creating a new workbook in Excel. Doing so automatically adds a new member to the VBProjects collection. Similarly, you can't remove a VBProject object directly; closing a workbook removes the VBProject object from the collection.

The VBComponents collection

To access a member of the VBComponents collection, use the VBComponents property with an index number or name as its argument. The following instructions demonstrate the two ways to access a VBA component and create an object variable:

Set VBC = ThisWorkbook.VBProject.VBComponents(1)

Set VBC = ThisWorkbook.VBProject.VBComponents(“Module1”)

The References collection

Every VBA project in Excel contains a number of references. You can view, add, or delete the references for a project by choosing the ToolsReferences command. (Refer to Figure 28-1 to see the References dialog box.) Every project contains some references (such as VBA itself, Excel, OLE Automation, and the Office object library), and you can add more references to a project as needed.

You can also manipulate the references for a project by using VBA. The References collection contains Reference objects, and these objects have properties and methods. The following procedure, for example, displays a message box that lists the Name, Description, and FullPath property for each Reference object in the active workbook's project:

Sub ListReferences()

Dim Ref As Reference

Msg = “”

For Each Ref In ActiveWorkbook.VBProject.References

Msg = Msg & Ref.Name & vbNewLine

Msg = Msg & Ref.Description & vbNewLine

Msg = Msg & Ref.FullPath & vbNewLine & vbNewLine

Next Ref

MsgBox Msg

End Sub

Figure 28-2 shows the result of running this procedure when a workbook that contains six references is active.

note.eps Because it declares an object variable of type Reference, the ListReferences procedure requires a reference to the VBA Extensibility Library. If you declare Ref as a generic Object, the VBA Extensibility Library reference is not needed.

You can also add a reference programmatically by using either of two methods of the Reference class. The AddFromFile method adds a reference if you know its filename and path. AddFromGuid adds a reference if you know the reference's globally unique identifier, or GUID. Refer to the Help system for more information.

475355-fg2802.eps

FIGURE 28-2: This message box displays information about the references for a project.

Displaying All Components in a VBA Project

The ShowComponents procedure, which follows, loops through each VBA component in the active workbook and writes the following information to a worksheet:

The component's name

The component's type

The number of lines of code in the code module for the component

Sub ShowComponents()

Dim VBP As VBIDE.VBProject

Dim VBC As VBComponent

Dim row As Long

Set VBP = ActiveWorkbook.VBProject

‘ Write headers

Cells.ClearContents

Range(“A1:C1”) = Array(“Name”, “Type”, “Code Lines”)

Range(“A1:C1”).Font.Bold = True

row = 1

‘ Loop through the VB Components

For Each VBC In VBP.VBComponents

row = row + 1

‘ Name

Cells(row, 1) = VBC.Name

‘ Type

Select Case VBC.Type

Case vbext_ct_StdModule

Cells(row, 2) = “Module”

Case vbext_ct_ClassModule

Cells(row, 2) = “Class Module”

Case vbext_ct_MSForm

Cells(row, 2) = “UserForm”

Case vbext_ct_Document

Cells(row, 2) = “Document Module”

End Select

‘ Lines of code

Cells(row, 3) = VBC.CodeModule.CountOfLines

Next VBC

End Sub

Notice that I used built-in constants (for example, vbext_ct_StdModule) to determine the component type. These constants aren't defined unless you've established a reference to the Microsoft Visual Basic for Applications Extensibility Library.

Figure 28-3 shows the result of running the ShowComponents procedure. In this case, the VBA project contained six components, and only one of them had an empty code module.

on_the_cd.eps This code is available on the CD-ROM in a workbook named list VB components.xlsm. The workbook includes an enhancement that lets you choose from all open VB projects.

475355-fg2803.tif

FIGURE 28-3: The result of executing the ShowComponents procedure.

Listing All VBA Procedures in a Workbook

The ListProcedures macro in this section creates a list (in a message box) of all VBA procedures in the active workbook.

Sub ListProcedures()

Dim VBP As VBIDE.VBProject

Dim VBC As VBComponent

Dim CM As CodeModule

Dim StartLine As Long

Dim Msg As String

Dim ProcName As String

‘ Use the active workbook

Set VBP = ActiveWorkbook.VBProject

‘ Loop through the VB components

For Each VBC In VBP.VBComponents

Set CM = VBC.CodeModule

Msg = Msg & vbNewLine

StartLine = CM.CountOfDeclarationLines + 1

Do Until StartLine >= CM.CountOfLines

Msg = Msg & VBC.Name & “: “ & _

CM.ProcOfLine(StartLine, vbext_pk_Proc) & vbNewLine

StartLine = StartLine + CM.ProcCountLines _

(CM.ProcOfLine(StartLine, vbext_pk_Proc), _

vbext_pk_Proc)

Loop

Next VBC

MsgBox Msg

End Sub

Figure 28-4 shows the result for a workbook that has nine procedures.

475355-fg2804.eps

FIGURE 28-4: The message box lists all procedures in the active workbook.

on_the_cd.eps This example, named list all procedures.xlsm, is available on the companion CD-ROM.

Replacing a Module with an Updated Version

The example in this section demonstrates how to replace a VBA module with a different VBA module. Besides demonstrating three VBComponent methods (Export, Remove, and Import), the procedure also has a practical use. For example, you might distribute a workbook to a group of users and then later discover that a macro contains an error or needs to be updated. Because the users could have added data to the workbook, replacing the entire workbook isn't practical. The solution, then, is to distribute another workbook that contains a macro that replaces the VBA module with an updated version stored in a file.

This example consists of two workbooks:

UserBook.xlsm: Contains a module (Module1) that needs to be replaced.

UpdateUserBook.xlsm: Contains VBA procedures to replace Module1 in UserBook.xlsm with a later version of Module1 (which is stored in UpdateUserBook.xlsm).

The BeginUpdate procedure follows. This macro is contained in the UpdateUserBook.xlsm workbook, which would be distributed to users of UserBook.xlsm. This procedure ensures that UserBook.xlsm is open. It then informs the user of what is about to happen with the message shown in Figure 28-5.

475355-fg2805.eps

FIGURE 28-5: This message box informs the user that a module will be replaced.

Sub BeginUpdate()

Dim Filename As String

Dim Msg As String

Filename = “UserBook.xlsm”

‘ Activate workbook

On Error Resume Next

Workbooks(Filename).Activate

If Err <> 0 Then

MsgBox Filename & “ must be open.”, vbCritical

Exit Sub

End If

Msg = “This macro will replace Module1 in UserBook.xlsm “

Msg = Msg & “with an updated Module.” & vbCrLf & vbCrLf

Msg = Msg & “Click OK to continue.”

If MsgBox(Msg, vbInformation + vbOKCancel) = vbOK Then

Call ReplaceModule

Else

MsgBox “Module not replaced,”, vbCritical

End If

End Sub

When the user clicks OK to confirm the replacement, the ReplaceModule procedure is called. This procedure replaces Module1 in the UserBook.xlsm with the copy of Module1 in the UpdateUserBook.xlsm file:

Sub ReplaceModule()

Dim ModuleFile As String

Dim VBP As VBIDE.VBProject

‘ Export Module1 from this workbook

ModuleFile = Application.DefaultFilePath & “ empmodxxx.bas”

ThisWorkbook.VBProject.VBComponents(“Module1”) _

.Export ModuleFile

‘ Replace Module1 in UserBook

Set VBP = Workbooks(“UserBook.xlsm”).VBProject

On Error GoTo ErrHandle

With VBP.VBComponents

.Remove VBP.VBComponents(“Module1”)

.Import ModuleFile

End With

‘ Delete the temporary module file

Kill ModuleFile

MsgBox “The module has been replaced.”, vbInformation

Exit Sub

ErrHandle:

‘ Did an error occur?

MsgBox “ERROR. The module may not have been replaced.”, _

vbCritical

End Sub

This procedure performs the following actions:

1. It exports Module1 (the updated module) to a file.

The file has an unusual name to reduce the likelihood of overwriting an existing file.

2. It removes Module1 (the old module) from UserBook.xlsm, using the Remove method of the VBComponents collection.

3. It imports the module (saved in Step 1) to UserBook.xlsm.

4. It deletes the file saved in Step 1.

5. It reports the action to the user.

General error handling is used to inform the user that an error occurred.

on_the_cd.eps This example is available on the companion CD-ROM. It requires two workbooks: UserBook.xlsm and UpdateUserBook.xlsm.

Using VBA to Write VBA Code

The example in this section demonstrates how you can write VBA code that writes more VBA code. The AddButtonAndCode procedure does the following:

1. Inserts a new worksheet.

2. Adds an ActiveX CommandButton control to the worksheet.

3. Adjusts the position, size, and caption of the CommandButton.

4. Inserts an event-handler procedure for the CommandButton named CommandButton1_Click in the sheet's code module.

This procedure simply activates Sheet1.

The AddButtonAndCode procedure follows.

Sub AddButtonAndCode()

Dim NewSheet As Worksheet

Dim NewButton As OLEObject

‘ Add the sheet

Set NewSheet = Sheets.Add

‘ Add a CommandButton

Set NewButton = NewSheet.OLEObjects.Add _

(“Forms.CommandButton.1”)

With NewButton

.Left = 4

.Top = 4

.Width = 100

.Height = 24

.Object.Caption = “Return to Sheet1”

End With

‘ Add the event handler code

Code = “Sub CommandButton1_Click()” & vbCrLf

Code = Code & “ On Error Resume Next” & vbCrLf

Code = Code & “ Sheets(“”Sheet1””).Activate” & vbCrLf

Code = Code & “ If Err <> 0 Then” & vbCrLf

Code = Code & “ MsgBox “”Cannot activate Sheet1.””” _

& vbCrLf

Code = Code & “ End If” & vbCrLf

Code = Code & “End Sub”

With ActiveWorkbook.VBProject. _

VBComponents(NewSheet.Name).CodeModule

NextLine = .CountOfLines + 1

.InsertLines NextLine, Code

End With

End Sub

Figure 28-6 shows the worksheet and the CommandButton control that were added by the AddButtonAndCode procedure.

on_the_cd.eps This example is available on the companion CD-ROM. The filename is add button and code.xlsm.

475355-fg2806.tif

FIGURE 28-6: This sheet, the CommandButton, and its event handler were added by using VBA.

The tricky part of this procedure is inserting the VBA code into the code module for the new worksheet. The code is stored in a variable named Code, with each instruction separated by a carriage return and linefeed sequence. The InsertLines method adds the code to the code module for the inserted worksheet.

The NextLine variable stores the number of existing lines in the module incremented by one. This ensures that the procedure is added to the end of the module. If you simply insert the code beginning at line 1, it causes an error if the user's system is set up to add an Option Explicit statement to each module automatically.

Figure 28-7 shows the procedure that is created by the AddButtonAndCode procedure in its new home in the code window.

475355-fg2807.eps

FIGURE 28-7: VBA generated this event-handler procedure.

Adding Controls to a UserForm at Design Time

If you've spent any time developing UserForms, you probably know that it can be quite tedious to add and adjust the controls so that they're aligned and sized consistently. Even if you take full advantage of the VBE formatting commands, it can still take a considerable amount of time to get the controls to look just right.

The UserForm shown in Figure 28-8 contains 100 CommandButtons, all of which are identical in size and positioned precisely on the form. Furthermore, each CommandButton has its own event-handler procedure. Adding these buttons manually and creating their event handlers would take some time — lots of time. Adding them automatically at design time by using a VBA procedure takes less than a second.

475355-fg2808.eps

FIGURE 28-8: A VBA procedure added the CommandButtons on this UserForm.

Design-time versus runtime UserForm manipulations

It's important to understand the distinction between manipulating UserForms or controls at design time and manipulating these objects at runtime. Runtime manipulations are apparent when the UserForm is shown, but the changes made aren't permanent. For example, you might write code that changes the Caption property of the UserForm before the form is displayed. The new caption appears when the UserForm is shown, but when you return to the VBE, the UserForm displays its original caption. Runtime manipulation is very common, and Part IV of this book contains many examples of code that perform runtime manipulation of UserForms and controls.

Design-time manipulations, on the other hand, are permanent — just as if you made the changes manually by using the tools in the VBE. Normally, you perform design-time manipulations as a way to automate some of the tedious chores in designing a UserForm. to make design-time manipulations, you access the Designer object for the UserForm.

To demonstrate the difference between design-time and runtime manipulations, I developed two simple procedures that add a CommandButton to a UserForm. One procedure adds the button at runtime; the other adds it at design time.

The following RunTimeButton procedure is very straightforward. When used in a general (non-UserForm) module, it adds a CommandButton to the UserForm, changes a few of the CommandButton's properties, and then displays the UserForm. The CommandButton appears on the form when the form is shown, but when you view the form in the VBE, the CommandButton isn't there.

Sub RunTimeButton()

‘ Adds a button at runtime

Dim Butn As CommandButton

Set Butn = UserForm1.Controls.Add(“Forms.CommandButton.1”)

With Butn

.Caption = “Added at runtime”

.Width = 100

.Top = 10

End With

UserForm1.Show

End Sub

Following is the DesignTimeButton procedure. Unlike the previous example, this procedure uses the Designer object, which is contained in the VBComponent object. Specifically, it uses the Add method to add the CommandButton control. Because the Designer object was used, the CommandButton is added to the UserForm just as if you did it manually in the VBE.

Sub DesignTimeButton()

‘ Adds a button at design time

Dim Butn As CommandButton

Set Butn = ThisWorkbook.VBProject. _

VBComponents(“UserForm1”) _

.Designer.Controls.Add(“Forms.CommandButton.1”)

With Butn

.Caption = “Added at design time”

.Width = 120

.Top = 40

End With

End Sub

Adding 100 CommandButtons at design time

The example in this section demonstrates how to take advantage of the Designer object to help you design a UserForm. In this case, the code adds 100 CommandButtons (perfectly spaced and aligned), sets the Caption property for each CommandButton, and also creates 100 event-handler procedures (one for each CommandButton).

Sub Add100Buttons()

Dim UFvbc As VBComponent

Dim CMod As CodeModule

Dim ctl As Control

Dim cb As CommandButton

Dim n As Long, c As Long, r As Long

Dim code As String

Set UFvbc = ThisWorkbook.VBProject.VBComponents(“UserForm1”)

‘ Delete all controls, if any

For Each ctl In UFvbc.Designer.Controls

UFvbc.Designer.Controls.Remove ctl.Name

Next ctl

‘ Delete all VBA code

UFvbc.CodeModule.DeleteLines 1, UFvbc.CodeModule.CountOfLines

‘ Add 100 CommandButtons

n = 1

For r = 1 To 10

For c = 1 To 10

Set cb = UFvbc.Designer. _

Controls.Add(“Forms.CommandButton.1”)

With cb

.Width = 22

.Height = 22

.Left = (c * 26) - 16

.Top = (r * 26) - 16

.Caption = n

End With

‘ Add the event handler code

With UFvbc.CodeModule

code = “”

code = code & “Private Sub CommandButton” & n & _

“_Click” & vbCr

code = code & “Msgbox “”This is CommandButton” & n & _

“””” & vbCr

code = code & “End Sub”

.InsertLines .CountOfLines + 1, code

End With

n = n + 1

Next c

Next r

End Sub

on_the_cd.eps This example is available on the companion CD-ROM. The file is named add 100 buttons.xlsm.

The Add100Buttons procedure requires a UserForm named UserForm1. You'll need to make the UserForm a bit larger than its default size so that the buttons will fit. The procedure starts by deleting all controls on the form by using the Remove method of the Controls collection and then deleting all the code in the code module by using the DeleteLines method of the CodeModule object. Next, the CommandButtons are added, and the event-handler procedures are created within two For-Next loops. These event handlers are very simple. Here's an example of such a procedure for CommandButton1:

Private Sub CommandButton1_Click()

MsgBox “This is CommandButton1”

End Sub

If you'd like to show the form after adding the controls at design time, you need to add the following instruction right before the End Sub statement:

VBA.UserForms.Add(“UserForm1”).Show

It took me quite a while to figure out how to actually display the UserForm. When VBA generates the 100-button UserForm, it indeed exists in VBA's memory, but it isn't officially part of the project yet. So you need the Add method to formally enroll UserForm1 into the collection of userForms. The return value of this method is a reference to the form itself, which is why the Show method can be appended to the end of the Add method. So, as a rule, the UserForm must be added to the UserForms collection before it can be used.

Creating UserForms Programmatically

The final topic in this chapter demonstrates how to use VBA code to create UserForms at runtime. I present two examples. One is relatively simple, and the other is quite a bit more complex.

A simple runtime UserForm example

The example in this section isn't all that useful — in fact, it's completely useless. But it does demonstrate some useful concepts. The MakeForm procedure performs several tasks:

1. It creates a temporary UserForm in the active workbook by using the Add method of the VBComponents collection.

2. It adds a CommandButton control to the UserForm by using the Designer object.

3. It adds an event-handler procedure to the UserForm's code module (CommandButton1_Click).

This procedure, when executed, simply displays a message box and then unloads the form.

4. It displays the UserForm.

5. It deletes the UserForm.

The net result is a UserForm that's created on the fly, put to use, and then deleted. This example and the one in the next section both blur the distinction between modifying forms at design time and modifying forms at runtime. The form is created by using design-time techniques, but it all happens at runtime.

The following shows the MakeForm procedure:

Sub MakeForm()

Dim TempForm As Object

Dim NewButton As Msforms.CommandButton

Dim Line As Integer

Application.VBE.MainWindow.Visible = False

‘ Create the UserForm

Set TempForm = ThisWorkbook.VBProject. _

VBComponents.Add(3) ‘vbext_ct_MSForm

With TempForm

.Properties(“Caption”) = “Temporary Form”

.Properties(“Width”) = 200

.Properties(“Height”) = 100

End With

‘ Add a CommandButton

Set NewButton = TempForm.Designer.Controls _

.Add(“Forms.CommandButton.1”)

With NewButton

.Caption = “Click Me”

.Left = 60

.Top = 40

End With

‘ Add an event-hander sub for the CommandButton

With TempForm.CodeModule

Line = .CountOfLines

.InsertLines Line + 1, “Sub CommandButton1_Click()”

.InsertLines Line + 2, “ MsgBox “”Hello!”””

.InsertLines Line + 3, “ Unload Me”

.InsertLines Line + 4, “End Sub”

End With

‘ Show the form

VBA.UserForms.Add(TempForm.Name).Show

‘ Delete the form

ThisWorkbook.VBProject.VBComponents.Remove TempForm

End Sub

on_the_cd.eps This example, named create userform on the fly.xlsm, is available on the companion CD-ROM.

The MakeForm procedure creates and shows the simple UserForm shown in Figure 28-9.

475355-fg2809.eps

FIGURE 28-9: This UserForm and its underlying code were generated on the fly.

note.eps The workbook that contains the MakeForm procedure doesn't need a reference to the VBA Extensibility Library because it declares TempForm as a generic Object (not specifically as a VBComponent object). Moreover, it doesn't use any built-in constants.

Notice that one of the first instructions hides the VBE window by setting its Visible property to False. This eliminates the on-screen flashing that might occur while the form and code are being generated.

A useful (but not so simple) dynamic UserForm example

The example in this section is both instructive and useful. It consists of a function named GetOption that displays a UserForm. Within this UserForm are a number of OptionButtons whose captions are specified as arguments to the function. The function returns a value that corresponds to the OptionButton selected by the user.

on_the_cd.eps The example in this section is available on the companion CD-ROM. The filename is ‘getoption function.xlsm'.

The GetOption function procedure follows.

Function GetOption(OpArray, Default, Title)

Dim TempForm As Object

Dim NewOptionButton As Msforms.OptionButton

Dim NewCommandButton1 As Msforms.CommandButton

Dim NewCommandButton2 As Msforms.CommandButton

Dim i As Integer, TopPos As Integer

Dim MaxWidth As Long

Dim Code As String

‘ Hide VBE window to prevent screen flashing

Application.VBE.MainWindow.Visible = False

‘ Create the UserForm

Set TempForm = _

ThisWorkbook.VBProject.VBComponents.Add(3)

TempForm.Properties(“Width”) = 800

‘ Add the OptionButtons

TopPos = 4

MaxWidth = 0 ‘Stores width of widest OptionButton

For i = LBound(OpArray) To UBound(OpArray)

Set NewOptionButton = TempForm.Designer.Controls. _

Add(“Forms.OptionButton.1”)

With NewOptionButton

.Width = 800

.Caption = OpArray(i)

.Height = 15

.Accelerator = Left(.Caption, 1)

.Left = 8

.Top = TopPos

.Tag = i

.AutoSize = True

If Default = i Then .Value = True

If .Width > MaxWidth Then MaxWidth = .Width

End With

TopPos = TopPos + 15

Next i

‘ Add the Cancel button

Set NewCommandButton1 = TempForm.Designer.Controls. _

Add(“Forms.CommandButton.1”)

With NewCommandButton1

.Caption = “Cancel”

.Cancel = True

.Height = 18

.Width = 44

.Left = MaxWidth + 12

.Top = 6

End With

‘ Add the OK button

Set NewCommandButton2 = TempForm.Designer.Controls. _

Add(“Forms.CommandButton.1”)

With NewCommandButton2

.Caption = “OK”

.Default = True

.Height = 18

.Width = 44

.Left = MaxWidth + 12

.Top = 28

End With

‘ Add event-hander subs for the CommandButtons

Code = “”

Code = Code & “Sub CommandButton1_Click()” & vbCrLf

Code = Code & “ GETOPTION_RET_VAL=False” & vbCrLf

Code = Code & “ Unload Me” & vbCrLf

Code = Code & “End Sub” & vbCrLf

Code = Code & “Sub CommandButton2_Click()” & vbCrLf

Code = Code & “ Dim ctl” & vbCrLf

Code = Code & “ GETOPTION_RET_VAL = False” & vbCrLf

Code = Code & “ For Each ctl In Me.Controls” & vbCrLf

Code = Code & “ If TypeName(ctl) = “”OptionButton””” _

& “ Then” & vbCrLf

Code = Code & “ If ctl Then GETOPTION_RET_VAL = “ _

& “ctl.Tag” & vbCrLf

Code = Code & “ End If” & vbCrLf

Code = Code & “ Next ctl” & vbCrLf

Code = Code & “ Unload Me” & vbCrLf

Code = Code & “End Sub”

With TempForm.CodeModule

.InsertLines .CountOfLines + 1, Code

End With

‘ Adjust the form

With TempForm

.Properties(“Caption”) = Title

.Properties(“Width”) = NewCommandButton1.Left + _

NewCommandButton1.Width + 10

If .Properties(“Width”) < 160 Then

.Properties(“Width”) = 160

NewCommandButton1.Left = 106

NewCommandButton2.Left = 106

End If

.Properties(“Height”) = TopPos + 24

End With

‘ Show the form

VBA.UserForms.Add(TempForm.Name).Show

‘ Delete the form

ThisWorkbook.VBProject.VBComponents.Remove VBComponent:=TempForm

‘ Pass the selected option back to the calling procedure

GetOption = GETOPTION_RET_VAL

End Function

The GetOption function is remarkably fast, considering all that's going on behind the scenes. On my system, the form appears almost instantaneously. The UserForm is deleted after it has served its purpose.

Using the GetOption function

The GetOption function takes three arguments:

OpArray: A string array that holds the items to be displayed in the form as OptionButtons.

Default: An integer that specifies the default OptionButton that is selected when the UserForm is displayed. If 0, none of the OptionButtons are selected (the user clicks Cancel).

Title: The text to display in the title bar of the UserForm.

How GetOption works

The GetOption function performs the following operations:

1. Hides the VBE window to prevent any flashing that could occur when the UserForm is created or the code is added.

2. Creates a UserForm and assigns it to an object variable named TempForm.

3. Adds the OptionButton controls by using the array passed to the function via the OpArray argument.

It uses the Tag property of the control to store the index number. The Tag setting of the chosen option is the value that's eventually returned by the function.

4. Adds two CommandButton controls: the OK button and the Cancel button.

5. Creates an event handler procedure for each of the CommandButtons.

6. Does some final cleanup work.

It adjusts the position of the CommandButtons as well as the overall size of the UserForm.

7. Displays the UserForm.

When the user clicks OK, the CommandButton1_Click procedure is executed. This procedure determines which OptionButton is selected and also assigns a number to the GETOPTION_RET_VAL variable (a Public variable).

8. Deletes the UserForm after it's dismissed.

9. Returns the value of GETOPTION_RET_VAL as the function's result.

note.eps A significant advantage of creating the UserForm on the fly is that the function is self-contained in a single module and doesn't even require a reference to the VBA Extensibility Library. Therefore, you can export this module (which is named modOptionsForm) and then import it into any of your workbooks, thus giving you access to the GetOption function.

The following procedure demonstrates how to use the GetOption function. In this case, the UserForm presents five options (contained in the Ops array).

Sub TestGetOption()

Dim Ops(1 To 5)

Dim UserOption

Ops(1) = “North”

Ops(2) = “South”

Ops(3) = “West”

Ops(4) = “East”

Ops(5) = “All Regions”

UserOption = GetOption(Ops, 5, “Select a region”)

Debug.Print UserOption

MsgBox Ops(UserOption)

End Sub

The UserOption variable contains the index number of the option selected by the user. If the user clicks Cancel (or presses Escape), the UserOption variable is set to False.

Notice that the Accelerator property is set to the first character of each option's caption, so the user can use an Alt+letter combination to make a choice. I made no attempt to avoid duplicate Accelerator keys, so the user may need to press the key combination multiple times to make a selection.

Figure 28-10 shows the UserForm that this function generates.

475355-fg2810.eps

FIGURE 28-10: The GetOption function generated this UserForm.

note.eps The UserForm adjusts its size to accommodate the number of elements in the array passed to it. Theoretically, the UserOption function can accept an array of any size. Practically speaking, however, you'll want to limit the number of options to keep the UserForm at a reasonable size. Figure 28-11 shows how the form looks when the options contain more text.

475355-fg2811.eps

FIGURE 28-11: The UserForm adjusts its height and width to accommodate the number of options and the length of the text.

GetOption Event-Handler code

Following are the event-handler procedures for the two CommandButtons. This is the code generated within the GetOption function and placed in the code module for the temporary UserForm.

Sub CommandButton1_Click()

GETOPTION_RET_VAL = False

Unload Me

End Sub

Sub CommandButton2_Click()

Dim ctl

GETOPTION_RET_VAL = False

For Each ctl In Me.Controls

If TypeName(ctl) = “OptionButton” Then

If ctl Then GETOPTION_RET_VAL = ctl.Tag

End If

Next ctl

Unload Me

End Sub

note.eps Because the UserForm is deleted after it's used, you can't see what it looks like in the VBE. So, if you'd like to view the UserForm, convert the following instruction to a comment by typing an apostrophe (‘) in front of it:

ThisWorkbook.VBProject.VBComponents.Remove _

VBComponent:=TempForm

..................Content has been hidden....................

You can't read the all page of ebook, please click here login for view all page.
Reset