Questions similar to this appear on the MicroStation Programming Forum, posed by MDL and VBA developers. These appeared in the VBA discussion group.
Q Grouped Holes are, in MicroStation terminology, complex elements. In other words, they are planar shapes-with-holes.
A A Grouped Hole is an anonymous cell. The cell contains an outer shape that encloses one or more inner shapes. The outer shape is marked as a solid, and the inner shapes are marked as holes. All the shapes are coplanar (i.e. they are flat, and have the same Z coordinate).
The terminology solid and hole is confusing. We're all working in 3D these days (you are working in 3D, aren't you?) and the terms solid and hole have a particular meaning in our real world of three dimensions. However, Grouped Holes were born in a previous era, when the world was flat. In a Grouped Hole and other 2D elements, solid and hole indicate that a shape should be considered as filled or hollow.
VBA has no method that determines whether an element is a Grouped Hole. However, MDL includes such a function, and it's easy to use it in your VBA code.
First, you must add a function declaration at the beginning of your VBA module …
' MDL function declarations
Declare PtrSafe Function mdlElmdscr_isGroupedHole Lib "stdmdlbltin.dll" (ByVal groupEdP As LongPtr) As Long
Here's the VBA method that wraps the MDL function …
' ---------------------------------------------------------------------
' IsGroupedHole determines whether a given element is a grouped hole,
' which is an anonymous cell that contains one solid element that
' encloses one or more hole elements
' ---------------------------------------------------------------------
Public Function IsGroupedHole(ByVal oElement As Element) As Boolean
IsGroupedHole = 0 <> mdlElmdscr_isGroupedHole(oElement.MdlElementDescrP)
End Function
Here's an example class that implements ILocateCommandEvents
to create a Grouped Hole locator.
Create a new class module named clsGroupedHoleLocator
in your VBA project, then copy and paste this code into the new module …
' ---------------------------------------------------------------------
Option Explicit' ---------------------------------------------------------------------
Private Const sMODULE_NAME As String = "clsGroupedHoleLocator"' ---------------------------------------------------------------------
Implements ILocateCommandEvents' ---------------------------------------------------------------------
Private m_dblArea As Double' ---------------------------------------------------------------------
Public Property Get Area() As Double Area = m_dblArea End Property' ---------------------------------------------------------------------
Private Sub ILocateCommandEvents_Accept(ByVal oElement As Element, point As Point3d, ByVal view As view) m_dblArea = ComputeGroupedHoleArea(oElement.AsCellElement) Dim msg As String msg = "Grouped hole ID " & DLongToString(oElement.ID) & " area=" & CStr(m_dblArea) ShowMessage msg, msg, msdMessageCenterPriorityInfo End Sub' ---------------------------------------------------------------------
Private Sub ILocateCommandEvents_Cleanup() End Sub' ---------------------------------------------------------------------
Private Sub ILocateCommandEvents_Dynamics(point As Point3d, ByVal view As view, ByVal drawMode As MsdDrawingMode) End Sub' ---------------------------------------------------------------------
Private Sub ILocateCommandEvents_LocateFailed() End Sub' ---------------------------------------------------------------------
Private Sub ILocateCommandEvents_LocateFilter(ByVal oElement As Element, point As Point3d, accepted As Boolean) accepted = IsGroupedHole(oElement) End Sub' ---------------------------------------------------------------------
Private Sub ILocateCommandEvents_LocateReset() CommandState.StartLocate Me End Sub' ---------------------------------------------------------------------
Private Sub ILocateCommandEvents_Start() Dim oLocateCriteria As LocateCriteria CommandState.CommandName = "Locate Grouped Hole" ' V8i and later ShowCommand "Locate Grouped Hole" ShowPrompt "Select an element"' Set up the locate criteria to allow locked elements and ' reference files. Specifying False as the argument to ' CreateLocateCriteria says that this program will not modify ' the elements and therefore can accept read-only elements ' such as locked elements and elements from reference files.
Set oLocateCriteria = CommandState.CreateLocateCriteria(False) CommandState.SetLocateCriteria oLocateCriteria End Sub
You can start this example from another VBA module like this …
Sub FindGroupedHole() CommandState.StartLocate New clsGroupedHoleLocator End Sub
Each element must be a planar closed shape. A shape may be simple (e.g. a rectangle or ellipse) or complex. The outer element has the solid property. Each inner element has the hole property.
You need to create an array of suitable elements.
Your array must have a closed solid element first: it's the shape that encloses the remaining shapes.
The second and subsequent shapes should be closed hole elements.
Once you've built the array, call CreateCellElement1
to create a cell element.
A key task in creating the shapes for your grouped hole is the assignment of solid and hole properties to each shape.
VBA provides the IsHole
property as part of the ClosedShape
interface.
Unfortunately, it provides no way to set that property.
We can work around that omission by calling MDL code to set the shape's solid |hole status.
To use an MDL function, we need to declare it in a VBA module before any procedures are defined.
We have wrapped the MDL code inside a VBA procedure SetSolidHole
to hide the gory details …
' ---------------------------------------------------------------------
' MDL function declaration
' ---------------------------------------------------------------------
Declare PtrSafe Sub mdlElmdscr_setProperties Lib "stdmdlbltin.dll" ( _
ByRef edP As LongPtr, _
ByRef level As Long, _
ByRef ggNum As Long, _
ByRef elementClass As Long, _
ByRef locked As Long, _
ByRef newElm As Long, _
ByRef modified As Long, _
ByRef viewIndepend As Long, _
ByRef solidHole As Long)
Thanks go to VBA developer Lars Moth-Poulsen, who lives and works in Denmark, who found that the above declaration needed modification to work correctly with CONNECT.
' --------------------------------------------------------------------- ' Create meaningful names Solid and Hole ' ---------------------------------------------------------------------
Private Const Solid As Long = 0 Private Const Hole As Long = 1' --------------------------------------------------------------------- ' SetSolidHole ' Work-around for the omission of a VBA method to set a shape element's ' solid|hole property ' Returns: True on success ' ---------------------------------------------------------------------
Private Function SetSolidHole(ByRef oElement As Element, ByRef solidHole As Long) As Boolean SetSolidHole = False Const sPROC_NAME As String = "SetSolidHole" On Error GoTo err_SetSolidHole If (oElement.IsClosedElement) Then Dim descriptor As LongPtr descriptor = oElement.MdlElementDescrP mdlElmdscr_setProperties descriptor, 0, 0, 0, 0, 0, 0, 0, solidHole SetSolidHole = True End If Exit Function err_SetSolidHole: ReportError sPROC_NAME, sMODULE_NAME End Function
Here's some example code to create a grouped hole.
First we create an enclosing shape, marked as solid.
Next we create two inner shapes, marked as holes.
We copy the three shapes into an array, then create the grouped hole by calling CreateCellElement1
.
Finally, we draw the new grouped hole and add it to the model …
' --------------------------------------------------------------------- ' Main entry point ' MicroStation keyin: ' vba run [GroupedHole]modMain.Main ' ---------------------------------------------------------------------
Public Sub Main() Const sPROC_NAME As String = "Main" On Error GoTo err_Main Dim msg As String msg = "Construct Grouped Hole Example" ShowMessage msg, msg, msdMessageCenterPriorityInfo Dim oEnclosure As ShapeElement Dim oInner1 As ShapeElement Dim oInner2 As ShapeElement Dim points(0 To 4) As Point3d' Create outer solid shape
points(0) = Point3dFromXY(100, 100) points(1) = Point3dFromXY(600, 100) points(2) = Point3dFromXY(600, 300) points(3) = Point3dFromXY(100, 300) points(4) = Point3dFromXY(100, 100) Set oEnclosure = CreateShapeElement1(Nothing, points, msdFillModeUseActive) SetSolidHole oEnclosure, Solid'ActiveModelReference.AddElement oEnclosure
oEnclosure.Redraw msdDrawingModeNormal' Create first inner hole shape
points(0) = Point3dFromXY(150, 150) points(1) = Point3dFromXY(200, 150) points(2) = Point3dFromXY(200, 200) points(3) = Point3dFromXY(150, 200) points(4) = Point3dFromXY(150, 150) Set oInner1 = CreateShapeElement1(Nothing, points, msdFillModeUseActive) SetSolidHole oInner1, Hole'ActiveModelReference.AddElement oInner1
oInner1.Redraw msdDrawingModeNormal' Create second inner hole shape
points(0) = Point3dFromXY(350, 200) points(1) = Point3dFromXY(450, 200) points(2) = Point3dFromXY(450, 250) points(3) = Point3dFromXY(350, 250) points(4) = Point3dFromXY(350, 200) Set oInner2 = CreateShapeElement1(Nothing, points, msdFillModeUseActive) SetSolidHole oInner2, Hole'ActiveModelReference.AddElement oInner2
oInner2.Redraw msdDrawingModeNormal' Put elements into an array
Dim groupedHole(0 To 2) As Element Set groupedHole(0) = oEnclosure Set groupedHole(1) = oInner1 Set groupedHole(2) = oInner2 Dim oGroupedHole As CellElement Dim origin As Point3d origin = Point3dFromXY(200, 200) Set oGroupedHole = CreateCellElement1(vbNullString, groupedHole, origin, False) oGroupedHole.Color = 3 oGroupedHole.Redraw msdDrawingModeNormal ActiveModelReference.AddElement oGroupedHole msg = "Grouped Hole example complete" ShowMessage msg, msg, msdMessageCenterPriorityInfo Exit Sub err_Main: ReportError sPROC_NAME, sMODULE_NAME End Sub
Verify that you really do have a grouped hole by applying a fill colour or pattern. You should see something like this (size and colour may vary) …
You can download this grouped hole VBA project.
Unpack the ZIP archive and copy GroupedHole.mvba
to a well-known location.
Keyin vba run [GroupedHole]modMain.Main
to execute this example.
VBA's Pattern
method applies only to those elements that
implement the ClosedElement
interface.
MicroStation Grouped Holes don't provide that interface.
However, we can call MDL functions to do the patterning for us.
There is a family of mdlPattern_xxx
functions that we can use for simple hatching,
cross-hatching, and area patterning.
This article describes how to apply patterning to MicroStation Grouped Hole elements. Snippets from the project VBA source code are below, with some cursory explanation about how it all works. If you want to take a shortcut, then you can download the Grouped Hole Patterning VBA project.
To use MDL functions we must declare them at the beginning of a VBA module. Here are the relevant declarations used in the sample project …
' ---------------------------------------------------------------------
' MDL function declarations
' ---------------------------------------------------------------------
Declare PtrSafe Function mdlElmdscr_isGroupedHole Lib "stdmdlbltin.dll" (ByVal groupEdP As LongPtr) As Long
Declare PtrSafe Function mdlElmdscr_add Lib "stdmdlbltin.dll" (ByVal elemDescr As LongPtr) As Long
Declare Sub mdlElmdscr_freeAll Lib "stdmdlbltin.dll" (ByRef elemDescrPP As LongPtr)
Declare PtrSafe Function mdlPattern_crossHatch Lib "stdmdlbltin.dll" ( _
ByRef hatchEdPP As LongPtr, _
ByVal shape As LongPtr, _
ByVal holes As LongPtr, _
ByVal templateP As LongPtr, _
ByVal angle1 As Double, _
ByVal angle2 As Double, _
ByVal spacing1 As Double, _
ByVal spacing2 As Double, _
ByVal view As Long, _
ByVal searchForHoles As Long, _
ByRef originPoint As Point3d) As Long
The VBA project's Main
subroutine does little more than to instantiate and start a
class clsAreaLocator
that Implements ILocateCommandEvents
…
' ---------------------------------------------------------------------
' Main entry point in modMain VBA module
' ---------------------------------------------------------------------
Public Sub Main()
Dim oLocator As New clsAreaLocator
CommandState.StartLocate oLocator
End Sub
The clsAreaLocator
is a pretty standard locator class that Implements ILocateCommandEvents
.
It's designed to accept either Grouped Holes or ClosedElement
s.
When you accept an area, it then calls the appropriate patterning function.
Note that this project makes use of the IsGroupedHole
function
described elsewhere …
' --------------------------------------------------------------------- ' Interesting methods of the clsAreaLocator class ' --------------------------------------------------------------------- ' ILocateCommandEvents_Accept ' ---------------------------------------------------------------------
Private Sub ILocateCommandEvents_Accept(ByVal oElement As Element, point As Point3d, ByVal view As view) Dim oPattern As CrossHatchPattern MakeCrossHatchPattern oPattern If (IsGroupedHole(oElement)) Then' ---------------------------------------------------------------------
' Use custom patterning function for Grouped Holes
' ---------------------------------------------------------------------
If (PatternGroupHole(oElement, oPattern)) Then oElement.Redraw msdDrawingModeNormal oElement.Rewrite End If ElseIf (oElement.IsClosedElement) Then' ---------------------------------------------------------------------
' Use VBA patterning method for normal closed elements
' ---------------------------------------------------------------------
Debug.Print "Apply pattern to element ID " & DLongToString(oElement.ID) With oElement.AsClosedElement .SetPattern oPattern, Matrix3dIdentity End With oElement.Redraw msdDrawingModeNormal oElement.Rewrite End If End Sub' --------------------------------------------------------------------- ' ILocateCommandEvents_LocateFilter ' ---------------------------------------------------------------------
Private Sub ILocateCommandEvents_LocateFilter(ByVal oElement As Element, point As Point3d, accepted As Boolean) accepted = False If (oElement.IsClosedElement Or IsGroupedHole(oElement)) Then accepted = True End If End Sub
Now for the smoke-and-mirrors.
MDL extends the C
language.
It uses pointers and dynamic memory allocation liberally: idioms that are alien to VBA.
The code below declares a variable pHatch
that pretends to be an MDL Element Descriptor.
The MDL function mdlPattern_crossHatch
takes the existing Grouped Hole element's descriptor,
and applies the pattern to it to create the pHatch
descriptor chain
(i.e. a list of LineElement
s that make up the hatch or crosshatch pattern).
Then, if the patterning was successful, we write pHatch
to our DGN model …
' --------------------------------------------------------------------- ' PatternGroupHole ' ---------------------------------------------------------------------
Public Function PatternGroupHole(ByVal oGroupedHole As CellElement, ByVal oPattern As CrossHatchPattern) As Boolean PatternGroupHole = False Dim pHatch As LongPtr' Pointer to element descriptor
Const SUCCESS As Long = 0 If (SUCCESS = mdlPattern_crossHatch(pHatch, oGroupedHole.MdlElementDescrP, 0, 0, oPattern.angle1, oPattern.angle2, oPattern.spacing1, oPattern.spacing2, 0, 1, oGroupedHole.Origin)) Then Dim filePos As Long filePos = mdlElmdscr_add(pHatch) mdlElmdscr_freeAll pHatch If (0 < filePos) Then PatternGroupHole = True Debug.Print "Added hatch at filePos " & CStr(filePos) End If Else MsgBox "PatternGroupHole failed", vbCritical Or vbOKOnly, "Pattern Grouped Hole" End If End Function
You can download the Patterning VBA Project.
It's in a ZIP archive, which you need to unpack and place in a location where MicroStation can find it.
Depending on which version of MicroStation you are using, copy Patterning.zip
here …
C:\Documents and Settings\All Users\Application Data\Bentley\WorkSpace\Projects\vba
C:\Program Files\Bentley\WorkSpace\Projects\vba
You need to enumerate the component elements of the Grouped Hole. The outer (solid) element has the greatest area, from which you must subtract the area of each inner (hole) element. Here's a function that performs that computation …
' --------------------------------------------------------------------- ' ComputeGroupedHoleArea ' Computes the area of a grouped hole element. Measure the area of ' the enclosing solid, then subtract the area of each enclosed hole element ' Returns: Area of grouped hole or 0.0 on error ' ---------------------------------------------------------------------
Public Function ComputeGroupedHoleArea(ByVal oGroupedHole As CellElement) As Double ComputeGroupedHoleArea = 0# On Error GoTo err_ComputeGroupedHoleArea If (IsGroupedHole(oGroupedHole)) Then Dim area As Double Dim oEnumerator As ElementEnumerator Set oEnumerator = oGroupedHole.GetSubElements' Get enclosing element
oEnumerator.MoveNext If (oEnumerator.Current.IsClosedElement) Then area = oEnumerator.Current.AsClosedElement.Area End If Do While oEnumerator.MoveNext' Get each hole element
If (oEnumerator.Current.IsClosedElement) Then area = area - oEnumerator.Current.AsClosedElement.Area End If Loop If (0# < Area) Then ComputeGroupedHoleArea = area End If End If Exit Function err_ComputeGroupedHoleArea: MsgBox "Error no. " & CStr(Err.Number) & ": " & Err.Description, vbOKOnly Or vbCritical, "Error in ComputeGroupedHoleArea" End Function
Post questions about VBA to the MicroStation Programming Forum.