This article is written for an audience of Visual Basic for Applications (VBA) programmers. Specifically, VBA programmers wanting to write code for Bentley Systems MicroStation® VBA.
Questions similar to this appear on the MicroStation Programming Forum.
Sometimes we want to place infinitesimal points in a MicroStation DGN model. A point can be a point cell or a zero-length line. A zero-length line is represented by a DGN line element having identical start and end points.
Scott Belyea, an Estimator at Carroll Construction Supply, commented: I use a file converter to convert PDF to DWG, then edit with MicroStation. The hatches convert to thousands of individual linestrings, that I want to delete. I'd like to be able to search for linestrings that are .2 units in length, then delete them.
LA Solutions reacted fast to my request for some modifications to the Zero-Length Lines VBA tool. The tool will save a lot of processing time!
Q How can I select zero-length line elements?
A MicroStation stores elements in models (VBA ModelReference
).
A model contains zero or more elements.
We can scan a model for line elements and reject those that fail to pass our length limits.
If we're looking for zero-length lines, then the length should be exactly zero.
Q How can I select line elements that are almost, but not quite, zero-length?
A A MicroStation user posted a conundrum on the MicroStation Forum. In this unusual case his DGN model contained what appeared to be, at first sight, zero-length lines that he could not delete. On closer examination we found that the 'zero-length' lines had a tiny length value — something like one ten-billionth of a metre.
For most people, in most situations, one ten-billionth of a metre might count as zero for all practical purposes. So how do you delete all those 'zero-length' lines?
A line is represented by a LineElement
object.
One of its properties is Length
(in the model's master units).
We need to examine each LineElement
in a model and
determine whether its length falls below a given limit.
How do we examine each LineElement
?
The scan engine is one way to examine each element in a DGN model.
It is implemented in VBA by the ModelReference.Scan
method.
You can specify filtering criteria through the ScanCriteria
object.
In this case, we want the scan engine to find LineElement
s for us,
which we then compare to our limit …
Public Function ScanLinesByLength( _
ByVal MaxLength As Double) As Long
ScanLinesByLength = 0
const Exact As Boolean = True
Dim nLines As Long
nLines = 0
ActiveModelReference.UnselectAllElements
Dim oCriteria As New ElementScanCriteria
oCriteria.ExcludeNonGraphical
oCriteria.ExcludeAllTypes
oCriteria.IncludeType msdElementTypeLine
Dim oLines As ElementEnumerator
Set oLines = ActiveModelReference.Scan(oCriteria)
While (oLines.MoveNext)
Dim oLine As LineElement
Set oLine = oLines.Current.AsLineElement
' Function IsZeroLengthLine implements our test for a zero-length line
If IsZeroLengthLine (oLine, Not Exact, MaxLength) Then
nLines = 1 + nLines
End If
Wend
ScanLinesByLength = nLines
End Function
How do you tell the scanner what values to assume for MaxLength
?
In this example, the user supplies the value through a VBA UserForm.
The screenshot above shows the UserForm and the controls that display
the user settings.
The Test button starts things off.
It calls the ScanLinesByLength
function, passing the maximum length
values from the form.
If the Exact option is chosen, then the maximum length is zero.
The ZeroLengthLines VBA project is freeware — available free of charge. You can download it here. It includes the working VBA code, including the UserForm above. The project is not protected, so you can dissect it and modify it to suit your particular purpose.
We want to test either for exact zero-length lines or lines that are almost zero-length.
Function IsZeroLengthLine
implements that requirement.
We pass it a LineElement
and a boolean flag exact
.
If exact
is true then the line must have exactly zero length.
If exact
is false then the line must be shorter than the passed value epsilon
.
' ---------------------------------------------------------------------
' IsZeroLengthLine
' Test whether a line is exactly zero-length or, if a tolerance is specified,
' whether line's length is less than that value
' Returns: Boolean true if we consider this line to be zero-length
' ---------------------------------------------------------------------
Public Function IsZeroLengthLine( _
ByVal oLine As LineElement, _
ByVal exact As Boolean, _
ByVal epsilon As Double) As Boolean
IsZeroLengthLine = False
If exact Then
IsZeroLengthLine = (0# = oLine.length)
Else
IsZeroLengthLine = (oLine.length <= epsilon)
End If
End Function
Another MicroStation user wanted to add found lines to a Selection Set. We added that option in March 2020. To further the tool's versatility, we also let you find zero-length lines by level, if desired.
You can download the freeware Zero Length Lines MVBA project.
The project includes the MVBA project ZeroLengthLines.mvba
and an example DGN file with a few lines used to test the project.
C:\Program Files\Bentley\Workspace\Standards\vba
vba run [ZeroLengthLines]modMain.Main
The Zero Length Lines MVBA project is freeware: we ask for no license fee and grant you the right to use it for whatever purpose. As freeware this is unsupported software: use at your own risk.