Q MicroStation has built-in tools to extract metrics from different types of objects. For example, it can measure the length of a line, the area of an ellipse, or the volume of a cube. However, it doesn't satisfy the following questions, posed by MDL and VBA developers, that pop up occasionally on the Be Communities Discussion Groups, …

A  Since a line string doesn't have the concept of area, MicroStation can't measure it. However, it seems reasonable to many people that a line-string whose first and last vertices are coincident looks remarkably like a shape and consequently should be prepared to reveal its area, especially when that other CAD product can do it anyway …

MicroStation grouped hole elements pose a different problem: MicroStation can measure the area of a grouped hole, but how do you do it using VBA? There a page dedicated to help you identify and measure a grouped hole element using VBA.

Here's a VBA example that illustrates how to obtain information about areas and closed line-string elements. Copy this code into a regular VBA module, then run it within the IDE, or from a MicroStation keyin vba run [MeasureArea]modMain.Main …

Option Explicit
Option Base 0

' ---------------------------------------------------------------------
'   MeasureArea gets the area of planar closed elements (e.g. ellipse,
'   shape, complex shape) or closed line strings.  A closed line-string
'   has the appearance of a shape element (i.e. the first and last
'   vertices are coincident), and this module treats it as if it were
'   a shape element
'
'   To run this tool, use this keyin:
'   vba run [MeasureArea]modMain.main
'
'   Notice:
'   MeasureArea is supplied as example code by LA Solutions Ltd.
'   http://www.la-solutions.co.uk
'   This code is provided without guarantee of fitness for purpose and
'   is not supported.  You are free to copy this code and use it for
'   whatever purpose in pursuit of MicroStation VBA happiness provided
'   that this notice is retained in full
' ---------------------------------------------------------------------

Sub Main()
    CommandState.StartLocate New clsMeasureArea
End Sub

The Main() subroutine invokes MicroStation's location logic by creating an instance of the MeasureArea class that implements ILocateCommandEvents …

Option Explicit
' ---------------------------------------------------------------------
Implements ILocateCommandEvents
' ---------------------------------------------------------------------
Private Sub ILocateCommandEvents_Accept(ByVal oElement As Element, Point As Point3d, ByVal View As View)
    Debug.Print "Accept element type " & CStr(oElement.Type)
    Dim area    As Double
    area = 0#
    If oElement.IsLineElement Then
        '   Convert line string to shape to measure area
        Dim vertices()  As Point3d
        vertices = oElement.AsVertexList.GetVertices
        Dim oShape      As ShapeElement
        Set oShape = CreateShapeElement1(oElement, vertices)
        ShowArea oShape.AsClosedElement.area, oElement.Type
    Else
        ShowArea oElement.AsClosedElement.area, oElement.Type
    End If
End Sub
' ---------------------------------------------------------------------
Sub ShowArea(area As Double, elemType As MsdElementType)
    Dim strLastTerseMessage     As String
    Dim strLastVerboseMessage   As String
    Dim strElemType             As String
    strLastTerseMessage = "Area " & Format(area, "#,###.00") & " sq " & ActiveModelReference.MasterUnit.Label
    Select Case elemType
    Case msdElementTypeEllipse
        strElemType = "ellipse"
    Case msdElementTypeShape
        strElemType = "shape"
    Case msdElementTypeComplexShape
        strElemType = "complex shape"
    Case msdElementTypeLineString
        strElemType = "closed line string"
    End Select
    strLastVerboseMessage = "Area of " & strElemType & "=" & Format(area, "#,###.0000") & " sq " & ActiveModelReference.MasterUnit.Label
    ShowError strLastTerseMessage
    ShowMessage strLastTerseMessage, strLastVerboseMessage
End Sub
' ---------------------------------------------------------------------
Private Sub ILocateCommandEvents_Cleanup()

End Sub
' ---------------------------------------------------------------------
Private Sub ILocateCommandEvents_Dynamics(Point As Point3d, ByVal View As View, ByVal DrawMode As MsdDrawingMode)

End Sub
' ---------------------------------------------------------------------
Private Sub ILocateCommandEvents_LocateFailed()
    ShowError "Closed element not found"
    ShowMessage vbNullString
End Sub
' ---------------------------------------------------------------------
Private Sub ILocateCommandEvents_LocateFilter(ByVal oElement As Element, Point As Point3d, Accepted As Boolean)
    Accepted = False

    If oElement.IsShapeElement Then
        Accepted = True
    ElseIf oElement.IsEllipseElement Then
        Accepted = True
    ElseIf oElement.IsComplexShapeElement Then
        Accepted = True
    ElseIf oElement.IsLineElement Then
        With oElement.AsVertexList
            Dim nVertices   As Integer
            nVertices = .VerticesCount
            If (2 < nVertices) Then
                Dim oVertexList() As Point3d
                oVertexList = .GetVertices
                Accepted = Point3dEqual(oVertexList(0), oVertexList(nVertices - 1))
            End If
        End With
    End If
End Sub
' ---------------------------------------------------------------------
Private Sub ILocateCommandEvents_LocateReset()

End Sub
' ---------------------------------------------------------------------
Private Sub ILocateCommandEvents_Start()
   Dim oLocateCriteria As LocateCriteria

    '  Since this command does not modify the original element,
    '  set the locate criteria to allow  read-only elements.
    Set oLocateCriteria = CommandState.CreateLocateCriteria(False)
    CommandState.SetLocateCriteria oLocateCriteria
    ShowCommand "Measure Area"
    ShowPrompt "Select a closed element"
    ShowMessage vbNullString
    ShowError vbNullString
End Sub
' ---------------------------------------------------------------------

When you run the above code, the area of suitable element is displayed in MicroStation's status bar and also in the message center …

You can copy and paste the above code into a new VBA module, or drop the MeasureArea.mvba module into a suitable location, such as X:\Program Files\Bentley\Workspace\Projects\Untitled\vba, on your computer.