You are on page 1of 25

VBA Part 2

By John Gibb

Visual Basic (VB) and Visual Basic Applications (VBA) both offer the ability to interface with AutoCAD.
Starting with Release 14 Autodesk included VBA as a language that works inside the AutoCAD environment
the same as their low end AutoLISP language and their high end ObjectARX language. The fact that VBA
works inside AutoCAD gives it the a edge over VB in many situations inside AutoCAD.

We’re going to work with VBA in this session, since it is native with AutoCAD, but you should remember that
anything we do in the VBA environment can be transferred into the VB environment with only a few extra lines
of code. The exception to this is a few of the controls found in VBA.

Although VB does not work inside the AutoCAD environment it does have its own advantages. VB has controls
for initiating DDE conversations with other programs while VBA doesn’t.

With a class of this brief duration it is important to cover ground fast. We’re going to cover the following
subjects as we build several small applications.

• The VBAIDE interface


• Accessing the Document Object in VBA
• User Selecting and Collecting with and without filters
• File Input & Output
• Creating Entity Objects
• Creating Table Definitions
• Creating Collections of Objects
• Creating Forms

The VBAIDE Interface

If you are just learning VBA do not panic yourself by thinking there is a lot of typing involved in creating
programs. The editor (VBAIDE) provides a fast typing mechanism for object trees. When you properly
dimension (Dim) an object type, the system will display the properties and methods in a pop-up list for quick
selection.

Page: 1
VBA Part 2

After typing the first character or two of the property or method you are after the menu scrolls down to the area
you are looking for. You can then select the remainder of the word with the mouse. Portable computer users
with the pointing device near the keyboard report this is a really great feature. You can use keyboard strokes to
select the value desired as well and press the Tab key when satisfied with the selection. This method of code
input greatly enhances the speed and accuracy of the coding.

Accessing the Document Object in VBA

VBA runs inside AutoCAD and when the AutoCAD drawing editor is active, there is always a current drawing.
The current drawing (or document) is defined as an object with the name “ThisDrawing” in the VBA
environment. ThisDrawing is essentially the trunk of the object tree with the application object being the root.
Programs can control the opening, saving, and other file based operations of the AutoCAD system using the
associated methods.

The object tree can be explored by referencing the reserved object variable “ThisDrawing”.

Public Sub Main()

Debug.Print ThisDrawing.Name

End Sub

To do the same thing from VB you would need to first reference the AutoCAD library, set an object to the
application, set another object to the active drawing and then issue the same command.

On Error Resume Next

Set acadAPP = GetObject(, "AutoCAD.Application")

If Err Then ‘ AutoCAD not running

Err.Clear

Page: 2
VBA Part 2
Set acadAPP = CreateObject("AutoCAD.Application") ‘ start it

Else

Set ThisDrawing = acadAPP.ActiveDocument ‘same as ThisDrawing in VBA

Debug.Print ThisDrawing.Name

End If

Document object methods

From the document object, all other objects inside a drawing are accessed. For example, if you were interested
in getting to the layer table, you would use the ThisDrawing.Layers property to obtain the link to the layer
collection object. The individual layer names and their respective properties are each found inside the layer
collection.

The following is a partial list of methods that can be accessed with the document object. File accessing and
global drawing settings are the primary activities that take place within these methods.

Method Name Does What?


Activate Make this drawing the current document when in multiple
document mode.
Close Closes the drawing.
Export, Import Output and input of drawing information in DXF, WMF, BMP,
SAT, or EPS type files. These file formats are used by other
applications for storage of graphic data.
GetVariable, Retrieve or set the value of a specified AutoCAD system variable.
SetVariable
HandleToObject Converts a handle (string) into an object reference. When reading
handles from an external database and wanting to locate the
associated object, this function will be used extensively.
LoadShapeFile Load a shape file into the current drawing. Shape files are used in
custom line types and as a possible substitute for blocks. This
method loads the entire shape file for access by other commands.
New Start a new drawing based on a template drawing in single
document mode. For multiple document mode, the “Add” method
should be used from the documents collection.
Open Open an existing drawing in single document mode. For multiple
document mode, use the Open method in the documents collection.
PurgeAll Purge the tables in the current drawing.
Regen Regenerate the current drawing in the graphics window.
Save, SaveAs Save the drawing to the disk using the current name or another
name.

Page: 3
VBA Part 2
SendCommand Send an AutoCAD or AutoLISP command to the command
processor for that document. The document will be made the
current document if it is not already when this method is run.
Wblock Write the contents of a block definition to the disk.

Document Object Properties

The following table lists some of the properties or data elements that are defined at the document level. Not all
of the properties are in this table. These are simply the most popular ones used by applications developers. A
complete list can be found in the online help files supplied with AutoCAD for VBA ActiveX automation. The
properties of the drawing object contain a varied set of information. Data ranges from file naming of the current
drawing to collection linkages allowing the programmer to dig deeper inside the drawing to get at information
such layer names, entity details, and block definitions.
Property Name Does What?
Active Flag to indicate if this is the active document in multiple document
mode.
ActiveLayer, Pointers to the objects that are the current settings for the drawing
ActiveLinetype, system.
ActiveSpace,
ActiveTextStyle,
ActiveUCS
ActiveSelectionSet The active selection set in the drawing is one currently being built
by a command in progress or as a result of selecting objects as in
the use of grips. This is a reference to a collection of entities.
Application The application object for the AutoCAD system. The application
object is actually higher in the AutoCAD object tree than the
document object and this property provides a link back to it. The
application object is used when you need to control the AutoCAD
windows themselves. This is a read only value that provides a
bridge to the upper level of the program. All objects in the
ActiveX/VBA interface have an application property.
Blocks Returns the blocks collection object for the drawing. This is a read
only value that is used to get at the block table objects.
Dictionaries Returns the dictionaries collection object for the drawing. This is
a read only value that is used to access the user defined dictionary
table.
DimStyles Returns the dimension styles collection object for the current
drawing. This is a read only value that is used to access the
dimension style table.
FullName, Name, The complete name, just the drawing name, or just the path name
Path of the drawing with directory path. You can set the value of
FullName prior to using the SAVE method.

Page: 4
VBA Part 2
Groups Returns the groups collection object for the current drawing. This
is a read only value that is used to get at the group objects.
Layers Returns the layers collection object for the current drawing. This
is a read only value that is used to get at the layer table objects.
Limits The drawing limits can be set and referenced as a variant
containing the upper and lower corners as 2D points. Limits
control the display of the drawing grid and zoom all options.
Linetypes Returns the linetypes collection object for the current drawing.
This is a read only value that is used to get at the linetype table
objects.
ModelSpace Returns the model space collection for the current drawing. This
is a read only value that is used to get at the entity objects in model
space.
PaperSpace Returns the paper space collection for the current drawing. This is
a read only value that is used to get at the entity objects in paper
space.
Plot, Access to the plotter information related to the drawing. The Plot
PlotConfigurations object contains the methods for generating the output while the
PlotConfigurations object is where the details of what to plot can
be found.
ReadOnly A read only property that tells an application if the current drawing
is read only itself or not.
Saved A read only property flag that tells an application if the current
drawing has any unsaved changes.
TextStyles Returns the text style collection object for the current drawing.
This is a read only value that is used to get at the text style table
objects.
Utility Returns the utility object for the drawing. The utility object
contains a library of very useful functions for communicating with
the AutoCAD user. We will explore this object in detail at the end
of this chapter.

There are many more properties associated with the document object; these are just a few of the more
commonly used ones. The document level contains the methods and properties that apply to the entire
document as well as the collection objects that contain the details of the drawing.

User Selection and Collecting

User Input

There are many different ways to collect information from users’. The Utility property allows you to gather data
the similar to AutoLISP. The following code shows a way to collect data from the user using the utility
property.

Page: 5
VBA Part 2
Public Sub GetStringfromUser ()

AppActivate ThisDrawing.Application.Caption

Debug.Print ThisDrawing.Utility.GetString(False, "Enter Your Name please: ")

End Sub

This does nothing more than give the user a prompt and then it writes the response to the debug window. To be
more useful the program should collect the answer into a variable for later processing. The following code
shows how to do that.

Public Sub GetStringfromUser_PrintIt ()

Dim strAnswer as String

AppActivate ThisDrawing.Application.Caption

StrAnswer = ThisDrawing.Utility.GetString(True, "Enter Your Name please: ")

Debug.Print strAnswer

End Sub

Notice that the first argument was changed to True to allow spaces in the response.

Selection Sets

Gathering data using selection sets is another user-input function that you will need to work with. There are
several different methods available for creating selections sets.

In order to use a selection set in a program, it must first be created. Adding a new member to the selection sets
collection creates a new selection set as in the following code segment.

Public Sub CreateSelectionSet ()

Dim S1 as AcadSelectionSet

Set S1 = thisDrawing.SelectionSets.Add(“S1”)

End Sub

In the code just shown the variable S1 is defined as being of the type “AcadSelectionSet”. Dimensioning it
gives it a structure while the “set” statement gives it a value. In this case the new selection set added to the
selection sets collection is named “S1”. The name string does not have to match the name of the variable used,
but it does help to keep things straight. Once the container object that is to hold the selection is created you must
ask the operator to select some objects.

Page: 6
VBA Part 2
Operator Controlled Set Creation

The following example demonstrates how to have the operator select objects and add them to a new selection
set named “S2”. First the selection set object is created as a member of the selection sets collection. Then the
SelectOnScreen method is run to allow the operator to pick the objects to place into the selection set. Between
the two is the AppActivate statement. This function brings the AutoCAD window to the foreground so that the
operator may select the objects. The only time this is an issue is when you are using a form for user input or are
testing your macros from within the development environment.

Public Sub CreateSelectionSet_FillIt ()

Dim S2 as AcadSelectionSet

Set S2 = ThisDrawing.SelectionSets.Add(“S2”)

AppActivate ThisDrawing.Application.Caption

S2.SelectOnScreen

End Sub

Each step builds upon the last. A problem with creating a named selection set object for the selectionsets
collection is that if the named object already exists inside the collection, the code throws an error. You can
make your code trap the error and then fix the problem with just a few lines of code as show in the code
fragment below.

Public Sub CreateSelectionSet_WithErrorTrapping ()

Dim S2 As AcadSelectionSet

On Error Resume Next

Set S2 = ThisDrawing.SelectionSets.Add("S6")

If Err.Number <> 0 Then

Set S2 = ThisDrawing.SelectionSets.Item(strSetName)

End If

AppActivate ThisDrawing.Application.Caption

S2.SelectOnScreen

Dim lngI As Long

For lngI = 0 To S2.Count - 1

Debug.Print S2.Item(lngI).ObjectName

Page: 7
VBA Part 2
Debug.Print S2.Item(lngI).ObjectID

Next lngI

End Sub

You might also notice that the For…Next statement was introduced to spin through the set to show you what
the operator selected. This is a standard method for accessing the objects inside a selection set.

Creating Selection Sets with Filters

You have the option of either creating a selection set independent of the operator or with the operator using the
Select method of a selection set object or the SelectOnScreen method (as shown earlier in the Operator
Controlled Set Creations section). Both methods allow filters to be applied so only objects meeting your criteria
will be selected. This next example shows how to filter all objects out of a set except block occurrences by the
name that you pass it. This is also the first example of using functions instead of subroutines.

Public Function Get_Blk_Occurrences(BlockName As String) As AcadSelectionSet

Dim S1 As AcadSelectionSet ' declare the selection set

AddSelectionSet S1, "S1" ' create or get the set

S1.Clear ' clear the set

Dim intFtyp(1) As Integer ' setup for the filter

Dim varFval(1) As Variant

Dim varFilter1, varFilter2 As Variant

intFtyp(0) = 0: varFval(0) = "INSERT" ' get only block occurrences

intFtyp(1) = 2: varFval(1) = BlockName ' of this name

varFilter1 = intFtyp: varFilter2 = varFval

S1.Select acSelectionSetAll, , , varFilter1, varFilter2 ' do it

Set Get_Blk_Occurrences = S1 ' return the set

End Function

The following code will allow you to test your new function.

Page: 8
VBA Part 2
Public Sub Test_Get_Blk_Occurrences()

Dim ss As AcadSelectionSet

Set ss = Get_Blk_Occurrences("Widget")

Dim objBlk As AcadBlockReference

Dim strMsg As String

If ss.Count > 0 Then

Dim lngI As Long

For lngI = 0 To ss.Count - 1

Set objBlk = ss.Item(lngI)

strMsg = strMsg & objBlk.Name & " handle is " & objBlk.Handle & _

" on layer " & objBlk.Layer & vbCrLf

Next lngI

End If

MsgBox strMsg

End Sub

A word of warning is necessary here. This routine returns all blocks in the drawing no matter what space they
reside in. This can be a problem in some applications where you might only want the blocks in a given space.
See the Creating Collections of Objects section later for an alternative to this method that will allow you control
over the space the block objects are gathered from.

File Output & Input

Accessing data from the hard drive is very simple in VBA and very similar to how AutoLISP handles files. The
code shown below opens a file for writing writes to the file.

Public Sub FileManipulation_Output()

Dim intWfl As Integer

intWfl = FreeFile

Open "c:\winnt\temp\AU2000 TestFile.txt" For Output Shared As #intWfl

Print #intWfl, "This is a test" ' Print text to file.

Page: 9
VBA Part 2
Print #intWfl, ' Print blank line to file.

Print #intWfl, "Zone 1"; Tab; "Zone 2" ' Print in two print zones.

Close #intWfl

End Sub

Now that we have a file to look at, let’s read it back in as shown in the routine below.

Public Sub FileManipulation_Input()

Dim strLine As String

Open "c:\winnt\temp\AU2000 TestFile.txt" For Input As #intWfl

Do While Not EOF(1) ' Loop until end of file.

Input #intWfl, strLine ' Read data into two variables.

Debug.Print strLine ' Print data to Debug window.

Loop

Close #intWfl

End Sub

Creating Entity Objects

Creating an entity object such as a line, as shown below, seems to be labor intensive but it is simple once you
get the hang of it.

Public Sub AddLine()

Dim mospace As AcadModelSpace 'The model space object collection

Set mospace = ThisDrawing.ModelSpace

Dim NL As String

NL = Chr(13) & Chr(10) 'Define newline

Dim prompt1, prompt2 As String 'Define variables for prompt strings

prompt1 = NL & "Start point: "

prompt2 = NL & "End point: "

Page: 10
VBA Part 2
On Error Resume Next

AppActivate ThisDrawing.Application.Caption

Dim stPnt, enPnt As Variant 'Define variables to receive return values

stPnt = ThisDrawing.Utility.GetPoint(, prompt1)

If Err.Number <> 0 Then

MsgBox "Operation cancelled.", vbInformation

Else

enPnt = ThisDrawing.Utility.GetPoint(stPnt, prompt2)

Dim objLine As AcadLine

Set objLine = mospace.AddLine(stPnt, enPnt)

End If

If Not IsEmpty(objLine) Then

Debug.Print objLine.Handle

End If

End Sub

Breaking it down into small steps is the easiest way to deal with entity object creation.

1. The first two line declare an object to hold the model space and set that object the current drawing’s. model
space.
2. The next two lines declare a variable for defining a new line character feed and load it with the appropriate
codes.
3. The next two lines declare two variables to hold the prompts for the operator and load the prompts.
4. The next two lines set the error trapping for canceling and activate the screen window.
5. The next two lines declare the variables to hold the end points selected and ask for the first endpoint.
6. The Err.Number line tests to see if the operator canceled (this would generate the error).
7. The first line in the error trapping is a message box that appears when the operator cancels.
8. The next three lines of code in the else statement do the work. They prompt for the second point, declare a
line object, and create the line placing it into the line object.
9. The last if statement and code are there as an example of how to test if an object was created and then do
something with it (in this case print out to the debug window the new line object’s handle.

As you can see, it is easy when you break it into small steps. Step nine is only necessary if you want to further
process the new line object. Step 2 is optional but good practice to keep the prompting looking like AutoCAD

Page: 11
VBA Part 2
prompts. The real meat of the program is in the getting of the two points and the creation of the line object from
those two points. The rest is support code that makes the program more palatable to the operator.

Creating Layers

AutoCAD uses tables to store general information about layers, text styles, dimension styles, linetypes, views,
viewports, user coordinate systems, and plot styles. Table definitions are created in a different way than objects.
With objects you need to be concerned with the space the object goes into and where in the space it resides
along with properties such as color, lineweight, linetype, and plot style. Table information focuses more on the
properties because most table information is used as a pattern or template (style) for the objects’ properties. The
table exception to this rule of thumb is the ‘views’ table, which defines coordinates for the zoom command to
restore. Here we will create a new layer as an example of how to create new table entries.

Public Sub CreateLayer()

Dim objLayer As AcadLayer

Set objLayer = ThisDrawing.Layers.Add("My Red Layer")

objLayer.Color = acRed ‘ make it red

ThisDrawing.ActiveLayer = objLayer ‘ make the new layer active

' Display the status of the new layer

MsgBox objLayer.Name & " has been added." & vbCrLf & _

"LayerOn Status: " & objLayer.LayerOn & vbCrLf & _

"Freeze Status: " & objLayer.Freeze & vbCrLf & _

"Lock Status: " & objLayer.Lock & vbCrLf & _

"Color: " & objLayer.Color, , "Add Example"

End Sub

Creating Collections of Objects

Earlier we talked about selection sets. These are the traditional internal mechanism in AutoCAD for gathering
information to process. VBA has its own internal mechanism called a collection for holding data to be
processed. This mechanism can also be used to hold AutoCAD objects or even selection sets for later
processing. Here we will learn a few of the techniques for manipulating collections.

Page: 12
VBA Part 2
GetAllEnts

Here you can collect all objects from a desired space into a collection. We use a function to do the work and
pass back the collection.

Public Function GetAllEnts(Space As Object, objName As String) As Collection

Dim colObjects As New Collection

Dim Ent As Object

For Each Ent In Space

On Error Resume Next

If UCase(Ent.ObjectName) = UCase(objName) Then ' is it a block?

colObjects.Add Ent

End If

Next

Set GetAllEnts = colObjects

End Function

The following code will allow you to test your new function.

Public Sub CreateEntsCollection()

Dim ents As New Collection

Set ents = GetAllEnts(ThisDrawing.ModelSpace, "AcDbCircle")

' Set ents = GetAllEnts(ThisDrawing.ModelSpace, "AcDbBlockReference")

If ents.Count > 0 Then

'Dim blk As AcadBlockReference

Dim cir As AcadCircle

'Set blk = ents.Item(1)

Set cir = ents.Item(1)

ViewObjectCollection ents

Page: 13
VBA Part 2
Else

MsgBox "No entities found."

End If

Debug.Print ents.Count

End Sub

Now you can use regular methods for spinning through a collection to process the objects. An example of that
type of code is shown below.

Public Sub ViewObjectCollection(Collection As Collection)

If Collection.Count > 0 Then

Dim strMsg As String, lngI As Long

strMsg = "Collection has a total of " & CStr(Collection.Count) & " in it." & _

vbCrLf

For lngI = 1 To Collection.Count

strMsg = strMsg & Collection.Item(lngI).ObjectName & vbCrLf

Next lngI

MsgBox strMsg

Else

MsgBox "Collection is empty."

End If

End Sub

Forms

Forms are a set of tools in VBA for gathering data and operating instructions from the operator. Forms are a
graphical interface making it easier for the operator to drive your program. A form is nothing more that a
special kind of module. Like any module it follows the rules of scope, precedence, and life of a variable. The
objects that make up a form are called controls. Each control has its own set of methods and properties. You

Page: 14
VBA Part 2
create a form and place various controls on it setting their properties and filling out their methods. This section
covers some of the techniques for creating and manipulating form controls and their methods and properties.

You create a new form by selecting the Userform menu item from the Insert pull down on the menu. You get a
blank form as shown below.

Think of this as your blank palette on which you can create your masterpiece of user interaction.

Page: 15
VBA Part 2
Use the Properties window to change the name property of your form and any other properties you need
changing (such as the caption at the top of the form). If you don’t have the Properties window you can display it
by selecting the Properties Window menu item on the View pull down of the menu.

Controls

If you’ve been using Windows for any length of time at all then you are familiar with form controls and how
they should behave. A well-behaved form will have controls that interact with one another. Buttons or other
controls will not be enabled until necessary data is supplied, the form is laid out in a logical manner for moving
the operator through the necessary steps to complete the task, and error trapping is in place to catch possible
miscues by the operator.

Page: 16
VBA Part 2
Here we will create a form for the simple task of changing the data in every specified block’s attribute in all
spaces. If the forms Toolbox window is not already open select the Toolbar menu item from the View pull
down menu to display it as shown below.

Create the following form.

Form name fmMain


Caption Manipulating Block Attributes

Create the following controls on the form.

Combo Control Two Buttons


Name cmbBlockName
Name btnChange
List Control Caption Change
Name lstAttr Name btnCancel
Caption Cancel
Edit Box
Name edAttr

Three labels

Name lblBlockName
Caption Blocks
Name lblAttrib
Caption Attributes
Name lblAttribs
Caption Data

Page: 17
VBA Part 2

The resulting form should appear similar to the one below.

Interaction between controls

We will give the form’s controls two behaviors to demonstrate how to make the controls interact. The list box
should always contain any attribute tags found in the block’s definition (blank if no attributes present) and we’ll
make the edit box invisible until an attribute tag is selected in the list box. Since the edit box will be invisible it
makes sense to have the form smaller until it is needed. To assign these behaviors we need to place some code
behind the form and its controls.

Coding takes place in the code window just as it does with modules. The Object list (upper left ribbon) and the
Procedure list (upper right ribbon) on the code window take on more meaning when working on a form
module’s code. The object list will correspond with the named controls of the form (along with the form itself)
and the procedure list will correspond with events for those controls (and the form). The figure below shows the
code window with the form’s procedure list open.

Page: 18
VBA Part 2

I had the cursor in the form’s initialize procedure (thus the form was in the object list on the upper left). The
procedures are actually events for the form. VBA differs slightly from VB in that there is no form Load event in
VBA. Everything you want to do to start up a form must occur in the initialize procedure (event).

Building the graphical interface was very simple. Just drag a control over to the form and fill out its properties
the way you wanted. Now you need to go behind the controls and add the code. I always start with the form
itself since that is where you load data and setup the look of the form when it first loads.

To get to the code behind the form or control all you need to do it double click on the form or control. Clicking
in the form takes you to the initialize code area. Clicking on a control takes you to its click area. You can add
other events by selecting them from the procedure list. VBA will automatically create the procedure header for
you if it doesn’t already exist or place you in the code area if it does already exist.

We’ll start with the form’s initialize event as shown below.

Public Sub UserForm_Initialize()

Dim ss As Collection

Set ss = GetBlockNamesCollection

Dim i As Long

With Me

For i = 1 To ss.Count

.cmbBlockNames.AddItem UCase(ss.Item(i))

Next i

If .cmbBlockNames.ListCount > 0 Then

.cmbBlockNames.ListIndex = 0

End If

.edAttr.Visible = False

.lblAttribs.Visible = False

End With

End Sub

Page: 19
VBA Part 2
Here we are getting a collection of all the block names in the drawing (a procedure we haven’t written yet) and
using the data to fill the combo box on the form. We then set the combo box to the first item in the list and make
the edit box and its label invisible. Now to create the procedure for gathering all the block names.

Private Function GetBlockNamesCollection() As Collection

Dim colBlockNames As AcadBlocks

Dim colNames As New Collection

Dim objBlock As Variant

For Each objBlock In ThisDrawing.Blocks

If Not IsInCollection(objBlock.Name, colNames) Then

If Left(objBlock.Name, 1) <> "*" Then

colNames.Add objBlock.Name, objBlock.Name

End If

End If

Next

Set GetBlockNamesCollection = colNames

End Function

This function is just a wrapper for gathering the block names from the Blocks collection in the drawing. Notice
that any block name starting with an asterisk (*) is not added. This way anonymous blocks and the two spaces
are left out of the list.

It looks good except that we are calling another procedure that we haven’t written yet (IsInCollection). That
function checks to make sure that the block name isn’t already in the collection before trying to add it to the
collection (thus avoiding error trapping at this level). Let’s build that now.

We’ll send it the block name and the collection we are building and it will return a True if the block is already
in the collection (thus the NOT on or if statement).

Page: 20
VBA Part 2

Public Function IsInCollection(Key As String, ByVal TheCollection As Collection) As Boolean

' This routine takes a string item an determines if it is in the supplied collection

' It returns True when present and False when not present

Dim Result As Boolean

Result = False

If TheCollection.Count > 0 Then

On Error Resume Next

Debug.Print "Checking on " & TheCollection.Item(Key) & _

" in the collection" ' leave in to force error

If Err.Number = 0 Then

Result = True

Else

Err.Clear

End If

End If

IsInCollection = Result

End Function

We do error trapping at this level. That way the working code above looks cleaner but we are assured that the
name is going into the collection or is already there.

Now it is time to finish the coding for the form. We need to get the Cancel button and the Change Data button,
along with making sure the combo box, listbox, and edit box all behave as specified. Let’s start with the Cancel
button.

Private Sub btnCancel_Click()

Unload Me

Terminate

End Sub

Looks simple but it is calling a user defined function called terminate (shown below).

Page: 21
VBA Part 2

Public Sub Terminate()

End

End Sub

Some may ask why put the end function in a wrapper like this since it is only one line of code. The answer
reside in good programming style. One of the basic rules for good programming is that there is only one starting
point and one ending point for a program (the same is true of a procedure). If we were to put the end function in
the Cancel button then it shouldn’t be called by any other procedure. This way any procedure can end the
program by making a call to the Terminate function.

Let’s do the populating of the list box based upon the combo box selection next.

Private Sub cmbBlockNames_Change()

Populate_Attributes_List Me.cmbBlockNames.Text

End Sub

Again we’ve wrapped a function inside another function (this time the combo box change event). Same reason
as before. This way multiple places can trigger the loading of the list box (something we are not doing in this
example application). So now we need to write the code that will populate the list box based upon whatever
block name was selected in the combo box.

This function will clear the list box and edit box before loading the list box. It will then spin through the
supplied block’s definition and gather the attribute names loading them into the list box.

Page: 22
VBA Part 2

Private Sub Populate_Attributes_List(BlockName As String)

Me.lstAttr.Clear

Me.edAttr.Text = ""

Dim blkref As AcadBlock

Set blkref = ThisDrawing.Blocks.Item(BlockName)

Dim lngI As Long

For lngI = 0 To blkref.Count - 1

If blkref.Item(lngI).ObjectName = "AcDbAttributeDefinition" Then

Me.lstAttr.AddItem blkref.Item(lngI).TagString

End If

Next lngI

End Sub

We’re just about done now. The only things not working are the list box behavior and the Change Data button
code. Let’s look at the list box behavior. We want the edit box to appear the first time the operator selects
anything inside the list box and since the edit box is out beyond the current edge of the form we want to make
the form wider when this happens. Here is how the code should look to accomplish these things.

Private Sub lstAttr_Click()

Me.Width = 385.2

Me.edAttr.Visible = True

Me.lblAttribs.Visible = True

Me.edAttr.Text = ""

End Sub

Whenever the operator clicks on the listbox the code will make sure the form’s width is set and it will show the
edit box and its label along with clearing any data typed into the edit box.

Our last piece in the puzzle is the actual work to be preformed. Here is what that will look like.

Page: 23
VBA Part 2
Private Sub btnChange_Click()

' gather the data

Dim strBlockName As String, strTagName As String, strData As String

With Me

strBlockName = .cmbBlockNames.Text

strTagName = .lstAttr.Value

strData = .edAttr.Text

End With

ProcessData strBlockName, strTagName, strData

End

End Sub

When the operator clicks on the Change Data button the code will gather and store the block name, attribute tag,
and the data to be filled in and then call a subroutine that will do the work (called ProcessData). The
ProcessData code is shown below.

Public Sub ProcessData(BlockName As String, TagName As String, strData As String)

‘ spin through all the blocks in model space and alter the data in the tag of the

‘ ones that match the blockname

ThisDrawing.ActiveSpace = acModelSpace

Dim ss As AcadSelectionSet

Set ss = Get_Blk_Occurrences (BlockName)

Dim objBlk As AcadBlockReference

Dim objBlkRef As AcadBlock

Dim varAttribs As Variant

Dim lngI As Long

For Each objBlk In ss

varAttribs = objBlk.GetAttributes

Page: 24
VBA Part 2
For lngI = 0 To UBound(varAttribs)

If varAttribs(lngI).TagString = TagName Then

If strData = "" Then

strData = " "

End If

varAttribs(lngI).TextString = strData

End If

Next lngI

Next

End Sub

This work horse routine makes sure that the drawing is in model space, gets a selection set of all the requested
blocks, spins through each block in the set finding the requested attribute tag, and changes the data in the
attribute to the requested data. The Get_Blk_Occurrences function called from this module was created earlier
in the session and is located in the AU2000 module.

There is one problem with this application. Even though we are setting the space to model space that will have
no effect on the Get_Blk_Occurrences function. It will return all occurrences of the block in all spaces. This is
because the function uses the Select method with the All option (which takes everything).

Can you write a function that will return only blocks found in a given space?

Conclusion

We’ve covered a lot of ground today. I’ve always felt that the basics of learning any new language is mastering
the languages input and output functions. With AutoCAD you also need to become familiar with the AutoCAD
objects, tables, methods, and events to write complex programs. This is not as daunting as it may seem on the
surface. Take small steps and write your program in small modules. Learn how to pass arguments back and
forth (as we’ve done here today). Master the user interface (you were only introduced to it today). Once you
have done this, you will find a whole other world of even more complex things you can do with VBA and
AutoCAD. I always say, you are only limited by your imagination. While not 100% true with VBA, it is certain
that Autodesk has raised the bar again for making AutoCAD easier to customize. There are many great
examples you can learn from shipped with AutoCAD. Check out the projects residing in the Sample/VBA
folder. The Acad_cg.dvb project is the one of the most comprehensive and it got me started. Have fun out there.

Page: 25

You might also like