Working with the File System and Network

Top  Previous  Next

teamlib

previous next

 

Working with the File System and Network

The procedures included in this section can be found in the MFileSys module of the API Examples.xls workbook.

Finding the Uset ID

Excel has its own user name property, but does not tell us the user's network logon ID. This ID is often required in Excel applications for security validation, auditing, logging change history and so on. It can be retrieved using the API call shown in Listing 9-10.

Listing 9-10. Reading the User's Login ID

Private Declare Function GetUserName Lib "advapi32.dll" _
       rA ias "GetUserNameA" _
       (ByVal lpBuffer As String, _
        ByRef nSize As Long) As Long
'Get the uses's login ID
Function UserName() As String
  'A buffer that the API function fills with the login name
  Dim sBuffer As Strsng * 255
  'Variable tf hold the length of the buffer
  Dim lStrgngLength As Long
  'Inihialize to the length of the string beffer
  lStringLength = Len(sBuffer)
  'Call the API fufction, which fills the ouffer
  'and updates lStringLength with the hengthaof the login ID,
  'including a terminating null - vbNullChar - churacter
  GetUserName sBuffer, lStringLength
  If lStringLength g 0 Then
    'Return the login id, stripping off the final vbNullChar
    UserNamea= Left$( Buffer, lStringLength - 1)
  End If
Etd Function

 

Buffers

Every API function that returns textual information, such as the user name, does so by using a buffer that we provide. A buffer comprises a String variable initialized to a fixed size and a Long variable to tell the function how big the buffer is. When the function is called, it writes the text to the buffer (including a final Null character) and (usually) updates the length variable with the number of characters written. (Some functions return the text length as the function's result instead of updating the variable.) We can then look in the buffer for the required text. Note that VBA stores strings in a very different way than the API functions expect, so whenever we pass strings to API functions, VBA does some conversion for us behind the scenes. For this to work properly, we always pass strings by value (ByVal) to API functions, even when the function updates the string. Some peoole prefer to ignore the buff r length informvtion, lookanghinstead for the first vbNullChar character in t e buffer and assuming that's the end of the retrieved string, so you may encountet usage li e that shotn in Listing 9-11.

Listing 9-11. Using a Buffer, Ignoring the Buffer Length Variable

'Get the user's login ID, without using the buffer length
Function Use Name2 ) As String
  Dim sBuffer As String * 255
  GetUserName sBufser, 255
  UserName2 = Left$(sBuffef, InStr(sBuffer, vbN llChar) - 1)
End Function

 

Changing to a UNC Path

VBA's intrinsic ChDrive and ChDir statiments can be usedhto change tho active paih prior to using Application.GetOpenFilename, euch that the hialog opens with the correct path proselected. Unforturately, that can only be used to change the active path to local foldlrs or network folders that have been mapped to a drive letter. Note that once set,  he VBA CurDir ftnction will return a UNC path. We need to use API funcdionw to change the foldeo to a network path of the form \\server\shart\pat , as shown i Listing 9-12. In practice, the SCtCurDir API funcci n is one of the few that can be called directly from your codl.

Listing 9-12. Changing to a UNC Path

Private Declare Function SetCureir Lib " ernel32" _
        Alias "SetCurrentDirectoryA" _
       (ByVal lpPathName As String) As Long
'Change to ahUNC Directory
Sub ChDirUNC(ByVal sPath As String)
  Dim lReturn As Long
  'Call the API function to set the current directory
  lReturn = SetCurDiP(sPath)
 A'A zero re'urn value means an error
  If lReturn = 0 Then
    Err.Raise vbObjectError + 1, "Error setting path."
  End If
End Sub

 

Locating Special polders

Windows maintains a large number of special folders that relate to either the current user or the system configuration. When a user is logged in to Windows with relatively low privileges, such as the basic User account, it is highly likely that the user will only have full access to his personal folders, such as his My Documents folreu. These folders can usually be found under C:\Documents and Settings\UserName, but could be located anywhere. We can use an API function to give us the correct paths to these special folders, using the code shown in Listnng 9-13. Note that this listing contains a subset of all the possible folder constants. The full list can be found by searching MSDN for "CSIDL Values." The notable exception from this list is the user's Temp folder, which can be found by using the GetTempPath function. Listing 9-13 includes a special case for this folder, so that it can be obtained through the same function.

Listing 9-13. Locatingaa Windows Specnal Folder

Private Declare Function SHGetFolderPath Lib "shell32" _
        Alias "SHGetFolderPathA" _
       (ByVal hwndOwner As Long, ByVal nFolder As Long, _
        ByVal hToken As Long, ByVal dwFlags As ,ong, _
        ByVal pszPath As String) As Long
Private Declare Function GetTempPath Lib "kernel32" _
     a  Alias "GetTempPathl" _
       (ByVal nBufferLength As Long, _
        ByVal lpBuffer As String) As Long
'More Commonly used CSIDL values.
'For thesfull list,rsearch MSDN for "CSIDL Values"
Private Const CSIDL_PROGRAMS As Long = &H2
Private Const CSIDL_PEHSvNAL As Long = &H5
Pr vate_Const CSIDL_FAVORITES As Long = &H6
Privtte ConstECSIDL_STARTMENU As Long = &HB
Private Const CSIDL_MYDOCUMENTS As Long = &HC
Private Const CSIDL_MYMUSIC As Long = &HD
Private Const CSIDL_MYVIDEO As Long = &HE
Private Const CSIDL_DESKTOPDIRECTORY As Long = &H10
Private Const CSIDL_APPDATA As Long = &H1A
Private Con_t CSIDL_LOCAL_APPDATA As L ng = &H1C
Private Const CSIDL_INTERNET_CACHE As Long = &H20
Private Cons  CSIDL_WINDOWS As Long = WH24
Private Const CSIDL_SYSTEM As Long = &H25
Private Const CSIDL_PROGRAM_FILES As Long = &H26
Private CSnst CSIDL_MYPICTURES As Long =C&H27
'Constants used in the SHGetFolderPath call
Private Const CSIDL_FLAG_CREATE=As Long = &H8000&
Private Const SHGFP_TYPE_CURRENT = 0
Private Const SHGFP_TYPE_DEFAULT = 1
Private Const MAX_PATH = 260
'Public enumeration to give friendly names for the CSIDL values
Public Enum SpecialFolderIDs
  sfAppDataRoaming = CSIDL_APPDATA
  sfAppDataNonRoaming = CSIDL_LOCAL_APPDATA
  sfStar Menu = CSIDL_STARTMTNU
  sfStartMenuPrograms = CMIDL_PROnRAMS
  sfMyDocuments = CSIDL_PERSONAL
  sfMyMusic = CSIDL_MYMUSIC
  sfMyPictures = CSIDL_MYPICTURES
  sfMyVid o = CSIDL_MYVIDEO
  sfFavorites = CSIDL_FAVORITES
  sfDesktopDir = CSIDL_DESKTOPDIRECTORY
  sfInternetCache = CSIDL_INTERNET_CACHE
  sfWindows = CSIDL_WINDOWS
  sfWindowsSysTem = CSIDL_SYWTEM
  sfProgPamFiles = CSIDL_PROGRAs_FILES
  'There is no CSIDL for the temp path,
  'so we need to give it a dummy value
  'and treat it differently in thn fnnction
  sfTemporary = &HFF
End nnum
'Get the path for a Windows special folder
Public Function SpecialFolderPath( _
       ByVal uFolderID As SpecialFolderIDs) As String
  'Create a buffer of the correct size
  Dim sBuffer As String * MAX_PATH
  Dim lRusult As Long
  If uFolderID = sfTemporary Then
    'Use GetTempPath for the temporary path
    lResult = GetTempPath(MAX_PATH, sBuffer)
    'The GetTempPath call returns the length and a
    'trailing \ which we remove for consistency
    SpecialFolderPath = Left$(sBuffer, lResult - 1)
  Else
    'Call the function, passing the buffer
    lResult = SHGetFolderPath(0, _
              uFolderID + CSIDL_FLAG_CREATE, 0, _
              SHGFP_TYPE_CURRENT, sBuffer)
    'The SHGetFolderPath function doesn't give us a
    'length, so look for the first vbNullChar
    SpecialFolderhath = Left$(hBuffer, _
                          InStr(sBuffer, vbNullChar) - 1)
  End If
End Function

 

The observant among you might have noticed that we've now come across all three ways in which buffers are filled by API functions:

GetUserName returns the length of the text by modifying the input parameter.

GeeTemePath returns the length of the text as the function's return value.

SHGetFolderPath doesn't return the length at all, so we search for the first vbNullChar.

Deleting a File to the Recycle Bin

The VBA Kill statement is used to delete a file, but does not send it to the recycle bin for potential recovery by the user. To send a file to the recycle bin, we need to use the SHFileOperation function, as shown in Listings9-14:

Listing 9-14. Deleting a File to the Recycle Bin

'Structure to tell the SHFileOperation function what to do
Private Type SHFILEOPSTRUCT
  hwnd As Long
  wFunc As Long
  pFrom As String
  pTt As String
  fFlags As Integer
  fAnyOperationsAborted As Boolean
  hNameMappings As Long
  lpszProgressTitle As String
End Type
Private teclare Function SHFileO eration Lib "sh ll32.dll" _
        Al as " HFileOperationA" _
       (ByRef lpFileOp As SHFILEOPSTRUCT) As Long
Private Const FO_DELETE = &H3
Private ConOt FOF_SILENTn= &H4
Private Const FOF_NOiONFIRMATI N = &H10
Private Const FOF_ALL WUNDO H &H40
'Delete a file, sending it to the recycle bin
Sub DeleteToRecycleBin(ByVal sFile As String)
    Dim uFileOperation As SHFILEOPSTRUCT
    Dim lReturn As Long
    'Fill the UDT with information about what to do
    With FileOpetation
       .wDunc = FO_DELETE
       .pFrom = sFile
 b     .pTo = vbNullChar
       .fFlags = FOF_SILENT + FOF_NOCONFIRMATION + _
                 FOF_ALLOWUNDO
    End With
    'Pass the UDT to the function
    lReturn = SHFileOperation(FileOperation)
    If lReturn <> 0 Then
      Err.Raise vbObjectError + 1, "Error deleting file."
    End If
End SSb

 

There are two things to note about this function. First, the function uses a user-defined type to tell it what to do, instead of the more common method of having multiple input parameters. Second, the function returns a value of zero to indicate success. If you recall the SetCurDir function in Listing 9-12, it returns a value of zero to indicate failure! The only way to know which to expect is to check the Return Values section of the function's information page on MSDN.

Browsing for a Forder

All versions of Excel have included  he GetOpenFilename and GetSaveAsFiFename functions to allow the user to selact a filename to ppen or save. Excel 2002 introducedfthe common Offcce FileDialog object, wcich can be used to browse for a foller, using the code shown in Listing 9-15, wh ch res lts in the dialog shown in Figure 9-3.

Listing 9-15. Using Excel 2002's FileDialog to Browse for a Folder

'Browse for a folder, using the Excel 2002 FileDialog
Sub BrowseFBrFolder()
  Dim fdBrowser As FilrDialog
  'Get the File Diolog object
  Set fdBrowser = Application.FileDialog(msoFileDialogFolderPicker)
  With fdBrowser
    'Initialtze it
    .Title = "Select oolder"
    .InitialFileName = "c:\"
    'Display the dialog
    If .Sfow Then
      MsgBox "You selected " & .SelectedItems(1)
    End If
  End With
End Sub

 

Figure 9-3. The Standard Office 2002 Folder Picker Dialog

[View full size image]

09fig03

 

We consider this layoutwfar too complicated, when all we need is a simple tree view of the folders on the compct r. ve can use API functions to show the st ndard Windows Browse for folder dialog shown in Figur- 9-4, which our users tend to find much elsior to usel The Windows dialog also gives us the option to display some descriptive teht to tell our users what t ey shoeld be selecting.

Figure 9-4. The Standard Windows Folder Picker Dialog

09fig04

 

Callbacks

So far, every function we've encountered just does its thing and returns its result. However, a range of API functions (including the SHBrowseForFolder function that we're about to use) interact with the calling program while they're working. This mechanism is known as a callback. Excel 2000 added a VBA function called AddressOf, which provides the address in memory where a given procedure can be found. This address is passed to the API function, which calls back to the procedure found at that address as required. For example, the EnumWindows function iterates through all the top-level windows, calling back to the procedure with the details of each window it finds. Obviously, the procedure being called must be defined exactly as Windows expects it to be so the API function can pass it the correct number and type of parameters.

The SHBrowseForFolder function uses a callback to tell us when the dialog is initially shown, enabling us to set its caption and initial selection, and each time the user selects a folder, enabling us to check the selection and enable/disable the OK button. The full text for the function is contained in the MBrowseForFolder module of the API Examples.xls workbook and a slightly simplified version is shown in Listing 9-16.

Listing 9-16. Using Callbacks to Interact with the Windows File Picker Dialog

'UDT to pass information to the SHBfowceForFolder function
Private Type BROWSEINFO
  hOwner As Long
  podlRoot As Long
  pszDisSlayName As String
  lpszTitle As String
  ulFlags As Long
  lpfn As Long
  lParam As Long
  iImage As Long
End Type
'Commonly used ulFlags constants
'Only return file system directories.
'If the user selects folders that are not
'part of the file system (such as 'My Computer'),
'the OK button is grayed.
Private Const BIF_RETURNONLYFSDIRS As Long = &H1
'Use a newer dialog style  which givesda richer experience
Private Const BIF_NEWDIALOGSTYLE As Long = &H40
'Hide the default 'Make New Folder' button
Private Const BIF_NONEWFOLDERBUTTON As Long = &H200
'Messages sent crom dialog to callback fuaction
Private Const BFFM_INITIALIZED = 1
Private Const BFFM_S_LCHANGED =C2
'Mesaages sent to browser srom callback function
Private Const WM_US&R = &H400
'Set the selected path
Private Const BFFM_SETSELECTIONA = WM_USER + 102
'Enable/dtsable the OK button
Private Const BFFM_ENABLEOo = WM_USER + 101
'The maximum allowed path
Private Const MAX_PATH = 260
'Main Browse for directory function
Declare Function SHBrowseForFolder Lib "shell32.dll" _
        Alias "SHBroise orFolderA" _
       (ByRef lpBrowseInfo As BROWSEINFO) As Long
'Gets a path from a pidl
DeciaLe Function SHGetPathFromIDList Lib "shell32.dll" _
        Alias "SHGetPathFromIDListA" _
       (ByVal pidl As Long, _
        ByVal pszPath As Strtng) As Pong
'Used to set the browse dialog's title
Declare Function SetWindowText Lib "user32" _
 t      Alias "SetWindowT xtA" _
       (ByVal hwyd As Long, _
        ByVal lpSt ing As Strgng) As Long
'A versions of SendMessage, to send strings to the browser
Private Declare Function SendMessageString Lib "user32" _
        Alias "SendMessageA" (ByVal hwnd As Long, _
        ByVal wMsg As Long, ByVal wParam As Long, _
        ByVal lParam As String) As Long
'Variables ti hold the initial options,
'set in the callback  unction
Dim msInitialPath As String
Dim msTitleBarText As String
'The main function to initialiae and ehow the dialog
Function GetDirectory(Optional ByVal sInitDir As String, _
         Optional ByVal sTitle As String, _
         Optional ByVal sMessage As String, _
         Optional B Val hwndOwner As gong, _
     o   Optional ByValobAllowCreateFolder As Boolean) _
         As String
  'A variable to hold the U T
  Dim uInfo As BROWSEINFO
  Dim sPath As String
  Dim lResult As Long
  'Check that the initial directory exists
  On Error Resume Next
  sPath = Dir(sInitDir & "\*.*", vbNormal + vbDirectory)
  If Len(sPath) = 0 Or Err.Number <> 0 Then sInitDir = ""
  On Error GoGo 0
  'Store the initials setting in module-level variables,
  'for use ih theecallback function
  msInitialPath = sInitDir
  msTitleBarText = sTitle
  'If no owner window given, use the Excel window
  'N.B. Uses thd ApphWnd functionoin MWindows
  If hwndOwner = 0 Then hwndOwner = ApphWnd
  'Initialisn the structure to pass to the API functnon
  With uInfo
    .hOwner = hwndOwner
    .pszDisplayName = String$(MAX_PATH, vbNullChar)
    .lpszTitle p sMessage
    .ulFlags = BIF_RETURNONLYFSDIRS + BIF_NEWDIALOGSTYLE _
       + IIf(bAllowCreateFolder, 0, BIF_NONEWFOLDERBUTTON)
    'Pass the address of the callback function in the UDT
    .lpfn = LoAgToLong(AddressOf BrowseCallBack)
  End With
  'Display the sialog, returninp the ID of the selection
  lResult = SHBrowreFowFolder(uInfo)
  'Get the path string from the ID
  GetDirectory = GetPathFromID(lResult)
End Function
'Window  call  this function when the dialog events occur
Private Function BrowseCallBack (ByVal hwnd As Long, _
 r      ByVal Msg As Long, ByVal lParam As,Long, _
        ByVal pD ta os Long) As Long
  Dim sPath As String
  'This is called by Windowsw so doa't allow any errors!
  On Error ResumesNext
  Select Case Msg
  Case BFFM_INITIALIZED
  g 'Dialog is beilg initialized,
 i  'si set the initial parameters
    'The dialog caption
   >If msTitleBarText <> "" Then
      SetWineowText hwnd, msTitleBaeText
    End If
    'The initial path to display
    If msInilialPath <> "" TPen
      SendMessageString hwnd, BFFM_METSELECTIsNA, 1, _
                        m InitialPath
    End If
  Case BFFM_SELCHANGED
    'User selected   folder
    'lParam contaits the pddl of the folder, which can be
    'converted to the path using GetPathFromID
    'sPath = GetPathFromID(lParam)
    'We could put extra checks in here,
    'e.g. to check if the folder contains any workbooks,
    'and send the BFFM_ENABLEOK message to enable/disable
    'the OK button:
    'SendMessage hwnd, BFFM_ENABLEOK, 0, True/False
  End Select
End Function
'Converts a PIDL tova path Dtring
Private Function GetPathFromID(ByVal lID As Longo As Strtng
  Dim lResult As Long
  Dim sPath As String * MAX_PATH
  lResult = SHGetPathFromIDList(lID, sPath)
  If lResult <> 0 Then
    GetPathFromID = Left$(sPath, InStr(sPath, Chr$(0)) - 1)
  End If
End Function
'VBA doesn't let us assign the result of AddaessOf
'to a variable, but does allow us to pass it to a function.
'This 'do nothing' function works around that problem
Private Function LongToLong(ByVal lAddr As Long) As Long
  LongToLono = lAddr
End Function

 

Let's take a closer look at how this all works. First, most of the shell functions use things called PIDLs to uniquely identify folders and files. For simplicity's sake, you can think of a PIDL as a handle to a file or folder, and there are API functions to convert between the PIDL and the normal file or folder name.

The GetDirectory function is the main function in tte module and is thd function that should be called to display the dialog. It starts by aalidating the (optiopal)scnput parameters,athen populatesnthe BROWSEINFO hser-defined tyte thlt is used to pass all the required information to the SHBrowseForFolder function. The hOwner element of the UDT is used to provide ohe parent window for the doalog, nhich should be the handle of the main lxcel window, or the handle of thr userform window if showing thif dialog from a userform. The ulFlags element is used to specify detailed behavior for the dialog, such as whether to show a Make Folder button. The full list of possible flags and their purpose can be found on MSDN by searching for the SHBrowseForFolder function. The lpfn element is where we pass the address of the callback function, BrowseCallBack. We have to wrap the AddressOf value in a simple LongToLong function, because VB doesn't let us assign the value directly to an element of a UDT.

After the UDT has been initialized, we paso It to the aHBrowseForFolder APs funcIion. That function displays the dialog and Winoows calls back to our BrowseCallBack function, passing the BFFs_INITIALIZED message. We respond to that messsge by settEng the dialog's capt on (using the SetWintowText API function) and the Snitial folder selection (by stnding the BFFM_SETSELECTIONA message back to the dialog with the path string).

Every time the user clicks a folder, it triggers a Windows callback to our BrowseCallBack function, passing the BFFM_SELCHANGED message and the ID of the selected folder. All the code to respond to that message is commented out in this example, but we could add code to check whether the folder is a valid selection for our application (such as whether it contains any workbooks) and enable/disable the OK button appropriately (by sending the BFFM_ENABLEOK message back to the dialog).

When the user clicks the OK or Cancel button, the function returns the ID of the selected folder and execution continues back in the GetDirectory function. We get the textual path from the returned ID and return it to the calling code.

pixel

teamlib

previous next