Questions similar to these appear in the Bentley Community Discussion Groups.
This page lists some solutions to common MicroStation VBA (MVBA) problems. Tips are published as examples and are not necessarily working code.
Visual Basic for Applications does not provide one feature that most people would consider should be an inclusive part of any computer language: the ability to open and save files in a consistent manner. Curiously, Microsoft provides the common dialog DLL in all versions of Windows, but makes it hard to use from VBA. The section on file browsing provides a solution to this problem.
Absent from both VB and VBA is a way to browse for a folder. It's common, for example, to want to process all files of a given type in a particular folder. There is no graphic item that provides a folder browser. The section on folder browsing provides a solution to this problem.
Answers to those questions are provided here, in the sections captioned Browse for a Folder and Browse for a File. Before we cover those topics, we introduce a more general Microsoft tool for managing files & folders in your VB or VBA code: Windows Scripting.
Both VB and VBA have archaic tools for examining file attributes and getting a list of files from a folder.
For example, if you want to get a list of all the writable DGN files in folder X and its sub-folders, where would you start?
Wherever you start, you'll end up in a mess.
Why? Because the VB Dir
function cannot be used recursively, and to examine sub-folders you need a recursive function.
With Windows 2000, Microsoft introduced the Windows Scripting library. As with many Microsoft technologies, its name is cast in jelly, and tends to change from time to time. This library, as its name hints, was initially aimed at improving the lot of those poor souls attempting to write VB Script code for web purposes. However, it's useful for any of us wanting to write better file & folder code in VB and VBA. Microsoft Scripting Runtime is not a substitute for the file and folder dialogs discussed below; it does not contain any user interface components.
Use Windows Scripting in your VBA applications.
Make a reference to the DLL that hosts this library using the VBA menu Tools|References.
This pops the References dialog, where you can scroll to find the scrrun.dll
file.
Select Microsoft Scripting Runtime and click the OK button.
Once you've made a reference to Microsoft Scripting Runtime you can view its properties and methods using VBA's built-in Object Viewer.
Press function key F2 to pop VBA's object viewer dialog.
The core of Windows Scripting are the FileSystemObject
and the Dictionary
classes.
Read Microsoft's Script Runtime Overview for more information.
The FileSystemObject
provides a number of useful methods that enable the easy collection of folders and files.
The Dictionary
class presumably underlies these methods, and is separately available for your own collection implementations.
The Dictionary
class appears to offer better performance than VB's own Collection
class.
There are also methods to construct file and folder names from their text components.
Once you've created a reference to Microsoft Scripting Runtime in your project, you can write code like this …
Dim oFileSystem As Scripting.FileSystemObject Set oFileSystem = New Scripting.FileSystemObject Dim oFolder As Scripting.Folder Set oFolder = oFileSystem.GetFolder("C:\Windows") If oFolder.Attributes AND 2 Then Debug.Print "Hidden folder." End If If oFolder.Attributes AND 4 Then Debug.Print "System folder." End If If oFolder.Attributes AND 16 Then Debug.Print "Folder." End If If oFolder.Attributes AND 32 Then Debug.Print "Archive bit set." End If If oFolder.Attributes AND 2048 Then Debug.Print "Compressed folder." End If
Q I want to browse for a file using VBA. But, I don't see any API reference to file operations such as open, save, or save as. How do I open a file using MicroStation VBA?
A The Windows Common Dialog provides a way to let the user open or save a file. However, for reasons known only to Microsoft, the Common Dialog design-time component is provided with Visual Basic but not with Visual Basic for Applications. This doesn't make a lot of sense, because of course the DLL that provides that functionality is part & parcel of Windows (otherwise, we would never be able to open a file, right?).
There's nothing original about the code that accompanies this article. It's been published before on several web sites, such as The Code Project.
Because the Common Dialog DLL is on your system right now (I'm assuming that you are sitting in front of a Windows operating system),
you can invoke it directly from code.
You need to declare a number of constants from the Win32 API,
a user defined type OPENFILENAME
to pass data to the dialog,
and declare the function name from the DLL.
Copy these declarations into your own VBA code module. Put them at the beginning of the module, before any procedure definitions.
' --------------------------------------------------------------------- ' Win32 API declarations so that 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' --------------------------------------------------------------------- ' 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' --------------------------------------------------------------------- ' 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' ---------------------------------------------------------------------
Here's a file open procedure ShowOpen
.
It's a function procedure, that returns the path of the file chosen by the user,
or an empty string if the user cancelled the file open dialog.
The declarations shown above must exist in the file where you put this funcion.
We declare a variable OFName
of type OPENFILENAME
.
Next, we fill in the members of that structure prior to calling the Win32 API function GetOpenFileName
.
If the user selects a file and press the OK button,
then the OFName.lpstrFile
member contains the chosed file.
' --------------------------------------------------------------------- ' ShowOpen Open common dialog ' Returns: full path of file to open, or zero-length string if Cancel ' Example: ' StrFilter = "Text Files (*.txt)" + Chr$(0) + "*.txt" + Chr$(0) ' StrFilter = StrFilter & "All Files (*.*)" + Chr$(0) + "*.*" + Chr$(0) ' ---------------------------------------------------------------------
Public Function ShowOpen( _ strTitle As String, _ Optional strFilterDescr As String = "All files (*.*)", _ Optional strFilterSpec As String = "*.*", _ Optional strInitDir As String = vbNullString) As String On Error GoTo Proc_Error Dim OFName As OPENFILENAME Dim strFileFilter As String, _ strFileSelected As String'strFileFilter = "Microstation Files (*.dgn)" & Chr$(0) & "*.dgn" & Chr$(0)
'strFileFilter = strFileFilter & "Autocad Files (*.dwg)" + Chr$(0) + "*.dwg" + Chr$(0)
'strFileFilter = strFileFilter & "All Files (*.*)" + Chr$(0) + "*.*" + Chr$(0)
strFileFilter = strFilterDescr & Chr$(0) & strFilterSpec & Chr$(0) With OFName .lStructSize = LenB(OFName) .hWndOwner = 0& .hInstance = 0& 'App.hInstance'Select a filter
.lpstrFilter = strFileFilter ' "Text Files (*.txt)" & Chr$(0) &"*.txt" & Chr$(0) & "All Files (*.*)" & Chr$(0) & "*.*" & Chr$(0) .lpstrFile = Space$(254) .nMaxFile = 255 .lpstrFileTitle = Space$(254) .nMaxFileTitle = 255 If (vbNullString <> strInitDir) Then _ .lpstrInitialDir = strInitDir .lpstrTitle = strTitle ' "Select File" .flags = OFN_PATHMUSTEXIST Or OFN_FILEMUSTEXIST End With If GetOpenFileName(OFName) Then strFileSelected = Trim$(OFName.lpstrFile) If (InStr(strFileSelected, Chr(0)) > 0) Then strFileSelected = Left(strFileSelected, InStr(strFileSelected, Chr(0)) - 1) End If ShowOpen = Trim$(strFileSelected) Else ShowOpen = vbNullString End If Proc_Exit: Exit Function Proc_Error: ShowOpen = vbNullString MsgBox Err.Description Resume Proc_Exit End Function
Q I want to do something with each file in a particular directory. I want to choose a folder, then build a list of files in that folder. But, how do I browse for a Windows folder?
Post questions about MicroStation programming to the MicroStation Programming Forum.