Questions similar to this appear on the Bentley Discussion Groups. These appeared in the VBA discussion group.
Q Measuring Parallel Lines
A
The simplest way, posted by Dean BB on the MicroStation VBA discussion group, is
Use the measure minimum distance command and get the measurement from CommandState.MeasureResult1.
Here's another way to find the distance between parallel lines, which is a programmer's approach to the problem. The outline of this solution is …
The code for this project is available in VBA project MeasureDistance.
Unpack the ZIP archive and copy MeasureDistance.mvba to a memorable location, such as Workspace\projects\untitled\mvba.
The projects contains two modules: modMain and clsLineLocator.
modMain exists to provide the Main entry point.
The MicroStation keyin to run this project is …
vba run [MeasureDistance]modMain.main
The Main subroutine creates an instance of clsLineLocator and starts MicroStation's locate logic …
Public Sub Main()
CommandState.StartLocate New clsLineLocator
End Sub
clsLineLocator is a class module that Implements ILocateCommandEvents.
It prompts you to locate two lines.
Each time you locate a line, it stores a reference to that line.
When you've located two lines, it starts its computations. The first computation is to find whether the two lines are parallel …
' ---------------------------------------------------------------------
' LinesParallel
' ---------------------------------------------------------------------
Public Function LinesParallel(ByVal oLine1 As LineElement, ByVal oLine2 As LineElement) As Boolean
LinesParallel = False
Dim v1 As Point3d
Dim v2 As Point3d
v1 = Point3dSubtract(oLine1.EndPoint, oLine1.StartPoint)
v2 = Point3dSubtract(oLine2.EndPoint, oLine2.StartPoint)
LinesParallel = Point3dAreVectorsParallel(v1, v2)
End Function
The second computation is to calculate the distance between the two lines …
' ---------------------------------------------------------------------
' DistanceBetweenLines
' Return the perpendicular distance between two lines, preferably parallel
' ---------------------------------------------------------------------
Public Function DistanceBetweenLines(ByVal oLine1 As LineElement, ByVal oLine2 As LineElement) As Double
DistanceBetweenLines = 0#
Dim v1 As Point3d
Dim v2 As Point3d
Dim pntProjected As Point3d
pntProjected = oLine1.ProjectPointOnPerpendicular(oLine2.StartPoint, Matrix3dIdentity)
DistanceBetweenLines = Point3dDistance(pntProjected, oLine2.StartPoint)
End Function
Q Measuring MultiLines
MultiLineElement? A
MicroStation multilines let you draw complex linear features as if you are drawing a single line or line-string.
Unfortunately, the VBA object MultiLineElement does not expose many of the properties that one might
reasonably expect of a linear element.
For example, there is no Length property, so how would you find the length of a MultiLineElement using VBA?
However, MultiLineElement does include the Drop method.
Drop creates an enumeration of the components of a multiline.
Since each component of a multiline must be the same length, you can drop the multiline and measure the length of the first component.
Here's a function that implements that idea …
Sub TestMultiLine ()
' This is for testing: it picks up the multiline element currently in a select set
Dim oEnumerator As ElementEnumerator
Set oEnumerator = ActiveModelReference.GetSelectedElements
While oEnumerator.MoveNext
Set oElement = oEnumerator.Current
Dim length As Double
length = MeasureMultiLine (oElement.AsMultiLineElement)
Debug.Print "Length=" & CStr(oLine.Length)
Wend
End Sub
' ---------------------------------------------------------------------------------
Function MeasureMultiLine(ByVal oMultiLine As MultiLineElement) As Double
MeasureMultiLine = 0#
Dim oComponents As ElementEnumerator
Set oComponents = oMultiLine.Drop
Dim oLine As LineElement
If oComponents.MoveNext Then
Set oLine = oComponents.Current
MeasureMultiLine = oLine.Length
End If
End Function
The code above works fine, and is compatible with MicroStation V8 2004 Edition. MicroStation XM provides a new way to interrogate elements using a Property Handler. This approach was suggested by Harry Stegeman, a regular contributor to the Bentley VBA Discussion Group.
Sub ShowMultilinePropertyStrings(oElement As Element)
If Not oElement.Type = msdElementTypeMultiLine Then
Debug.Print "Expected a multiline"
Exit Sub
End If
Dim oPropertyHandler As PropertyHandler
Set oPropertyHandler = CreatePropertyHandler(oElement)
Dim arraySpec As String
arraySpec = "Segments[" & (NumSegments(oPropertyHandler) - 1) & "]"
ShowDisplayString oPropertyHandler, arraySpec & ".Start"
ShowDisplayString oPropertyHandler, arraySpec & ".End"
ShowDisplayString oPropertyHandler, arraySpec & ".Length"
ShowDisplayString oPropertyHandler, arraySpec & ".Direction"
ShowDisplayString oPropertyHandler, arraySpec & ".ElevationAngle"
ShowDisplayString oPropertyHandler, arraySpec & ".DeltaX"
ShowDisplayString oPropertyHandler, arraySpec & ".DeltaY"
End Sub
' ---------------------------------------------------------------------------------
Private Sub ShowDisplayString(oPropertyHandler As PropertyHandler, accessString As String)
On Error GoTo HandleError
If Not oPropertyHandler.SelectByAccessString(accessString) Then
Debug.Print "Property '" & accessString & "' not found!"
Else
Debug.Print oPropertyHandler.GetDisplayString
End If
Exit Sub
HandleError:
Debug.Print Err.Description
End Sub