Questions similar to this appear on the Bentley Discussion Groups. These problems appeared in the VBA discussion group.

Q If I have a text element containing a string that is <<1>A<2>B<22>> (datafield, then text, datafield and text, etc) I can cycle through all the datafields using TextElement.DataEntryRegion(index) but how do I get to the text?

A A TextElement  may contain not only text, but also enter data fields. Enter data fields (also known as enter data regions) are placeholders in a text element. It's possible to update enter data fields independently of other text in a text element.

The question posed asks how to extract both the text of each enter data field and the intervening plain text. This task is made reasonably easy by MicroStation VBA's provision of several methods of the TextElement object …

TextElement.DataEntryRegion(index) returns a DataEntryRegion user-defined type that tells us the StartPosition and Length of the enter data field at a given index. Using this information, our code can walk through the enter data fields and extract both the enter data field content and the non-enter data field plain old text that lies between the enter data fields.

Here's an example. Copy and paste the code below into a new VBA module. Run the module from the Main subroutine, preferably when you have open a DGN model that contains some text having enter data fields …

Option Explicit

' ---------------------------------------------------------------------
'   Example to analyse the content of a text element that contains
'   enter data fields
' ---------------------------------------------------------------------
'   Notice:
'   Source code provided by LA Solutions Ltd as-is without warranty of
'   fitness for purpose.  You may use this code for whatever purpose
'   private or commercial
'   www.la-solutions.co.uk
'   End of notice
' ---------------------------------------------------------------------
'
Public Sub Main()
    '   In this example we obtain a TextElement from a DGN model that
    '   contains various TextElements some with, and some without, enter
    '   data fields
    Dim nObjects                            As Long
    nObjects = ScanEnterDataText(ActiveModelReference)
    Debug.Print "Found " & CStr(nObjects) & " text elements with enter data fields"
End Sub
' ---------------------------------------------------------------------
'   Function ScanEnterDataText
'   Scan a model for text elements.  We're interested only in those
'   text elements that have enter data regions.
'   Returns:    Long count of text elements having enter data regions
' ---------------------------------------------------------------------
Function ScanEnterDataText(ByVal oModel As ModelReference) As Long
    Dim nEnterDataTextElms                  As Long
    nEnterDataTextElms = 0
    ScanEnterDataText = 0
    Dim oScanCriteria                       As New ElementScanCriteria
    oScanCriteria.ExcludeAllTypes
    oScanCriteria.IncludeType msdElementTypeText
    Dim oTextElements                       As ElementEnumerator
    Set oTextElements = oModel.Scan(oScanCriteria)
    Do While oTextElements.MoveNext
        Dim oTextElement                    As TextElement
        Set oTextElement = oTextElements.Current.AsTextElement
        Dim nRegions                        As Integer
        nRegions = oTextElement.DataEntryRegionsCount
        If (0 < nRegions) Then
            If (AnalyseDataEntryRegions(oTextElement, nRegions)) Then
                nEnterDataTextElms = 1 + nEnterDataTextElms
            End If
        End If
    Loop
    ScanEnterDataText = nEnterDataTextElms
End Function
' ---------------------------------------------------------------------
'   AnalyseDataEntryRegions
'   Extract information from a TextElement having one or more
'   data entry fields
' ---------------------------------------------------------------------
Function AnalyseDataEntryRegions(ByVal oText As TextElement, ByVal nRegions As Long) As Boolean
    AnalyseDataEntryRegions = False
    Debug.Print "Found text '" & oText.Text & "' with " & CStr(nRegions); " enter data fields"
    Dim region                      As Long
    Dim index                       As Long
    Dim start                       As Long
    Dim length                      As Long
    Dim data                        As DataEntryRegion
    Dim s                           As String
    s = oText.Text
    Dim strings()                   As String
    ReDim strings(1 To 1 + nRegions * 2)
    start = 1
    index = 1
    For region = 1 To nRegions
        data = oText.DataEntryRegion(region)
        Debug.Print "Region [" & CStr(region) & "] start=" & CStr(data.StartPosition) & " length=" & CStr(data.length)
        '   Text before enter data field
        length = data.StartPosition - start
        If (0 = length) Then
            strings(index + 0) = "Text: "
        Else
            strings(index + 0) = "Text: " & Mid(s, start, length)
        End If
        '   Enter data field content
        strings(index + 1) = "Enter Data: " & oText.DataEntryRegionText(region)
        index = index + 2
        start = data.StartPosition + data.length
        AnalyseDataEntryRegions = True
    Next region
    '   Any text after final data entry field
    strings(index) = "Text: " & Mid(s, start)
    For region = LBound(strings) To UBound(strings)
        Debug.Print "Strings [" & CStr(region) & "] '" & strings(region) & "'"
    Next
End Function
' ---------------------------------------------------------------------