This article is about MicroStation® Visual Basic for Applications (VBA). It's written for developers using Bentley Systems MicroStation. Questions similar to this appear on the Be Communities Forums. This problem appeared in the MicroStation Programming Forum.

Introduction

MicroStation lets you create graphical elements of many types. Usually elements are not identical, meaning that they have different geometry, different symbology, different properties (e.g. level) or some other distinctive characteristic.

Occasionally we create identical elements, usually inadvertently. It's too easy, for example, to pick MicroStation's Copy command when we intended to pick the Move command. The result is two similar elements, and if you happend to provide an extra button click to place the copy congruently with its prototype, the two will be identical.

Identical Elements

Q   How do I compare two elements using VBA?

A   VBA doesn't have a built-in function to compare two elements. However, we can borrow a function from the MicroStationAPI …

  1. mdlElmdscr_areTwoIdentical
  2. mdlElmdscr_areIdenticalToTolerance

mdlElmdscr_areIdenticalToTolerance works as documented. An example is shown below.

Do Not Use mdlElmdscr_areTwoIdentical

mdlElmdscr_areTwoIdentical is a relic from MicroStation/J. Internally, it uses the C function memcmp to compare the two elements. memcmp performs a bitwise comparison. Unfortunately, MicroStation V8 assigns each and every element in a DGN file a unique ID. Two elements may be geometrically congruent, but will have differing Element IDs. Consequently, mdlElmdscr_areTwoIdentical will always fail.

How to Use mdlElmdscr_areIdenticalToTolerance

The first thing to do when you want to use an MDL function in VBA is to declare it. Bentley Systems provide function declarations in the MDL documentation installed with the MicroStation V8 SDK. Unfortunately, the MicroStationAPI documentation installed with the MicroStation CONNECT SDK lacks those declarations.

Here's the VBA function declaration of mdlElmdscr_areIdenticalToTolerance for MicroStation CONNECT …

Declare PtrSafe Function mdlElmdscr_areIdenticalToTolerance Lib "stdmdlbltin.dll" ( _
        ByVal edP1 As LongPtr, _
        ByVal edP2 As LongPtr, _
        ByVal comparisonFlags As Long, _
        ByVal distanceTolerance As Double, _
        ByVal directionTolerance As Double) As Long

Comparison Flags

That function's third argument is comparisonFlags. The permitted values for comparisonFlags are defined in a way that is incompatible with VBA. Each flag is a power-of-two (i.e. 2^N, where the ^ symbol means 'to the power of'), which is not obvious from the enum below. Flags can be combined with a logical Or.

Here's their VBA translation …

' ---------------------------------------------------------------------
'   Flags for MDL function mdlElmdscr_areIdenticalToTolerance
' ---------------------------------------------------------------------
Public Enum COMPAREOPT
    COMPAREOPT_IGNORE_MODEL_DIFFS = 1
    COMPAREOPT_IGNORE_SYMBOLOGY = 2
    COMPAREOPT_IGNORE_IDS = 4
    COMPAREOPT_IGNORE_LINKAGES = 8
    COMPAREOPT_IGNORE_MODIFIED = 16
    COMPAREOPT_IGNORE_DGNSTORE = 32
    COMPAREOPT_IGNORE_ATTRIBUTE_VALUE = 64
    COMPAREOPT_IGNORE_SINGLE_EDF_VALUES = 128
    COMPAREOPT_IGNORE_CELL_RANGEDIAG = 256
    COMPAREOPT_IGNORE_DGNDWGTEXTDIFFERENCES = 512
    COMPAREOPT_IGNORE_2D_RANGEZ = 1024
    COMPAREOPT_IGNORE_MULTISPANNINGSIBLINGBOUNDARIES = 2048
    COMPAREOPT_IGNORE_UNORDEREDSIBLINGORDER = 4096
    COMPAREOPT_IGNORE_LINESTYLEDIRECTION = 8192
    COMPAREOPT_IGNORE_LEVEL = 16384
    COMPAREOPT_IGNORE_2D_ZRANGE = 32768
    COMPAREOPT_IGNORE_CELL_TRANSFORM = 65536
    COMPAREOPT_IGNORE_XATTRIBUTES = 131072
    COMPAREOPT_TEST_FACEMATERIALS = 262144
    COMPAREOPT_IGNORE_INVISIBLE_ELEMENTS = 524288
    COMPAREOPT_IGNORE_ELEMENT_CLASS = 1048576
    COMPAREOPT_IGNORE_CELL_HEADER_ELM = 2097152
End Enum

Here's a convenient combination of those flags …

Const COMPAREOPT_STANDARD_IGNORES As Long = COMPAREOPT_IGNORE_MODEL_DIFFS _
                                            Or _
                                            COMPAREOPT_IGNORE_SYMBOLOGY _
                                            Or _
                                            COMPAREOPT_IGNORE_IDS _
                                            Or _
                                            COMPAREOPT_IGNORE_LINKAGES _
                                            Or _
                                            COMPAREOPT_IGNORE_MODIFIED _
                                            Or _
                                            COMPAREOPT_IGNORE_XATTRIBUTES

If you want your own combination of flags, do something like this. COMPAREOPT_MY_FLAGS instructs MicroStation to ignore element symbology, level and Element ID …

Const COMPAREOPT_MY_FLAGS As Long = COMPAREOPT_IGNORE_SYMBOLOGY _
                                            Or _
                                            COMPAREOPT_IGNORE_IDS _
                                            Or _
                                            COMPAREOPT_IGNORE_LEVEL

VBA Wrapper

Now we can write a VBA wrapper around the MDL function …

' ---------------------------------------------------------------------
'   AreTwoElementsIdenticalTolerance
'   Wrapper around MDL function mdlElmdscr_areIdenticalToTolerance
'   Returns:    Boolean True if elements are identical
' ---------------------------------------------------------------------
Public Function AreTwoElementsIdenticalTolerance(ByVal oElement1 As Element, ByVal oElement2 As Element) As Boolean
    Const LinearTolerance                   As Double = 0.1
    Const RadialTolerance                   As Double = 0.1
    Const Flags                             As Long = COMPAREOPT_STANDARD_IGNORES
    'Const Flags                             As Long = COMPAREOPT_MY_FLAGS
    AreTwoElementsIdenticalTolerance = 0 <> mdlElmdscr_areIdenticalToTolerance( _
        oElement1.MdlElementDescrP(), oElement2.MdlElementDescrP(), Flags, LinearTolerance, RadialTolerance)
End Function

I've made some simplifications to make the wrapper easier to use. You may want to experiment with the comparision flags and the linear and radial tolerances.

Test Procedure

Here's a subroutine to test the VBA wrapper. Before you use this, create an element and copy it. Ensure that the copy is exactly coincident with the original …

Sub TestAreTwoElementsIdenticalTolerance()
    Dim msg                                 As String
    '   Select two identical elements before proceeding
    Dim oEnumerator                         As ElementEnumerator
    Set oEnumerator = ActiveModelReference.GetSelectedElements
    Dim oSelection()                        As Element
    oSelection = oEnumerator.BuildArrayFromContents()
    '	Compute size of element array
    Dim nSelected                           As Long
    nSelected = UBound(oSelection) - LBound(oSelection) + 1
    If 2 = nSelected Then
        Dim identical                       As Boolean
        identical = AreTwoElementsIdenticalTolerance(oSelection(0), oSelection(1))
        If identical Then
            msg = "Elements " & DLongToString(oSelection(0).ID) & _
                " and " & DLongToString(oSelection(1).ID) & " are identical"
            ShowMessage msg, msg, msdMessageCenterPriorityInfo, True
        Else
            msg = "Elements " & DLongToString(oSelection(0).ID) & _
                " and " & DLongToString(oSelection(1).ID) & " are not identical"
            ShowMessage msg, msg, msdMessageCenterPriorityWarning, True
        End If
    Else
        msg = "Select exactly two elements"
        ShowMessage msg, msg, msdMessageCenterPriorityWarning, True
    End If
End Sub

Back to the VBA article index.