Q These questions are about MicroStation VBA and levels. Similar questions crop up now and then on the BE Community forums.
There are several examples of level manipulation here. There's an example VBA module that removes a named level, then recreates it and sets some level symbology properties.
As a VBA (or .NET or C++) programmer you are privileged: you can see both the internal level ID and the visible level code. What's the difference?
Often, levels are defined and stored in a Design File Library (DGNLIB).
DGNLIBs are also known asLevel libraries, although they are used to store many other types of drawing standard.
A DGNLIB is a DGN file having a .dgnlib extension.
You can open a DGNLIB for editing just like any other DGN file.
Level libraries (DGNLIBs) are great for sharing level definitions among many users. If you're interested in level libraries (DGNLIBs) and VBA programming, there's more information about DGNLIBs.
Q How do I turn on all levels in all views?
A We wrote this example to illustrate one solution to this question.
We declare oView as a variable that references an MVBA View object.
We iterate all the available views in the ActiveDesignFile.Views collection.
The inner loop (For Each … Next) iterates all the DGN levels,
and obliges the view to display that level.
Public Sub DisplayAllLevelsInAllViews()
Dim oView As View
Dim oLevel As Level
For Each oView In ActiveDesignFile.Views
For Each oLevel In ActiveDesignFile.Levels
oLevel.IsDisplayedInView(oView) = True
Next oLevel
oView.Redraw
Next oView
End Sub
Q
I need to display a list of levels in a ComboBox.
A
We wrote this simple example to illustrate one approach.
Place a ComboBox in a UserForm,
then call this procedure in the UserForm's Initialise method.
Public Sub PopulateLevelComboBox(ByVal cbo As MSForms.ComboBox)
Dim oLevel As Level
cbo.Items.Clear
For Each oLevel In ActiveDesignFile.Levels
cbo.AddItem oLevel.Name
Next oLevel
End Sub
Q I need to make a list of levels in my DGN file.
A We wrote this simple example to illustrate one approach.
Public Sub TraceLevelNames()
Dim oLevel As Level
For Each oLevel In ActiveDesignFile.Levels
Debug.Print "Level '" & oLevel.Name & "'"
Next oLevel
End Sub
Q I need to determine if a named level exists in a DGN file.
A
This is a little bit tricky.
There is no VBA method that tells you if a level exists, so you have to do something with
DesignFile.Levels ("level-name").
However, that method throws an error if the level doesn't exist, so you need to wrap the
call inside a safer function.
Something like this …
' --------------------------------------------------------------------- ' IsValidLevelName ' Returns: True if the named level exists in the active design file ' or in any attached level library ' ---------------------------------------------------------------------Public Function IsValidLevelName(ByVal levelName As String) As Boolean IsValidLevelName = False On Error GoTo err_IsValidLevelName Dim oLevel As Level Set oLevel = ActiveDesignFile.Levels(levelName) If oLevel Is Nothing Then IsValidLevelName = False Else IsValidLevelName = True End If Set oLevel = Nothing Exit Function err_IsValidLevelName: Select Case Err.Number Case 5:' Level not foundResume Next Case Else MsgBox "IsValidLevelName failed" End Select End Function
Q I need to delete a level from my DGN file.
A You can't delete a level if that level is used anywhere in your DGN model. Shared cell definitions are invisible but nevertheless use levels. If you can't delete a level, check that there is not a hidden shared cell definition that is thwarting your intent.
Whenever you add, remove, or change a level definition, you must call Levels.Rewrite to make your change permanent.
Here's a function that removes a named level from your DGN model …
' --------------------------------------------------------------------- ' RemoveLevel ' Removes the named level. This only works if this level is not ' used by any element (including shared cell definitions) in the DGN file. ' Returns: True if the level existed ' ---------------------------------------------------------------------Function RemoveLevel(ByVal levelName As String) As Boolean RemoveLevel = False Dim oLevels As Levels Dim oLevel As Level Set oLevels = ActiveDesignFile.Levels Set oLevel = oLevels.Find(levelName) If (oLevel Is Nothing) Then' Level does not existElse' Level existsIf (oLevel.IsInUseWithinModel(ActiveModelReference)) Then MsgBox "Level '" & levelName & "' is in use", vbExclamation Or vbOKOnly, "Unable to Delete Level" Else ActiveDesignFile.DeleteLevel oLevel' Persist changeoLevels.Rewrite RemoveLevel = True End If End If End Function
Q I need to create a level legend in my DGNLIB.
A Open the DGNLIB as a normal file. Iterate the level collection in the DGNLIB, and for each level create a sample graphic & descriptive text.
Q I need to create a level in my DGN file.
A You can create a named level and assign it properties (e.g. override colour) programmatically.
Whenever you add, remove, or change a level definition, you must call Levels.Rewrite to make your change permanent.
Here's a function that creates a named level in your DGN model, and assigns it a level code …
' --------------------------------------------------------------------- ' CreateLevel ' Create a new level in the active design file with the given name ' Returns: True if the new level was created ' ---------------------------------------------------------------------Function CreateLevel(ByVal levelName As String, _ ByVal levelCode As Long, _ ByVal colorByLevel As Long, _ ByVal colorOverride As Long, _ ByVal styleByLevel As Long, _ ByVal styleOverride As Long) As Boolean CreateLevel = False Dim oLevel As Level Set oLevel = ActiveDesignFile.AddNewLevel(levelName) If (oLevel Is Nothing) Then MsgBox "Failed to create new level '" & levelName & "'", vbExclamation Or vbOKOnly, "Level Creation Failed" Else MsgBox "Created new level '" & levelName & "'", vbInformation Or vbOKOnly, "Level Created" CreateLevel = True' Level.Number is user-assigned, in contrast to the MicroStation-assigned Level.IDoLevel.Number = levelCode' Colours are assigned by valueoLevel.ElementColor = colorByLevel oLevel.OverrideColor = colorOverride' Line styles take an object referenceDim oStyle As LineStyle Set oStyle = ActiveDesignFile.LineStyles.Item(styleByLevel) If (oStyle Is Nothing) Then MsgBox "Invalid line style '" & CStr(styleByLevel) & "'", vbExclamation Or vbOKOnly, "Invalid Line Style" Else Set oLevel.ElementLineStyle = oStyle End If Set oStyle = ActiveDesignFile.LineStyles.Item(styleOverride) If (oStyle Is Nothing) Then MsgBox "Invalid line style '" & CStr(styleOverride) & "'", vbExclamation Or vbOKOnly, "Invalid Line Style" Else Set oLevel.ElementLineStyle = oStyle End If End If End Function
Transparency and Priority are properties of a level that don't seem to have made it into VBA.
However, you can set level priority using MDL. Here is the function declaration …
Declare PtrSafe Function mdlLevel_setDisplayPriority Lib "stdmdlbltin.dll" ( _
ByVal modelRefIn As LongPtr, _
ByVal levelIdIn As Long, _
ByVal priorityIn As Long) As Long
priorityIn is an arbitrary positive or negative integer value.
Here's an example usage …
Dim oLevel As Level Dim oModel As ModelReference... get oLevel and oModel from somewhereDim levelId As Long levelId = oLevel.ID Dim modelRef As Long' MDL PointermodelRef = oModel.MdlModelRefP Const Priority As Long = 100 mdlLevel_setDisplayPriority modelRef, levelId, Priority
Transparency and Priority are properties of a level that don't seem to have made it into VBA.
However, you can set level transparency using MDL. Here is the function declaration …
Declare PtrSafe Function mdlLevel_setTransparency Lib "stdmdlbltin.dll" ( _ ByVal modelRefIn As LongPtr, _ ByVal levelIdIn As Long, _ ByVal transparencyIn As Double ) As Long
transparencyIn is a Double value in the range 0.0 to 1.0.
Here's an example usage …
Dim oLevel As Level Dim oModel As ModelReference... get oLevel and oModel from somewhereDim levelId As Long levelId = oLevel.ID Dim modelRef As Long' MDL PointermodelRef = oModel.MdlModelRefP Const Transparency As Double = 0.5 mdlLevel_setTransparency modelRef, levelId, Transparency
When you look at the Level Manager or Level Display dialogs, you are seeing all levels to which your active design file has access. Some level definitions exist in your DGN file's level table; other definitions may exist in level libraries attached as instructed by your workspace configuration.
When you create an element, the level definition must exist in the active DGN file. MicroStation copies the definition from a level library if that definition does not exist in the active file's level table. VBA doesn't provide a way to copy a level definition from a level library into the active level table. How do you get around that problem?
One way is to create a temporary element and assign the desired level to that element. MicroStation copies the level definition into the active level table. Next, delete the temporary element — leaving the level definition in the level table. Here's an example …
' --------------------------------------------------------------------- ' EnsureLevelIsInDgnFile ' You can see a level in the Levels collection, but it may be defined ' in a DGNLIB. This procedure ensures that the level exists in the ' active DGN file by creating and removing an element on that level. ' Note: the level passed in is ByRef and may be altered ' Returns: True if level already exists in DGN file or was added successfully ' --------------------------------------------------------------------- Public Function EnsureLevelIsInDgnFile(ByRef oLevel As level) As Boolean EnsureLevelIsInDgnFile = False Debug.Assert Not oLevel Is Nothing If oLevel.IsFromLevelLibrary Then Dim oTemp As EllipseElement Set oTemp = CreateEllipseElement2(Nothing, Point3dZero, 1#, 1#, Matrix3dIdentity) Set oTemp.level = oLevel ActiveModelReference.AddElement oTemp ActiveModelReference.RemoveElement oTemp ' Reassign level which is now in the DGN file's level table Set oLevel = ActiveDesignFile.Levels.Find(oLevel.name) End If EnsureLevelIsInDgnFile = True End Function
Here's an example VBA module that deletes a named level from your DGN model,
then recreates it and specifies some level symbology properties.
It illustrates how the above RemoveLevel and CreateLevel functions are used …
Option Explicit' --------------------------------------------------------------------- ' Create a new level and assign symbology and properties ' --------------------------------------------------------------------- ' 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()' Example level property definitionsConst strLevelName As String = "Example Level" Const nColorByLevel As Long = 7 Const nColorOverride As Long = 96 Const nStyleByLevel As Long = 1 Const nStyleOverride As Long = 2 If (RemoveLevel(strLevelName)) Then Dim oLevel As Level Dim oLevels As Levels Set oLevels = ActiveDesignFile.Levels Set oLevel = oLevels.Find(strLevelName) If (oLevel Is Nothing) Then If (CreateLevel(strLevelName, nColorByLevel, nColorOverride, nStyleByLevel, nStyleOverride)) Then' Make new level activeSet oLevel = oLevels.Find(strLevelName) oLevel.IsActive = True' Persist our changesoLevels.Rewrite End If End If Else MsgBox "Unable to remove level '" & strLevelName & "' already exists", vbExclamation Or vbOKOnly, "Unable to Remove Level" End If End Sub
Post questions about VBA to the MicroStation Programming Forum.