Questions similar to these appear in the Be Communities MicroStation Programming Forum.

This page lists some solutions to common MicroStation VBA (MVBA) problems. Tips are published as examples and are not necessarily working code.

Introduction

Suppose you install an application, such as Bentley Systems' MicroStation or Microsoft Excel, onto a Windows operating system.

File Extension

The application designates a file extension to be associated with the application. For example, the file extension registered for Excel is .xls. The file extension registered for MicroStation is .dgn.

A consequence of registering a file extension is that Windows Explorer knows what application to start when you double-click a file in an Explorer window. That is, if you double-click your-file.xls then Explorer starts Excel and instructs Excel to load that file.

File Type

At the same time as registering the file extension with Windows, installation may also register a File Type. The File Type is a brief description of the file's purpose. For example, the file type of a .xls file is Microsoft Excel Worksheet.

SHGetFileInfo

SHGetFileInfo is a Win32 function. The SH prefix indicates that it belongs to the Windows shell  family of functions. Its purpose is to obtain information about a directory, short-cut, icon, file or file type. As with many of Microsoft's Win32 functions, its usage is quite complex and requires the right combination of flags to behave in a sensible manner.

Win32 Declarations

VBA requires you to declare a Win32 function before you can use it. With 64-bit VBA, you must declare a Windows function PtrSafe. Here it is …

Declare PtrSafe Function SHGetFileInfo Lib "shell32.dll" Alias "SHGetFileInfoA" ( _
    ByVal pszPath As Any, _
    ByVal dwFileAttributes As Long, _
    ByRef psfi As SHFILEINFO, _
    ByVal cbFileInfo As Long, _
    ByVal uFlags As Long) As Long

We also need the VBA user-defined-type (UDT) that translates the Win32 SHFILEINFO struct …

Type SHFILEINFO
  hIcon As Long
  iIcon As Long
  dwAttributes As Long
  szDisplayName As String * 260
  szTypeName As String * 80
End Type

Win32 Flags

SHGetFileInfo takes a disconcerting combination of flags. For a full description, visit the Microsoft web site. Here are some, but possibly not all, VBA constant representation of those flags …

Const FILE_ATTRIBUTE_ARCHIVE = &H20
Const FILE_ATTRIBUTE_COMPRESSED = &H800
Const FILE_ATTRIBUTE_DIRECTORY = &H10
Const FILE_ATTRIBUTE_HIDDEN = &H2
Const FILE_ATTRIBUTE_NORMAL = &H0
Const FILE_ATTRIBUTE_READONLY = &H1
Const FILE_ATTRIBUTE_SYSTEM = &H4
Const SHGFI_ATTRIBUTES = &H800
Const SHGFI_DISPLAYNAME = &H200
Const SHGFI_EXETYPE = &H2000
Const SHGFI_ICON = &H100
Const SHGFI_ICONLOCATION = &H1000
Const SHGFI_LARGEICON = &H0
Const SHGFI_LINKOVERLAY = &H8000
Const SHGFI_OPENICON = &H2
Const SHGFI_PIDL = &H8
Const SHGFI_SELECTED = &H10000
Const SHGFI_SHELLICONSIZE = &H4
Const SHGFI_SMALLICON = &H1
Const SHGFI_SYSICONINDEX = &H4000
Const SHGFI_TYPENAME = &H400
Const SHGFI_USEFILEATTRIBUTES = &H10

VBA Example

Here's a VBA subroutine that gets the file type description of your choice of file. In this example, the file doesn't have to exist — we're just asking Windows to tell us about the file extension …


' ---------------------------------------------------------------------
'   TestSHGetFileInfo
'   Demonstrates use of Win32 function SHGetFileInfo to get information
'   about a file, shortcut, or icon
' ---------------------------------------------------------------------
Sub TestSHGetFileInfo()
    Dim info                                As SHFILEINFO  ' receives information about the file
    Dim retval                              As Long  ' return value of the Win32 function
    'Const FileName                          As String = "C:\dummy.mp3" ' OK
    Const FileName                          As String = "L:\FlexiTable\dgn\Hawes\Assembly.dgn"  '   OK
    ' Retrieve information about the file
    retval = SHGetFileInfo(FileName, FILE_ATTRIBUTE_ARCHIVE, info, Len(info), SHGFI_USEFILEATTRIBUTES Or SHGFI_TYPENAME Or SHGFI_ICON)
    Debug.Print "SHGetFileInfo (" & FileName & ") retval=" & CStr(retval)
    Debug.Print "Display name: " & info.szDisplayName
    Debug.Print "Type Descr:   " & info.szTypeName
End Sub

Acknowledgements

As is often the case, I could not have written this article without help gleaned from the web. I am indebted to the following web sites …