Q MicroStation DGN files contain one or more models that store model geometry and other information. When you are creating a model, you often place a cell to copy frequently-used geometry into the drawing. Cells are stored in a cell library file. A DGN file always contains at least one model; a cell library usually contains many models, each of which is a cell.
A
Similar questions are posted now and then on the
Bentley Discussion Groups.
A cell library is just a MicroStation DGN file having a .cel
extension. A cell is a model, and a model is a cell.
Iterating the cells in a cell library is identical to iterating the models in a design file.
Remember the mantra: A model is a cell. A cell is a model. Raise your understanding to a higher plane: mumble this mantra every morning!
There is sample code for VBA developers and MDL wonks.
Here's a simple VBA example that illustrates how to obtain information about models (in a DGN file) or cells (in a cell library).
Since a cell library is a DGN file, this code works for either. Copy this code into a regular VBA module,
then run it within the IDE, or from a MicroStation keyin vba run modMain.Main
…
Option Explicit Option Base 0' ---------------------------------------------------------------------
Sub Main() Dim nModels As Long nModels = EnumerateModels(ActiveDesignFile) MsgBox "Found " & CStr(nModels) & " models ", vbInformation Or vbOKOnly, "Enumerated Models" End Sub' ---------------------------------------------------------------------
Function EnumerateModels(dgn As DesignFile) As Integer Dim index As Integer Dim strName As String For index = dgn.Models.count To 1 Step -1 Dim oModel As ModelReference Set oModel = dgn.Models(index) Debug.Print "Model [" & CStr(index) & "] '" & oModel.name & "'" Next EnumerateModels = dgn.Models.count End Function
When you run the above code, the name of each model or cell is displayed in the IDE's immediate window. You will see the following information dialog that tells you the number of models found …
Here's an MDL example of cell iteration, courtesy of Mark Anderson at Bentley Systems …
void cellIterator (void)
{
DgnIndexIteratorP pDgnIndexIterator = NULL;
DgnFileObjP pLibObj = NULL;
DgnIndexItemP pDgnIndexItem = NULL;
// Get the current attached library
int iStatus = mdlCell_getLibraryObject (&pLibObj, tcb->celfilenm, TRUE);
pDgnIndexIterator = mdlModelIterator_create (pLibObj);
mdlModelIterator_setAcceptCellsOnly (pDgnIndexIterator, TRUE);
while (pDgnIndexItem = mdlModelIterator_getNext (pDgnIndexIterator))
{
mdlModelItem_getName (pDgnIndexItem, wCellName, MAX_CELLNAME_LENGTH);
mdlModelItem_getDescription (pDgnIndexItem, wCellDescription, MAX_CELLDSCR_LENGTH);
mdlModelItem_getData (pDgnIndexItem, &cellType, &isThreeD, &isLocked, &isHidden, &lastSaved);
}
mdlModelIterator_free (pDgnIndexIterator);
}
Q How do I find the range of a DGN model?
A
Similar questions are posted now and then on the
MicroStation Programming Forum.
MicroStation models contain graphic elements (VBA Element
).
Each graphic element has a range, or extent.
In VBA the extent is a Range
user defined type (UDT), with High
and Low
components.
The extent of a DGN model is the union of all element extents, and is available as the ModelReference.Range
property.
The following VBA procedure displays the active model's range …
' ---------------------------------------------------------------------
' Display the max and min values of the range of all elements in a model
' ---------------------------------------------------------------------
Public Sub GetModelRange()
Dim oModel As ModelReference
Set oModel = ActiveModelReference
Dim range As Range3d
Const IncludeAttachments As Boolean = True
Const IgnoreAttachments As Boolean = False
range = oModel.range(IgnoreAttachments)
Dim max As String
Dim min As String
If (oModel.Is3D) Then
max = "Model " & oModel.name & " range maximum: " & CStr(range.High.X) & "," & CStr(range.High.Y) & "," & CStr(range.High.Z)
min = "Model " & oModel.name & " range minimum: " & CStr(range.Low.X) & "," & CStr(range.Low.Y) & "," & CStr(range.Low.Z)
Else
max = "Model " & oModel.name & " range maximum: " & CStr(range.High.X) & "," & CStr(range.High.Y)
min = "Model " & oModel.name & " range minimum: " & CStr(range.Low.X) & "," & CStr(range.Low.Y)
End If
ShowMessage max, max, msdMessageCenterPriorityInfo
ShowMessage min, min, msdMessageCenterPriorityInfo
End Sub
If you want to visualise the range found with the above code then you need to create a rectangle using a ShapeElement
.
A ShapeElement
requires an array of Point3d
vertices, so we need to convert the
Range3d
…
' --------------------------------------------------------------------- ' Display range of all elements in a model as a rectangle ' ---------------------------------------------------------------------
Public Sub GetModelRangeAsRectangle() Dim oModel As ModelReference Set oModel = ActiveModelReference Dim range As Range3d Const IncludeAttachments As Boolean = False range = oModel.range(IncludeAttachments) Dim vertices(0 To 4) As Point3d Dim i As Integer' First and last vertices of a shape must be coincident
For i = 0 To 4 vertices(i) = range.Low Next i vertices(1).X = range.High.X vertices(2).X = range.High.X vertices(2).Y = range.High.Y vertices(3).Y = range.High.Y Dim oRectangle As ShapeElement Set oRectangle = CreateShapeElement (Nothing, vertices) ActiveModelReference.AddElement oRectangle oRectangle.Redraw End Sub