Each & every graphic element in a MicroStation DGN file has a unique 64-bit ID. Element IDs are used extensively by MicroStation internally, but normally they are of little concern to users. Nonetheless, sometimes you may need to find an element given its ID.
Q How do I find an element given its ID?
A Each and every graphic element in a MicroStation DGN file has a unique ID. The ID is a 64-bit integer number. You can see an element's ID using the element information tool …
The ID is listed at the bottom of the Element Information dialog under the Raw Data category …
MicroStation CONNECT is 64-bit and provides direct support for 64-bit integer numbers such as an Element ID.
VBA for MicroStation V8i does not provide intrinsic support for 64-bit numbers.
MicroStation VBA V8i substitutes the DLong
user-defined-type (UDT).
A DLong
packs two 32-bit integers into a UDT.
MicroStation VBA provides a number of methods that operate on DLong
.
In this example, we show how to enable a user to keyin a command and pass an element ID to the VBA code that locates an element.
Option Explicit Option Base 0' --------------------------------------------------------------------- ' Main entry point. Command-line syntax: ' vba run [ElementLocator]modMain.Main <element id> ' Substitute a valid MicroStation graphic element ID for <element id> ' ---------------------------------------------------------------------
Public Sub Main() Dim id As DLong id = DLongFromString(KeyinArguments) Dim oTarget As Element On Error GoTo err_ElementNotFound' Next line throws an error if the ID is not valid
Set oTarget = ActiveModelReference.GetElementByID(id) ZoomToElement oTarget, 1 Exit Sub err_ElementNotFound: MsgBox "Element having ID " & DLongToString(id) & " not found", vbOKOnly Or vbInformation, "Invalid Element ID" End Sub' --------------------------------------------------------------------- ' ZoomToElement ' ---------------------------------------------------------------------
Function ZoomToElement(ByVal oTarget As Element, ByVal nView As Integer) As Boolean ZoomToElement = False If (oTarget.IsGraphical) Then Const Zoom As Double = 4 Dim range As Range3d range = oTarget.range Dim oView As View Set oView = ActiveDesignFile.Views.Item(nView) Dim extent As Point3d extent = Point3dScale(Point3dSubtract(range.High, range.Low), Zoom) oView.origin = Point3dSubtract(range.Low, Point3dScale(extent, 0.5)) oView.Extents = extent oView.Redraw oTarget.IsHighlighted = True Else MsgBox "Element having ID " & DLongToString(oTarget.id) & " is not a graphical element", vbOKOnly Or vbInformation, "Invalid Element" End If Exit Function err_ZoomToElement: ReportError strMODULE_NAME, "ZoomToElement" End Function
When you run the above code, providing you pass a valid element ID, MicroStation adjusts view one to display the element.
You can
download the ElementLocator.mvba project.
Unpack the ZIP archive and extract ElementLocator.mvba
to a well-known
location such as
\Bentley\Workspace\Standards\vba
.
Run the macro using the keyin
vba run [ElementLocator]modMain.Main <element id>
,
substituting a valid element ID for <element id>
.