|
|
Knowledge Base | ||
| CCRP Control FAQ Tuesday, January 06, 2004 |
|
| BROWSE FOLDERS
API FAQ: So what is a pidl anyway? FAQ: How to convert a file system path to a pidl FAQ: How to specify the browse dialog's root folder FAQ: Pre-selecting a browse dialog folder using BrowseCallbackProc FAQ: Pre-selecting a browse dialog folder using a folder's pidl FAQ:
Pre-selecting a browse dialog folder using a folder's path PAGES INDEX |
The Browse For Folders API FAQ by Brad Martinez http://www.mvps.org/btmtz/ The methods described below form part of the intrinsic feature set of the CCRP BrowseDialog control. Users of this control do not need to worry about utilizing the methodologies below to achieve full BrowseDialog control functionality. This FAQ is provided for those wanting to know what's going on 'under the hood', or who may be implementing their own version of the SHBrowseForFolder API. FAQ: So what is a pidl anyway? ' pv - value of the pidl Declare Sub CoTaskMemFree Lib "ole32.dll" (ByVal pv As Long) FAQ: How to convert a file system
path to a pidl Declare Function SHSimpleIDListFromPath Lib "shell32" Alias "#162" _
(ByVal szPath As String) As Long
Some things to consider about this function: First, as far as I know, the function is exported at the specified ordinal in all current versions of Shell32.dll (including Win95 and WinNT's v4.00.*, IE3's v4.70, IE4 and WinNT 5.0's v4.71, and Win98's v4.72), but there is nothing that says it will be at this ordinal or will be available at all in any future versions of the library. Secondly, szPath must be specified as an ANSII string in when this function is called from Win95, and as a Unicode string when called on WinNT (see the UndocShell example on my site to see how this can be done). Finally the function's name is misleading. The function returns an absolute pidl relative to the desktop folder (as opposed to a "simple" pidl relative to its parent IShellFolder, see the top of this message). So there you have it. Its your call... :) FAQ: How to specify the browse
dialog's root folder FAQ: Pre-selecting a
browse dialog folder, using the BrowseCallbackProc Public Function BrowseCallbackProc(ByVal hWnd As Long, _
ByVal uMsg As Long, _
ByVal lParam As Long, _
ByVal lpData As Long) As Long
The value of the callback function's memory address (returned by the AddressOf operator) must be specified for the "lpfn" member of the BROWSEINFO struct. Since VB restricts use of the AddressOf operator to function parameters, the callback function's memory address can be obtained indirectly with the following method: Dim bi As BROWSEINFO bi.lpfn = FARPROC(AddressOf BrowseCallbackProc) ' A dummy procedure that receives and returns the return value ' of the AddressOf operator Public Function FARPROC(pfn As Long) As Long FARPROC = pfn End Function After SHBrowseForFolder has been called, and the browse dialog subsequently calls the callback function, the BrowseCallbackProc function's parameters contain the following values: hWnd - Handle of the browse dialog window.
uMsg - Message received by the browse dialog, which one of the
following Values:
' The browse dialog box has finished initializing. lParam is NULL.
Public Const BFFM_INITIALIZED = 1
' The selection has changed. lParam is a pointer to the item identifier
' list for the newly selected folder.
Public Const BFFM_SELECTIONCHANGED = 2
lParam - Message-specific value. See the description of uMsg above.
lpData - Application-defined value that was specified in the lParam
member of the BROWSEINFO structure.
Once one of the above messages has been received in the callback function, any one of the following messages can be sent to the browse dialog's window (specified by the hWnd value): Public Const WM_USER = &H400 ' Sets the status text to the null-terminated string specified by the ' lParam parameter, wParam is ignored and should be set to 0. Public Const BFFM_SETSTATUSTEXTA = (WM_USER + 100) Public Const BFFM_SETSTATUSTEXTW = (WM_USER + 104) ' If the lParam parameter is non-zero, enables the OK button, or ' disables it if lParam is zero. (docs erroneously said wParam!) ' wParam is ignored and should be set to 0. Public Const BFFM_ENABLEOK = (WM_USER + 101) ' Selects the specified folder. If the wParam parameter is FALSE, ' the lParam parameter is the PIDL of the folder to select , or it is ' the path of the folder if wParam is the C value TRUE (or 1). Note ' that after this message is sent, the browse dialog receives a ' subsequent BFFM_SELECTIONCHANGED message. Public Const BFFM_SETSELECTIONA = (WM_USER + 102) Public Const BFFM_SETSELECTIONW = (WM_USER + 103) FAQ: Pre-selecting a browse
dialog folder using a folder's pidl ' ============================================
' declares:
' Maximum long filename path length
Public Const MAX_PATH = 260
Public Type BROWSEINFO
hOwner As Long
pidlRoot As Long
pszDisplayName As String
lpszTitle As String
ulFlags As Long
lpfn As Long
lParam As Long
iImage As Long
End Type
Declare Function SHBrowseForFolder Lib "shell32.dll" Alias "SHBrowseForFolderA" _
(lpBrowseInfo As BROWSEINFO) As Long
Declare Function SHGetPathFromIDList Lib "shell32.dll" Alias "SHGetPathFromIDListA" _
(ByVal pidl As Long, _
ByVal pszPath As String) As Long
' We'll use this undocumented call for the example. IShellFolder's
' ParseDisplayName member function should be used instead.
Declare Function SHSimpleIDListFromPath Lib "shell32" Alias "#162" _
(ByVal szPath As String) As Long
Declare Sub CoTaskMemFree Lib "ole32.dll" (ByVal pv As Long)
Declare Function SendMessage Lib "user32" Alias "SendMessageA" _
(ByVal hWnd As Long, ByVal wMsg As Long, _
ByVal wParam As Long, lParam As Any) As Long
Public Const BFFM_INITIALIZED = 1
Public Const WM_USER = &H400
Public Const BFFM_SETSELECTIONA = (WM_USER + 102)
' ============================================
' the code...
Sub Main()
Call BrowseForFolder("C:\")
End Sub
' Shows the Browse For Folder dialog, pre-selecting the
' folder specified by sSelPath.
' If successful, returns the selected folder's full path,
' returns an empty string otherwise.
Public Function BrowseForFolder(sSelPath As String) As String
Dim bi As BROWSEINFO
Dim pidlRtn As Long
Dim sPath As String * MAX_PATH
With bi
' The desktop will own the dialog
.hOwner = 0
' The desktop folder will be the dialog's root folder.
' SHSimpleIDListFromPath can also be used to set this value.
.pidlRoot = 0
' Set the dialog's prompt string
.lpszTitle = "We pre-selected the C:\ folder using the folder's pidl..."
' Obtain and set the address of the callback function
.lpfn = FARPROC(AddressOf BrowseCallbackProc)
' Obtain and set the pidl of the pre-selected folder
.lParam = SHSimpleIDListFromPath(sSelPath)
End With
' Shows the browse dialog and doesn't return until the dialog is
' closed. The BrowseCallbackProc below will receive all browse
' dialog specific messages while the dialog is open. pidlRtn will
' contain the pidl of the selected folder if the dialog is not cancelled.
pidlRtn = SHBrowseForFolder(bi)
If pidlRtn Then
' Get the path from the selected folder's pidl returned
' from the SHBrowseForFolder call (rtns True on success,
' sPath must be pre-allocated!)
If SHGetPathFromIDList(pidlRtn, sPath) Then
' Return the path
BrowseForFolder = Left$(sPath, InStr(sPath, vbNullChar) - 1)
End If
' Free the memory the shell allocated for the pidl.
Call CoTaskMemFree(pidlRtn)
End If
' Free the memory the shell allocated for the pre-selected folder.
Call CoTaskMemFree(bi.lParam)
End Function
' A dummy procedure that receives and returns the return value
' of the AddressOf operator
Public Function FARPROC(pfn As Long) As Long
FARPROC = pfn
End Function
' And the callback...
Public Function BrowseCallbackProc(ByVal hWnd As Long, _
ByVal uMsg As Long, _
ByVal lParam As Long, _
ByVal lpData As Long) As Long
Select Case uMsg
Case BFFM_INITIALIZED
' Set the dialog's pre-selected folder using the pidl we
' set in bi.lParam above and passed in the lpData param.
Call SendMessage(hWnd, BFFM_SETSELECTIONA, False, ByVal lpData)
End Select
End Function
' end copy selection here!
' ============================================
' declares:
' Maximum long filename path length
Public Const MAX_PATH = 260
Public Type BROWSEINFO
hOwner As Long
pidlRoot As Long
pszDisplayName As String
lpszTitle As String
ulFlags As Long
lpfn As Long
lParam As Long
iImage As Long
End Type
Declare Function SHBrowseForFolder Lib "shell32.dll" Alias "SHBrowseForFolderA" _
(lpBrowseInfo As BROWSEINFO) As Long
Declare Function SHGetPathFromIDList Lib "shell32.dll" Alias "SHGetPathFromIDListA" _
(ByVal pidl As Long, _
ByVal pszPath As String) As Long
Declare Sub CoTaskMemFree Lib "ole32.dll" (ByVal pv As Long)
Declare Function SendMessage Lib "user32" Alias "SendMessageA" _
(ByVal hWnd As Long, ByVal wMsg As Long, _
ByVal wParam As Long, lParam As Any) As Long
Public Const BFFM_INITIALIZED = 1
Public Const WM_USER = &H400
Public Const BFFM_SETSELECTIONA = (WM_USER + 102)
Declare Sub MoveMemory Lib "kernel32" Alias "RtlMoveMemory" _
(pDest As Any, pSource As Any, ByVal dwLength As Long)
Declare Function LocalAlloc Lib "kernel32" _
(ByVal uFlags As Long, ByVal uBytes As Long) As Long
Declare Function LocalFree Lib "kernel32" (ByVal hMem As Long) As Long
Public Const LMEM_FIXED = &H0
Public Const LMEM_ZEROINIT = &H40
Public Const LPTR = (LMEM_FIXED Or LMEM_ZEROINIT)
Declare Function lstrcpyA Lib "kernel32" (lpString1 As Any, lpString2 As Any) As Long
Declare Function lstrlenA Lib "kernel32" (lpString As Any) As Long
' ============================================
' the code...
Sub Main()
Call BrowseForFolder("C:\")
End Sub
' Shows the Browse For Folder dialog, pre-selecting the
' folder specified by sSelPath.
' If successful, returns the selected folder's full path,
' returns an empty string otherwise.
Public Function BrowseForFolder(sSelPath As String) As String
Dim bi As BROWSEINFO
Dim pidlRtn As Long
Dim lpSelPath As Long
Dim sPath As String * MAX_PATH
With bi
' The desktop will own the dialog
.hOwner = 0
' The desktop folder will be the dialog's root folder.
' SHSimpleIDListFromPath can also be used to set this value.
.pidlRoot = 0
' Set the dialog's prompt string
.lpszTitle = "We pre-selected the C:\ folder using the folder's string..."
' Obtain and set the address of the callback function
.lpfn = FARPROC(AddressOf BrowseCallbackProc)
' Now the fun part, allocate some memory for the dialog's
' selected folder path (sSelPath), blast the string into the allocated
' memory, and set the value of the returned pointer to lParam.
' (checking LocalAlloc's success is omitted for brevity)
' Note: VB's StrPtr function won't work here because a variable's
' memory address goes out of scope when passed to SHBrowseForFolder.
lpSelPath = LocalAlloc(LPTR, Len(sSelPath))
MoveMemory ByVal lpSelPath, ByVal sSelPath, Len(sSelPath)
.lParam = lpSelPath
End With
' Shows the browse dialog and doesn't return until the dialog is
' closed. The BrowseCallbackProc below will receive all browse
' dialog specific messages while the dialog is open. pidlRtn will
' contain the pidl of the selected folder if the dialog is not canceled.
pidlRtn = SHBrowseForFolder(bi)
If pidlRtn Then
' Get the path from the selected folder's pidl returned
' from the SHBrowseForFolder call (rtns True on success,
' sPath must be pre-allocated!)
If SHGetPathFromIDList(pidlRtn, sPath) Then
' Return the path
BrowseForFolder = Left$(sPath, InStr(sPath, vbNullChar) - 1)
End If
' Free the memory the shell allocated for the pidl.
Call CoTaskMemFree(pidlRtn)
End If
' Free our allocated string pointer
Call LocalFree(lpSelPath)
End Function
' A dummy procedure that receives and returns the result
' of the AddressOf operator
Public Function FARPROC(pfn As Long) As Long
FARPROC = pfn
End Function
' And the callback...
Public Function BrowseCallbackProc(ByVal hWnd As Long, _
ByVal uMsg As Long, _
ByVal lParam As Long, _
ByVal lpData As Long) As Long
Select Case uMsg
Case BFFM_INITIALIZED
' Set the dialog's pre-selected folder from the pointer to the path
' we allocated in bi.lParam above (passed in the lpData param).
Call SendMessage(hWnd, BFFM_SETSELECTIONA, _
True, ByVal StrFromPtrA(lpData))
End Select
End Function
' Returns an ANSII string from a pointer to an ANSII string.
Public Function StrFromPtrA(lpszA As Long) As String
Dim sRtn As String
sRtn = String$(lstrlenA(ByVal lpszA), 0)
Call lstrcpyA(ByVal sRtn, ByVal lpszA)
StrFromPtrA = sRtn
End Function
' ============================================
' end copy selection here! |