Questions similar to this appear on the Be Communities MicroStation Programming Forum.
Q Two of the most common requirements of computer software are the ability to choose a file to open, and to choose a file name when saving a file. Those requirements are also true of MicroStation® VBA.
If you want to skip the explanation, you can download the VBA Common Dialogs project here.
A MicroStation CONNECT is a 64-bit application that includes Microsoft VBA v7.1 64-bit. Earlier versions of MicroStation deliver VBA v6.4 32-bit.
For the most part, VBA just works. There's not a lot of difference, on the surface, between the 64-bit and 32-bit versions. However, differences come into play when you venture outside the comfortable, homogenous environment of VBA.
For example, in this article we discuss the Windows Common Dialogs and how to call them from VBA. This requires us to call Win32 functions that are delivered in the various Windows DLLs installed on your computer. We must declare those functions, in our VBA code, so that VBA can find them and use them correctly.
Win32 function declarations differ between 64-bit and 32-bit versions of VBA. The declarations in this article and in the downloadable VBA project are for 64-bit VBA for MicroStation CONNECT.
A What you are looking for is the Windows Common Dialog Control. The Common Dialog Controls provide the familiar File Open, File Save As, and other dialogs. Inexplicably, Microsoft chose to omit that functionality from Visual Basic for Applications™ (VBA). They are, however, included in now-obselete Visual Basic™ (VB) in contrast to VBA.
If you want to move from VBA to .NET, then be aware that MicroStation CONNECT provides a first-class .NET API in addition to VBA and C++.
What makes the Common Dialog Controls' omission from VBA infuriating is that they are, of course, included with every copy of Windows. They are installed, along with many other system dynamically linked libraries (DLLs), in your Windows folder. Fortunately, there is a way to use them from VBA, but it's not intuitive. VB and VBA let you call functions implemented in Windows DLLs. Here's how…
Declare
a function stored in a DLL
Public
VBA procedure to hide the gory details
It's a good idea to build your own library of really useful procedures.
A library in MicroStation VBA is simply a project.
You can reference one VBA project from another.
For example, you might create a VBA project WindowsUtilities
that contains your wrappers around the Windows Common Dialog Controls.
When your new VBA application requires a File Open dialog, reference your library and call your wrapper procedure.
See the article about creating a colour chooser in VBA.
Calling a DLL is simple, but complicated by the amount of ancilliary information that goes along with it. That's why it's a good idea to wrap Windows functions inside a VBA procedure. Once done, it's done, and you can forget about the details.
First, declare the Windows function you want to use…
' ---------------------------------------------------------------------
' Win32 API declarations so that 64-bit VBA can call
' Windows functions directly
' ---------------------------------------------------------------------
Private Declare PtrSafe Function GetOpenFileName Lib "comdlg32.dll" _
Alias "GetOpenFileNameA" (ByRef lpofn As OPENFILENAME) As Long
Private Declare PtrSafe Function GetSaveFileName Lib "comdlg32.dll" _
Alias "GetSaveFileNameA" (pOpenfilename As OPENFILENAME) As Long
The declaration tells VBA that function GetSaveFileName
is imlemented in DLL comdlg32.dll
.
It takes a single argument by reference, which is a user defined type (UDT) OPENFILENAME
.
Visit this Microsoft web page for more information
about the
OPENFILENAME structure.
Here's the definition of OPENFILENAME
…
' ---------------------------------------------------------------------
' Win32 API structure definition as user-defined type
' ---------------------------------------------------------------------
Private Type OPENFILENAME
lStructSize As Long
hwndOwner As LongPtr
hInstance As LongPtr
lpstrFilter As String
lpstrCustomFilter As String
nMaxCustFilter As Long
nFilterIndex As Long
lpstrFile As String
nMaxFile As Long
lpstrFileTitle As String
nMaxFileTitle As Long
lpstrInitialDir As String
lpstrTitle As String
flags As Long
nFileOffset As Integer
nFileExtension As Integer
lpstrDefExt As String
lCustData As Long
lpfnHook As LongPtr
lpTemplateName As String
End Type
OPENFILENAME
parameters understand one or two flags that are defined by Microsoft…
' ---------------------------------------------------------------------
' Win32 API constants
' ---------------------------------------------------------------------
Private Const BIF_NEWDIALOGSTYLE As Long = &H40 Private Const BIF_RETURNONLYFSDIRS As Long = 1 Private Const MAX_PATH As Long = 260 Private Const OFN_OVERWRITEPROMPT As Long = &H2 Private Const OFN_FILEMUSTEXIST As Long = &H1000 Private Const OFN_PATHMUSTEXIST As Long = &H800 Private Const OFN_HIDEREADONLY As Long = &H4'--------------------------------------------------------------
Here's a VBA function ShowSave
.
It wraps the Windows function GetSaveFileName
so that it's easy to call from your VBA code.
Call it like this …
Dim dgnFile As String dgnFile = ShowSave ("Save Design File As...", _ "MicroStation Files (*.dgn)", "*.dgn", "V:\shared")
' --------------------------------------------------------------------- ' ShowSave Save As... common dialog ' Arguments: [in, String] dialog title, ' [in, String] filter description, [optional] ' [in, String] filter spec, [optional] ' [in, String] default directory [optional] ' Example call: ' dgnFile = ShowSave ("Save Design File As...", "MicroStation Files (*.dgn)", "*.dgn", "V:\shared") ' Returns: full path of file to be saved ' ---------------------------------------------------------------------
Public Function ShowSave( _ ByVal strDialogTitle As String, _ ByVal strProposed As String, _ Optional ByVal strFilterDescr As String = "All files (*.*)", _ Optional ByVal strFilterSpec As String = "*.*", _ Optional ByVal strDefaultDir As String = vbNullString) As String On Error Resume Next Dim strFilter As String, _ strFileSelected As String, _ proposed As String Dim OFName As OPENFILENAME strFilter = strFilterDescr + Chr$(0) + strFilterSpec + Chr$(0) proposed = strProposed & Chr$(0) & Space$(254 - Len(strProposed))'Create a buffer
Const Period As String = "." With OFName .lStructSize = LenB(OFName)' Set the structure size. Note use of LenB() not Len()
.hWndOwner = 0&' Set the owner window
.hInstance = 0&' Set the application's instance
.lpstrFilter = strFilter 'Set the filter .lpstrFile = proposed .lpstrDefExt = Mid$(strFilterSpec, 1 + InStr(strFilterSpec, Period)) .nMaxFile = 255' Set the maximum number of chars
.lpstrFileTitle = Space$(254) ' Create a buffer .nMaxFileTitle = 255'Set the maximum number of chars
If (vbNullString <> strDefaultDir) Then _ .lpstrInitialDir = strDefaultDir 'Set the initial directory .lpstrTitle = strDialogTitle'Set the dialog title
.flags = OFN_OVERWRITEPROMPT'no extra flags
End With If GetSaveFileName(OFName) Then'Show the 'Save File' dialog
strFileSelected = Trim$(OFName.lpstrFile) If (InStr(strFileSelected, Chr(0)) > 0) Then strFileSelected = Left(strFileSelected, InStr(strFileSelected, Chr(0)) - 1) End If ShowSave = Trim(strFileSelected) Else ShowSave = "" End If End Function
ShowSave
wraps the Windows function GetSaveFileName
.
Wrapping the Windows function makes it easy to call from your VBA code.
Someone using your code doesn't know (or need to know) that it contains a Windows function call.
ShowSave
is easy to call from your VBA code.
Call it like this…
Dim dgnFile As String dgnFile = ShowSave ("Save Design File As...", "MicroStation Files (*.dgn)", "*.dgn", "V:\shared") Dim msg As String If (0 < len (dgnFile)) Then msg = "User chose file '" & dgnFile & "'" Else msg = "User cancelled file save" End If ShowMessage msg, msg, msdMessageCenterPriorityInfo
ShowSave
wraps the Windows function GetSaveFileName
.
Wrapping the Windows function makes it easy to call from your VBA code.
Someone using your code doesn't know (or need to know) that it contains a Windows function call.
Here's how to call the wrapper to save a MicroStation DGN file in AutoCAD DWG format …
Dim dgnFile As String Dim folder As String folder = ActiveWorkspace.ConfigurationVariableValue("MS_DGNOUT") dwgFile = ShowSave ("Save File As DWG...", "AutoCAD Files (*.dwg)", "*.dwg", folder) Dim msg As String If (0 < len (dwgFile)) Then msg = "Saved DWG file '" & dwgFile & "'" ActiveDesignFile.SaveAs dwgFile, True, msdDesignFileFormatDWG Else msg = "User cancelled file save" End If ShowMessage msg, msg, msdMessageCenterPriorityInfo
The Common Dialogs VBA Project provides both File Open and File Save As dialogs. Ther are two modules in the project …
modMain
has two short subroutines to test the common dialogs
modCommonDialogs
has the code that implements the dialogs.
You can use the module in your own code by exporting it as a text file and importing
it into your project
You can download the Common Dialogs Project from this web site.
Post questions about MicroStation programming to the MicroStation Programming Forum.