You are on page 1of 16

Introduction to VBA Programming

In
MicroStation®

Copyright © 2013 Bentley Systems, Inc.


On the Grid…
Our Seminar today is intended to quickly introduce you to a number of concepts in MicroStation VBA.
We will create a “Grid Maker” applet as a means of accomplishing this task. Along the way, we will be
exploring MicroStation’s Integrated Development Environment (IDE); MicroStation’s API; various objects
along with their methods and properties; and the VBA programming language.

The “Grid Maker” is a simple applet we should be able to complete during the course of the seminar. It
makes use of fundamental structures and syntax. Yet while simple, it contains a ”standard” module, a
form and a class module.

What are forms and modules? In a MicroStation dgn file we group elements into cells, layers and
models according to their purpose. In a like manner we separate logical sections of a VBA project code
into understandable sections. In some sense forms, modules and classes serve as containers that enable
us to organize our code into logical bundles. The following is an overview of that structure:

Module

A module is a “container” for code. It contains lists of variables, functions and procedures or
subroutines.

Form

A form is an object such a window or dialog box. Forms usually contain various controls which are
referred to a child objects. Controls are items such as command buttons, check boxes, text boxes and
scroll bars.

A form has both graphical components and code components. Its code component is like a standard
module. As you build a form graphically by adding various controls such as progress bars, buttons and
labels, the events, methods and properties accompanying those controls (objects) become available for
you as a programmer to utilize.

Class Module

The visual basic reference defines a Class in this manner: “The formal definition of an object. The class
acts as the template from which an instance of an object is created at run time. The class defines the
properties of the object and the methods used to control the object's behavior.”

A class appears very similar to a standard module; however it has no real use/existence until it is
instantiated. In the GridMaker program, a class is used as a means for MicroStation to talk to the
program as if it were a native MicroStation command.

Procedures (sub routines)

Forms, Modules, and Class Modules are divided into functions or sub routines (procedures). Typically
procedures, subs and functions are structured in manner similar to these outlined below:

Copyright © 2013 Bentley Systems, Inc.


Private Sub DoSomething()
Line of code…
Line of code…
Line of code…
End Sub

or

Public Function FigureSomething(input_variable)


Line of code…
Line of code…
Line of code…
FigureSomething = n
End Function

The visual basic reference defines procedures in this manner: “A named sequence of statements
executed as a unit. For example, Function, Property, and Sub are types of procedures. A procedure
name is always defined at module level. All executable code must be contained in a procedure.
Procedures can't be nested within other procedures.”

Code Lines

Whereas modules can be broken down into procedures, procedures are broken into lines of code. A few
things to be aware of with lines as they appear in the VB editor:

 Words that appear in color (magenta) are reserved words that have preset meaning.
 Lines that begin with an apostrophe (‘) are comments and are not executed. These lines will
display green text with a cyan highlight.
 Text in red is problematic code.
 A line ending in an underscore (_) is continued on the next line.
 A colon (:) is used to separate statements on a line. It acts like a new line.

Syntax

We will discuss syntax as the seminar progresses. Unfortunately we won’t have time to address all
aspects of the VBA language. You will find, however, both Microsoft’s VBA and the MicroStation object
model are well documented in the help files that ship with MicroStation.

Getting Help
In addition to the local help files, there are numerous online resources at your disposal. These include:

 The BE Communities - http://communities.bentley.com/

 Select Services - http://selectservices.bentley.com/en-US/

 The Microsoft Developer Network – www.msdn.com

Copyright © 2013 Bentley Systems, Inc.


Explanation of GridMaker
The following is an explanation of various elements and conventions found in the GridMaker applet.
The applet code in its entirety is here, and is organized by module/form/class. Code appears in the blue
boxes and again at the end of this document in “print-out” form.

Option Explicit is a compiler directive that forces explicit


Startup Module declaration of variables. It is not a part of a procedure and
resides at the beginning of a module.
Option Explicit
The Public Sub StartGridMaker procedure will be visible to
Public Sub StartGridMaker() the”outside world” as an executable macro. We use this to start
the entire program.
FrmGridMaker.Show
FrmGridMaker.Show causes the FrmGridMaker form to
End Sub
appear.

End Sub is just that. It marks the end of our procedure.

FrmGridMaker Form Object

The FrmGridMaker form (pictured below) contains two text boxes, two labels and a command button.
The first text box is an object we have named TbRows .

Form Caption Close Button

Text box: “TbRows”


Labels
Text box: “TbCols”

Command Button: “CbPlaceGrid”

Form: “GridMakerForm”

Copyright © 2013 Bentley Systems, Inc.


To refer to the text box “TbRows” from a module programmatically we would key in:

FrmGridMaker.TbRows

Notice the dot (period) between the form name (container object) and the text box name. The dot
notation is how we show the “complete path” of an object, method or property. For instance if we
wanted to programmatically set the background color of the aforementioned text box to red we would
key in:

mGridMaker.TbRows.BackColor = vbRed

While the forgoing sample is something we might do when a


program is running, we could also change the background color at
design time through the properties dialog box in the IDE. This
dialog is usually docked to the left side of the Microsoft Visual
Basic window

BackColor Property in properties dialog

Copyright © 2013 Bentley Systems, Inc.


FrmGridMaker Form Code

Option Explicit is a compiler directive that forces explicit


Option Explicit declaration of variables. It is not a part of a procedure
Private Sub UserForm_Initialize() and resides at the beginning of a module.

' pre-populate text fields with default values The Private Sub UserForm_Initialize() procedure is
automatically executed as a result of calling the form’s
Me.TbRows = 4 show method in the procedure Startup.StartGridMaker.
We will use this procedure to pre-populate the text
Me.TbCols = 4 fields. Note the procedure is Private. This means it will
End Sub not be assessable from outside the form.

Any text that appears after an apostrophe (‘) is


considered a comment and is not compiled into
executable code.
The “Me.” statements refer to the object in which they
appear—in this case the FrmGridMaker form. While not MeTbRows = 4 sets the value/text to 4. When setting
necessary “Me.” is helpful in locating objects that are the text box to a string quotes are required e.g.
children of the form. More to the point, typing “Me.” MeTbRows = ”ABC”
produces a list of the form’s methods, properties and
End Sub is just that. It marks the end of our procedure.
child objects.

These two nearly identical


procedures respond to text box
exit events. The exit event
occurs when the text box loses
Private Sub TbCols_Exit(ByVal Cancel As MSForms.ReturnBoolean) the focus (e.g. the user clicks a
different control).

TbCols = Int(Val(TbCols)) The logic in these procedures


ensures useable data is entered.
If Val(TbCols) < 1 Then TbCols = 1
The Int function returns the
integer portion of a number and
End Sub the Val function returns a
number from a string. Note
these functions are nested.
In this case, a numeric value is
Private Sub TbRows_Exit(ByVal Cancel As MSForms.ReturnBoolean) derived from the characters in
the text box through the Val
function. The Int function then
TbRows = Int(Val(TbRows)) removes the decimal portion of
the number (if it exists).
If Val(TbRows) < 1 Then TbRows = 1

This statement ensures a


End Sub number of 1 or greater exists in
the text box.

Copyright © 2013 Bentley Systems, Inc.


This procedure is launched when the “Place Grid”
button is pressed. Technically this procedure responds
to the click event for the CbPlaceGrid command button.

Private Sub CbPlaceGrid_Click() The CommandState.StartPrimitive New ClsDrawGrid


statement “tells” MicroStation a new “primitive”
CommandState.StartPrimitive New ClsDrawGrid command is starting and what the command is.
End Sub An instance of the command class (ClsDrawGrid) is
created and attached to MicroStation. MicroStation
begins to send user input to the command class and
program flow moves to the class (See ClsDrawGrid).

ClsDrawGrid Class Module

Option Explicit The Implements IPrimitiveCommandEvents provides


the necessary “connection points” MicroStation requires
to interact with a command—In this case a command
that is used to create geometry. The connection points
Implements IPrimitiveCommandEvents are expressed as procedures that must be present--
even if they don’t do anything.
Dim points(0 To 1) As Point3d
The complete list of procedures for
Dim ClickNumber As Integer
IPrimitiveCommandEvents is as follows:
Dim DM As MsdDrawingMode
1. IprimitiveCommandEvents_Cleanup()
2. IprimitiveCommandEvents_DataPoint()
3. IprimitiveCommandEvents_Dynamics()
4. IprimitiveCommandEvents_Keyin()
5. IprimitiveCommandEvents_Reset()
Dim statements are used to establish variables of various types. 6. IprimitiveCommandEvents_Start()
Since these Dim statements appear outside a procedure, the
variables are visible to the entire module.

Dim ClickNumber as Integer creates a variable of the type integer


called “ClickNumber”.

Dim points(0 to 1) as Point3d creates a (short) array of variables


which may be reference by the name “points” and a number in
parenthesis e.g. points(1)

This procedure is not used in this case. Never-the-


less, its presence is required.

Private Sub IPrimitiveCommandEvents_Start() This procedure is called at beginning of the


command. It might be used to set variables or
adjust settings.
End Sub
Copyright © 2013 Bentley Systems, Inc.
Private Sub IPrimitiveCommandEvents_DataPoint(Point As Point3d, ByVal View As View)

points(ClickNumber) = Point
CommandState.StartDynamics causes MicroStation to
ClickNumber = ClickNumber + 1 continuously, with each change in mouse position, execute
the IPrimitivecommandEvents_Dynamics procedure.

If ClickNumber = 1 Then CommandState.StartDynamics

If ClickNumber = 2 Then DrawGrid points(0), points(1): PrimitiveCommandEvents_Reset

The IprimitiveCommandEvents_DataPoint procedure is executed each time a data point is sent to MicroStation while our custom
command is active. The coordinates of the data point as well as what view it was selected from are sent by MicroStation to this
procedure. Here is what’s happening:

1. An element of the “points” array is assigned the latest data point coordinates.
2. The variable ClickNumber is incremented.
3. Beginning after the first click, dynamics are turned on.
4. With the second click the grid is drawn and a reset is programmatically executed.

DM = DrawMode

DrawGrid points(0), Point

End Sub

The IprimitiveCommandEvents_Dynamics procedure is executed whenever the MicroStation cursor is moved. We use this procedure to
“undraw” and redraw elements to the screen dynamically. The DrawMode variable determines if the element is being erased or
redrawn. In our example here the DrawGrid procedure is being called with the first data point and the current location of the cursor.
The effect is a grid the dynamically resizes.

Copyright © 2013 Bentley Systems, Inc.


The IprimitiveCommandEvents_Reset procedure is
executed when the user enters a reset (usually a right
Private Sub IPrimitiveCommandEvents_Reset()
mouse click).

CommandState.StopDynamics CommandState.Stopdynamics halts the calling of


IprimitivecommandEvents_Dynamics procedure.
ClickNumber = 0

End Sub

This procedure is not used in


this case. Never-the-less, its
presence is required.
Private Sub IPrimitiveCommandEvents_Keyin(ByVal Keyin As String)

End Sub

This procedure is not used in


this case. Never-the-less, its
Private Sub IPrimitiveCommandEvents_Cleanup() presence is required.

This procedure is called at end


of the command. It is used to
End Sub take care of “housekeeping”
matters.

Copyright © 2013 Bentley Systems, Inc.


DrawGrid contains the logic for determining the
locations of the grid lines. It does not actually
draw the elements to the screen or to the
Sub DrawGrid(LL As Point3d, UR As Point3d)
MicroStation model—that is handled by the
Dim Startpt As Point3d DrawLine procedure.

Dim Endpt As Point3d DrawGrid requires two points be passed to it by


a calling statement. The points have been
Dim Dif As Point3d named LL (Lower Left) and UR (Upper Right).
Note: It is not critical the points be entered by
Dim c As Integer
the user in that order.
Dim Spacing As Double
Variable declarations.

The Point3DSubtract function subtracts the


Dif = Point3dSubtract(UR, LL) coordinates of two vectors or points.

'column lines Comments are preceded by an apostrophe(‘).

Spacing = Dif.X / FrmGridMaker.TbCols In this line we take the x ordinate of the point
“Dif” and divide it by the value TbCols text box
Startpt.Y = LL.Y
found on the form “FrmGridMaker”.
Endpt.Y = UR.Y
For – Next Loop
The contents of this loop is repeated until the
value ‘c’ is equal to the value in the
For c = 0 To FrmGridMaker.TbCols FrmGridMaker.TcCols text box. The starting
value of c is 0 and it is incremented each time
Startpt.X = LL.X + (Spacing * c)
the loop is executed.
Endpt.X = Startpt.X

DrawLine Startpt, Endpt

Next

'row lines

Spacing = Dif.Y / FrmGridMaker.TbRows


This section of code is nearly identical to the
Startpt.X = LL.X preceding section that calculated the column
lines.
Endpt.X = UR.X

For c = 0 To FrmGridMaker.TbRows

Startpt.Y = LL.Y + (Spacing * c)

Endpt.Y = Startpt.Y

DrawLine Startpt, Endpt

Next

End Sub

Copyright © 2013 Bentley Systems, Inc.


Creation and display of lines
happens here in the DrawLine
procedure. Statements that call
Sub DrawLine(Startpt As Point3d, Endpt As Point3d)
this procedure must pass it two
points.

Dim oLine As LineElement Declare oLine as a Line element


object

Object elements need to be Set


Set oLine = CreateLineElement2(Nothing, Startpt, Endpt) before that can be used. Here we
use CreateLineElement2 to
instantiate oLine.
If ClickNumber = 2 Then
The block If-then-else statement
ActiveModelReference.AddElement oLine checks the ClickNumber. If it is 2
the line (part of the grid) is
Else added to the current
MicroStation model, If the value
oLine.Redraw DM 'Used with dynamics
is not 2 then the element is
End If earthier drawn or undrawn to
the screen. The variable DM
controls the draw mode and is
set by the
End Sub
IPrimitivecommandEvents_
Dynamics procedure.

Copyright © 2013 Bentley Systems, Inc.


Terms
The following is a list of terms used in this case study. It is in no way exhaustive. Most of this
information is available in the “Standard” Visual Basic Reference help or the MicroStation-specific VBA
reference which will display when searching for help on a particular member in the object browser.

Control

An object you can place on a form that has its own set of recognized properties, methods, and
events. You use controls to receive user input, display output, and trigger event procedures. You
can manipulate most controls using methods. Some controls are interactive (responsive to user
actions), while others are static (accessible only through code). – Visual Basic Reference

Standard controls are readily available from the toolbox in the VBA editor. Other controls may
be added from the Tools pull-down menu.

Class Module

A module that contains the definition of a class, including its property and method definitions.
– Visual Basic Reference

Event

An event is an action recognized by an object, such as clicking the mouse or pressing a key, and
for which you can write code to respond. Events can occur as a result of a user action or
program code, or they can be triggered by the system. – Visual Basic Reference

Form

A window or dialog box. Forms are containers for controls. A multiple-document interface (MDI)
form can also act as a container for child forms and some controls. – Visual Basic Reference

Method

A procedure that acts on an object. – Visual Basic Reference

Module (standard module)

A module containing only procedure, type, and data declarations and definitions. Module-level
declarations and definitions in a standard module are Public by default. A standard module is
referred to as a code module in earlier versions of Visual Basic. – Visual Basic Reference

Model Reference

All graphical elements in MicroStation are in models. A Visual Basic program has to access a
model to be able to save or retrieve graphical elements. A MicroStation session may access
many models. The models may be in different design files. The same model may be referenced
different ways. For example, a model may be in use as the active model. There may also be

Copyright © 2013 Bentley Systems, Inc.


different views of the model mapped into the same view. The MicroStation object model treats
each of these references as a ModelReference object.

MVBA

File extension for a MicroStation Visual Basic Project (filename.mvba)

Procedure

A named sequence of statements executed as a unit. For example, Function, Property, and Sub
are types of procedures. A procedure name is always defined at module level. All executable
code must be contained in a procedure. Procedures can't be nested within other procedures.
– Visual Basic Reference.

Scope

Defines the visibility of a variable, procedure, or object. For example, a variable declared as
Public is visible to all procedures in all modules in a directly referencing project unless Option
Private Module is in effect. When Option Private Module is in effect, the module itself is private
and therefore not visible to referencing projects. Variables declared in a procedure are visible
only within the procedure and lose their value between calls unless they are declared Static. –
Visual Basic Reference.

String

A variable that contains a series of letters, sentences paragraphs or entire documents. When
we need to work with text we use strings

Sub procedure

A procedure that performs a specific task within a program, but returns no explicit value. A Sub
procedure begins with a Sub statement and ends with an End Sub statement. – Visual Basic Reference.

VBA Visual Basic for Applications

Copyright © 2013 Bentley Systems, Inc.


Launching a MicroStation VBA Macro

Macros may be launched from MicroStation by selecting the Utilities>Macros>Project Manager menu
item, loading the project (if necessary) and selecting the “Macros” button.

When using MicroStation’s command browser, Custom tool or other method that implements Key-ins,
use one of the following:

VBA RUN [project name]module_name.subprocedure Loads and Runs a Macro

VBA execute subprocedure Runs a visible sub


Or procedure that has
VBA execute module_name.subprocedure already been loaded.

Visual Basic for Applications Configuration Variables

The following table lists the configuration variables that affect Visual Basic for Applications. Each
configuration variable expects a valid value. An invalid value will not override a setting. You do not need
to close and restart in order for the configuration variable change to take effect.

Variable "Short name" Description

"Automatically save VBA If set to 1, automatically saves modified VBA projects every
MS_VBASAVEONRUN
project" time it starts running a VBA program.

"Names of standard Names of the projects that are opened when the VBA dialog is
MS_VBAAUTOLOADPROJECTS
projects" opened.

"Directories to search for Directories that are searched when opening an existing VBA
MS_VBASEARCHDIRECTORIES
VBA projects" project.

MS_VBANEWPROJECTDIRECTORY "Directory for new projects" Directory that is used when a new project is created.

Copyright © 2013 Bentley Systems, Inc.


Startup Module Code
Option Explicit
Dim Test As String

Public Sub StartGridMaker()

FrmGridMaker.Show

End Sub

FrmGridMaker Form Code


Option Explicit

Private Sub UserForm_Initialize()


' pre-populate text fields with default values
Me.TbRows = 4
Me.TbCols = 4 Text box: “TbRows”
End Sub
Text box: “TbCols”
Private Sub TbCols_Exit(ByVal Cancel As MSForms.ReturnBoolean) Command Button:
“CbPlaceGrid”
TbCols = Int(Val(TbCols))
If Val(TbCols) < 1 Then TbCols = 1

End Sub

Private Sub TbRows_Exit(ByVal Cancel As MSForms.ReturnBoolean)

TbRows = Int(Val(TbRows))
If Val(TbRows) < 1 Then TbRows = 1

End Sub

Private Sub CbPlaceGrid_Click()


CommandState.StartPrimitive New ClsDrawGrid
End Sub

ClsDrawGrid Class Module Code

Option Explicit

Implements IPrimitiveCommandEvents
Dim points(0 To 1) As Point3d
Dim ClickNumber As Integer
Dim DM As MsdDrawingMode

Private Sub IPrimitiveCommandEvents_Start()

End Sub

Private Sub IPrimitiveCommandEvents_DataPoint(Point As Point3d, ByVal View As View)


points(ClickNumber) = Point
ClickNumber = ClickNumber + 1

If ClickNumber = 1 Then CommandState.StartDynamics


If ClickNumber = 2 Then DrawGrid points(0), points(1): IPrimitiveCommandEvents_Reset

Copyright © 2013 Bentley Systems, Inc.


End Sub

Private Sub IPrimitiveCommandEvents_Dynamics(Point As Point3d, ByVal View As View, ByVal DrawMode


As MsdDrawingMode)

DM = DrawMode
DrawGrid points(0), Point

End Sub

Private Sub IPrimitiveCommandEvents_Reset()

CommandState.StopDynamics
ClickNumber = 0

End Sub

Private Sub IPrimitiveCommandEvents_Keyin(ByVal Keyin As String)

End Sub
Private Sub IPrimitiveCommandEvents_Cleanup()

End Sub

Sub DrawGrid(LL As Point3d, UR As Point3d)


Dim Startpt As Point3d
Dim Endpt As Point3d
Dim Dif As Point3d
Dim c As Integer
Dim Spacing As Double

Dif = Point3dSubtract(UR, LL)


'column lines
Spacing = Dif.X / FrmGridMaker.TbCols
Startpt.Y = LL.Y
Endpt.Y = UR.Y

For c = 0 To FrmGridMaker.TbCols
Startpt.X = LL.X + (Spacing * c)
Endpt.X = Startpt.X
DrawLine Startpt, Endpt
Next

'row lines
Spacing = Dif.Y / FrmGridMaker.TbRows
Startpt.X = LL.X
Endpt.X = UR.X

For c = 0 To FrmGridMaker.TbRows
Startpt.Y = LL.Y + (Spacing * c)
Endpt.Y = Startpt.Y
DrawLine Startpt, Endpt
Next

End Sub

Sub DrawLine(Startpt As Point3d, Endpt As Point3d)

Dim oLine As LineElement

Set oLine = CreateLineElement2(Nothing, Startpt, Endpt)

If ClickNumber = 2 Then
ActiveModelReference.AddElement oLine
Else
oLine.Redraw DM 'Used with dynamics
End If

End Sub

Copyright © 2013 Bentley Systems, Inc.

You might also like