This article is about MicroStation® Visual Basic for Applications (VBA). It's written for developers using Bentley Systems MicroStation. Questions similar to this appear on the Be Communities Forums. This problem appeared in the MicroStation Programming Forum.

Introduction

This article discusses an interactive cell placement tool for MicroStation. It is written in MicroStation VBA. The VBA project is available for download.

A MicroStation Cell is a group of graphic elements that is used repeatedly. Multiple cells are stored in a cell library. An architect, for example, might have a cell library named furniture.cel. Cells in that library would probably include doors, windows and other fixtures.

A MicroStation user places, or instantiates, a cell by …

  1. Selecting, or activating, a cell from a cell library
  2. Starting MicroStation's Place Cell command
  3. Placing a datapoint with the cursor to instantiate the cell
  4. MicroStation copies the cell and its components to the active model

How do I place a cell?


A Before you create a CellElement, you want to be sure it exists in a currently-attached Cell Library. Here's one way, that works on the negative inversion principle. Attempt to create a cell using the proposed name. If the create method succeeds, the cell exists in the cell library …

Function CellExistsInLibrary (cellName As String) As Boolean
  CellExistsInLibrary = False
  On Error GoTo err_CellExistsInLibrary
  Dim oCell   As CellElement
  Dim origin  As Point3d, _
      scale   As Point3d
  origin = Point3dZero
  scale = Point3dOne
  Set oCell = CreateCellElement2 (cellName, origin, scale, True, Matrix3dIdentity)
  ' If we get here, the cell exists in a library	
  CellExistsInLibrary = True
  Set oCell = Nothing
  Exit Function

err_CellExistsInLibrary:
  '  Cell doesn't exist	
  MsgBox "Cell '" & cellName & "' Not Found"
End Function

Here's another way, by Ron Reemer, who contributed this to the MicroStation Programming Forum …

Function CellExists(cellName As String) As Boolean
  CellExists = False
  If IsCellLibraryAttached Then
    Dim celEnum As CellInformationEnumerator
    ' Get list of cells	
    Set celEnum = GetCellInformationEnumerator(True, False)
    ' Loop through cells	
    Do While celEnum.MoveNext
      If celEnum.Current.Name = cellName Then
        ' Found the cell so return True 
        CellExists = True
        Exit Function
      End If
    Loop
    ' Cell not found	
    MsgBox "Cell '" & cellName & "' Not Found"
  Else
    ' No library attached	
    MsgBox "No Cell Library Attached"
  End If
End Function

A   We seek to replicate, more or less, MicroStation's built-in Place Cell command. The Cell Placer class provides that functionality.

A rider to the original question was "How do I enter a new cell name at any time to change the cell before it is placed?" We answer that question by allowing the user to key-in a cell name while our primitive command is operating.

A second rider to the original question was "How do I place a cell and immediately drop it?" That question is answered by the Cell Place and Drop class. It's identical to the first class except that, at the point of instantiation, the cell is dropped to its components. The components are added individually to the active model.

The VBA project has three modules …

Main Module

modMain provides two entry points, depending which version of Cell Placer you want to start …

  1. Sub PlaceCell
  2. Sub PlaceAndDropCell
' ---------------------------------------------------------------------
'   MicroStation key-in:
'   vba run [CellPlacement]modMain.PlaceCell
' ---------------------------------------------------------------------
Public Sub PlaceCell()
    Dim oCellPlacer As New clsCellPlacer
    oCellPlacer.CellName = ActiveSettings.CellName
    Const WantKeyins  As Boolean = True
    CommandState.StartPrimitive oCellPlacer, WantKeyins
End Sub
' ---------------------------------------------------------------------
'   MicroStation key-in:
'   vba run [CellPlacement]modMain.PlaceAndDropCell
' ---------------------------------------------------------------------
Public Sub PlaceAndDropCell()
    Dim oCellPlacer As New clsCellPlaceAndDrop
    oCellPlacer.CellName = ActiveSettings.CellName
    Const WantKeyins  As Boolean = True
    CommandState.StartPrimitive oCellPlacer, WantKeyins
End Sub

The code, in each case, creates an object from the class definition. It sets the class CellName property to the active cell name. It then assigns that object to MicroStation's state engine with CommandState.StartPrimitive.

Primitive Command Key-In

This code demonstrates a little-used facility of a primitive command: accepting a user key-in. We start the primitive function with the optional WantKeyins argument (Boolean True). While the primitive command is active, the MicroStation user can key-in text at any time.

In this example, the key-in is interpreted as a cell name. When the command starts, it uses the active cell. While the command is executing, the user may key-in a different cell name. If that cell exists in the attached cell library, the command immediately uses that cell.

Cell Placer Class

This is a VBA class module. It Implements IPrimitiveCommandEvents, making it a primitive command class. The cell name is stored in a class variable m_strCellName …

Private m_strCellName As String

m_strCellName is assigned the active cell name by the calling subroutine in modMain.

_Start Event

The IPrimitiveCommandEvents_Start subroutine implements the start event. It initialises the command, setting the user prompts and command name. It also starts dynamics, so that the user can see the cell as it is stuck to the cursor.

_Dynamics Event

MicroStation calls the dynamics event repeatedly as the user moves the cursor. We pass the cursor data point to the CreateCell subroutine, along with the DrawMode.

_Datapoint Event

MicroStation calls the dynamics event once, when the user places a data point. We pass the cursor data point to the CreateCell subroutine, along with the DrawMode msdDrawingModeNormal.

_Keyin Event

The user may key-in a new cell name at any time. The IPrimitiveCommandEvents_Keyin copies the user key-in to member variable m_strCellName. The new cell name is used immediately.

CreateCell Subroutine

The CreateCell subroutine is called by both the _Dynamics event and the _Datapoint event. Each event passes the current datapoint and draw mode. The _Datapoint event always passes draw mode msdDrawingModeNormal; the _Dynamics event passes one of several other MsdDrawingMode values.

We create the cell using the cell name stored in member variable m_strCellName.

We use the draw mode to either add the cell to the active model following a datapoint (ActiveModelReference.AddElement oCell), or to display it at the current cursor position (oCell.Redraw) …

Private Sub CreateCell(ByRef point As Point3d, ByVal drawMode As MsdDrawingMode)
    Dim oCell As CellElement
    Set oCell = CreateCellElement2(m_strCellName, point, Point3dOne, True, Matrix3dIdentity)
    If drawMode = msdDrawingModeNormal Then
        ActiveModelReference.AddElement oCell
    Else
        oCell.Redraw drawMode
    End If
End Sub

Cell Place and Drop Class

This class is identical to clsCellPlacer until the user places a datapoint. Instead of adding the cell to the active model, we add its components …

Private Sub DropCell(ByVal oCell As CellElement)
    Dim oComponents As ElementEnumerator
    Set oComponents = oCell.Drop
    Do While oComponents.MoveNext
        Dim oElement As Element
        Set oElement = oComponents.Current
        ActiveModelReference.AddElement oElement
    Loop
End Sub

Download VBA Cell Placement Project

Download CellPlacement.ZIP

The above code is available in this MicroStation VBA project. Unpack the ZIP archive and copy CellPlacement.mvba to a location where MicroStation can find it. A good place to copy it would be \Workspace\Standards\vba. To start placing cells, key one of the following into MicroStation's keyin dialog …

vba run [CellPlacement]modMain.PlaceCell
vba run [CellPlacement]modMain.PlaceAndDropCell

Back to the VBA article index.