LA Solutions
tel: +44 1398 361 800

MicroStation® is Bentley Systems flagship product for 3D computer-aided-design (CAD). Questions similar to this appear on the Be Community Forums. This problem appeared in the MicroStation Programming Forum.

Q How do I find elements on a specific level using MicroStation VBA?

Q How do I find elements of a particular type (e.g. line-string elements) using MicroStation VBA?

Q How do I determine whether a line-string element is closed using MicroStation VBA?

Q How do I find closed line-string elements using MicroStation VBA?

Q How do I convert a closed line-string element to a shape element using MicroStation VBA?

VBA Project: Convert Line-Strings to Shapes

Closed Line String Shape created from closed line-string

VBA project ConvertLineStringToShape.mvba provides answers to the above questions. It's a complete working VBA project with source code. The answers on this page explain the code's purpose.

  1. Click the link below to download a ZIP archive that contains the VBA project
  2. Unpack the archive and copy the .mvba file to a well-known location
      A well-known location would be, for example,  …\Organization\Standards\macros
  3. Open a MicroStation DGN file and place some closed line strings
  4. Key-in vba run [ConvertLineStringToShape]modMain.Main
    • The Convert Line Strings to Shapes dialog (VBA UserForm) appears …
Convert Line Strings to Shapes dialog

You can choose to convert all closed line strings in a DGN model, or only those found in a fence or selection set. To process all closed line strings, click the Process Multiple Lines button.

If you want to pick manually one or more line strings to convert, click the Pick Line String button.

Notes:

Download VBA Project

ConvertLineStringToShape ZIP archive

Download the ConvertLineStringToShape VBA Project.


A MicroStation includes a scanning engine that is used for many purposes. It's available to you in VBA as the ModelReference.Scan method. You specify what you want to search for (e.g. elements on a named level) through the ElementScanCriteria object.

The methodology of scanning a model is straightforward …

Enumeration provides you with a list of elements, each of which has already passed the test you imposed with your scan criteria. So, if you specified a level filter, you know that each element received from the enumerator belongs to one of the levels specified. If your scan criteria requested only text elements, then each element returned by the enumerator will be a TextElement.


A There are a number of scanning examples provided in the VBA help. Search help for scan criteria or scan to find them.

Scan by Level

Here's an example that searches for elements on a named level: copy this code into a module in the VBA editor, supply a valid level name, and vba run Main …

Main entry point 
Sub Main()
    Dim msg As String
    Dim nElements   As Long
    Const levelName As String = "Level 11"
    nElements = ScanByLevel(levelName)
    msg = "Found " & CStr(nElements) & " elements on level '" & levelName & "'", vbInformation Or vbOKOnly, "Scanned Elements"
    ShowMessage msg, msg, msdMessageCenterPriorityInfo
End Sub
' -------------------------------------------------------------- 
' Process any element that meets the scan criteria: named level 
' -------------------------------------------------------------- 
Function ScanByLevel(levelName As String) As Long

    Dim nElements       As Long
    nElements = 0
	'	Find named level
    Dim oLevel          As Level
    Set oLevel = ActiveModelReference.Levels(levelName)
    If (oLevel Is Nothing) Then
        MsgBox "Level '" & levelName & "' does not exist", vbCritical Or vbOKOnly, "Nonexistent Level"
        Exit Function
    End If
	'	Set up scan criteria
    Dim oScanCriteria   As ElementScanCriteria
    Set oScanCriteria = New ElementScanCriteria
    oScanCriteria.ExcludeAllLevels
    oScanCriteria.IncludeLevel oLevel
	'	Perform the scan
    Dim oEnumerator     As ElementEnumerator
    Set oEnumerator = ActiveModelReference.Scan(oScanCriteria)
    Do While oEnumerator.MoveNext
        oEnumerator.Current.Redraw msdDrawingModeHilite
        nElements = nElements + 1
    Loop
    ScanByLevel = nElements
End Function

A There are a number of scanning examples provided in the VBA help. Search help for scan criteria or scan to find them.

Scan for Line-String Elements

Here's an example that searches for line-string elements and processes only those that are closed. Copy this code into a module in the VBA editor and vba run Main …

Main entry point 
Sub Main()
    Dim msg As String
    Dim nElements   As Long
    nElements = ScanForLineStrings()
    msg = "Found " & CStr(nElements) & " line-string elements"
    ShowMessage msg, msg, msdMessageCenterPriorityInfo
End Sub
' -------------------------------------------------------------- 
' Process line-string elements                                          
' -------------------------------------------------------------- 
Function ScanForLineStrings() As Long
    Dim nElements       As Long
    nElements = 0

    '	Set up scan criteria
    Dim oScanCriteria   As ElementScanCriteria
    Set oScanCriteria = New ElementScanCriteria
    oScanCriteria.ExcludeAllTypes
    oScanCriteria.IncludeType msdElementTypeLineString
    '	Perform the scan
    Dim oEnumerator     As ElementEnumerator
    Set oEnumerator = ActiveModelReference.Scan(oScanCriteria)
    Do While oEnumerator.MoveNext
        Dim oLine       As LineElement
        Set oLine = oEnumerator.Current.AsLineElement
        ' ... do something with line-string
        nElements = 1 + nElements
    Loop
    ScanForLineStrings = nElements
End Function

Is a Line-String Closed?

Closed Line String

A The essential function in the code above is IsLineStringClosed. A closed line-string looks like a shape, but has no area. It looks like a shape because its first and last vertices are coincident. With VBA we can check those first and last vertices to see if they are the same.

Function IsLineStringClosed accepts a LineElement and determines whether its end points are coincident …

Function IsLineStringClosed (ByVal oLineString As LineElement) As Boolean
    IsLineStringClosed = False
    If 0.0 = Point3dDistance (oLineString.StartPoint, oLineString.EndPoint) Then
        IsLineStringClosed = True
    EndIf
End Function

Find Closed Line-Strings

Main entry point 
Sub Main()
    Dim msg As String
    Dim nElements   As Long
    nElements = ScanForClosedLineStrings()
    msg = "Found " & CStr(nElements) & " closed line-string elements"
    ShowMessage msg, msg, msdMessageCenterPriorityInfo
End Sub
' -------------------------------------------------------------- 
' Process line-string elements                                          
' -------------------------------------------------------------- 
Function ScanForClosedLineStrings() As Long
    Dim nElements       As Long
    nElements = 0

    '	Set up scan criteria
    Dim oScanCriteria   As ElementScanCriteria
    Set oScanCriteria = New ElementScanCriteria
    oScanCriteria.ExcludeAllTypes
    oScanCriteria.IncludeType msdElementTypeLineString
    '	Perform the scan
    Dim oEnumerator     As ElementEnumerator
    Set oEnumerator = ActiveModelReference.Scan(oScanCriteria)
    Do While oEnumerator.MoveNext
        If IsLineStringClosed (oEnumerator.Current.AsLineElement) Then
            nElements = 1 + nElements
        EndIf
    Loop
    ScanForLineStrings = nElements
End Function

Convert Line-String to Shape

A MicroStation element types are distinct. A line-string element and a shape element are different types. There is no direct conversion between different types. For example, there's no way in VBA to turn a LineElement into a ShapeElement.

If a line-string is closed, then the path from LineElement to ShapeElement is nonetheless straightforward …

  1. Extract the vertices of the line-string element
  2. Construct a new shape element from those vertices
  3. Delete the original line-string
  4. Add the new shape to the active DGN model

Here's some code that creates a ShapeElement from the vertices of a LineElement. Note that the line element is unaffected — it's not really been converted to a shape, even though it may appear that way to a user …

Function CreateShapeFromLineString(ByVal oLine As LineElement) As Boolean
    CreateShapeFromLineString = False
    Dim points()                            As Point3d
    points = oLine.GetVertices()
    Dim oShape                              As ShapeElement
    Set oShape = CreateShapeElement1(Nothing, points, msdFillModeFilled)
    ActiveModelReference.AddElement oShape
    CreateShapeFromLineString = True
End Function

Here's the result. Compare with the image above …

Shape created from closed line-string

Click the link above to download a ZIP archive that contains the VBA project


Questions

Post questions about MicroStation programming to the MicroStation Programming Forum.