Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations TouchToneTommy on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Browse for folder

Folders and Files

Browse for folder

by  sunaj  Posted    (Edited  )
This FAQ describes how you can let the user browse and select a folder. The Commondialog lets the user browse the files, but does not have an option to browser for folders.

Here is 2 methods that you can use. I suggest that you use the 1st, since the 2nd is slow if you have many folders on your disk(s)/network drives. On the other hand method 2 can be customized to show subsections of the disk(s) etc.

Method 1:
Use the Windows API to show the 'Browse for Folder' dialog.
Don't let all the code intimidate you, simply copy everything into a module (.bas) in your project and call the BrowseForFolder function to display the dialog (modally). The function will return the full path.


'--------------------------------------------------------------
Option Explicit

'--------------Start "browse for folder" declarations------------
Private Const BIF_STATUSTEXT = &H4&
Private Const BIF_RETURNONLYFSDIRS = 1
Private Const BIF_DONTGOBELOWDOMAIN = 2
Private Const MAX_PATH = 260

Private Const WM_USER = &H400
Private Const BFFM_INITIALIZED = 1
Private Const BFFM_SELCHANGED = 2
Private Const BFFM_SETSTATUSTEXT = (WM_USER + 100)
Private Const BFFM_SETSELECTION = (WM_USER + 102)

Private Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As String) As Long
Private Declare Function SHBrowseForFolder Lib "shell32" (lpbi As BrowseInfo) As Long
Private Declare Function SHGetPathFromIDList Lib "shell32" (ByVal pidList As Long, ByVal lpBuffer As String) As Long
Private Declare Function lstrcat Lib "kernel32" Alias "lstrcatA" (ByVal lpString1 As String, ByVal lpString2 As String) As Long

Private Type BrowseInfo
hWndOwner As Long
pIDLRoot As Long
pszDisplayName As Long
lpszTitle As Long
ulFlags As Long
lpfnCallback As Long
lParam As Long
iImage As Long
End Type

Private m_CurrentDirectory As String 'The current directory
'-----End "Browse for folder" declarations----



'-------------Handle "browser for folder dialog----------
Public Function BrowseForFolder(owner As Form, Title As String, StartDir As String) As String
'Opens a Treeview control that displays the directories in a computer

Dim lpIDList As Long
Dim szTitle As String
Dim sBuffer As String
Dim tBrowseInfo As BrowseInfo
m_CurrentDirectory = StartDir & vbNullChar

szTitle = Title
With tBrowseInfo
.hWndOwner = owner.hwnd
.lpszTitle = lstrcat(szTitle, "")
.ulFlags = BIF_RETURNONLYFSDIRS + BIF_DONTGOBELOWDOMAIN + BIF_STATUSTEXT
.lpfnCallback = GetAddressofFunction(AddressOf BrowseCallbackProc) 'get address of function.
End With

lpIDList = SHBrowseForFolder(tBrowseInfo)
If (lpIDList) Then
sBuffer = Space(MAX_PATH)
SHGetPathFromIDList lpIDList, sBuffer
sBuffer = Left(sBuffer, InStr(sBuffer, vbNullChar) - 1)
BrowseForFolder = sBuffer
Else
BrowseForFolder = ""
End If

End Function


Private Function BrowseCallbackProc(ByVal hwnd As Long, ByVal uMsg As Long, ByVal lp As Long, ByVal pData As Long) As Long

Dim lpIDList As Long
Dim ret As Long
Dim sBuffer As String

On Error Resume Next 'Sugested by MS to prevent an error from
'propagating back into the calling process.

Select Case uMsg

Case BFFM_INITIALIZED
Call SendMessage(hwnd, BFFM_SETSELECTION, 1, m_CurrentDirectory)

Case BFFM_SELCHANGED
sBuffer = Space(MAX_PATH)

ret = SHGetPathFromIDList(lp, sBuffer)
If ret = 1 Then
Call SendMessage(hwnd, BFFM_SETSTATUSTEXT, 0, sBuffer)
End If

End Select

BrowseCallbackProc = 0

End Function

' This function allows you to assign a function pointer to a vaiable.
Private Function GetAddressofFunction(add As Long) As Long
GetAddressofFunction = add
End Function
'-------------End handle "browser for folder" dialog----------

Method 2:
Make your own 'Browse for folder', by placing a treeview on a form and load the folder stucture into the treeview. Below is shown how you can populate a treeview with the folder stucture of your disk(s)/network drives. The population of the treeview is, however, slow and therefore only practical if the file structure is not too large.

---------------------------------------------------------------
Option Explicit

'Place a treeview and a command button on a form.
Dim LocalFileSystem
Dim ADrive As Variant

Private Sub Command1_Click()
MsgBox (TreeView1.SelectedItem)
End Sub

Function AddFolder(Node As String)
Dim AFolder As Variant, TheFolders As Variant
Set TheFolders = LocalFileSystem.GetFolder(Node)
For Each AFolder In TheFolders.SubFolders
TreeView1.Nodes.Add Node, tvwChild, AFolder, AFolder
AddFolder (AFolder)
Next
DoEvents
End Function

Private Sub Form_Load()
Set LocalFileSystem = CreateObject("Scripting.FileSystemObject")
For Each ADrive In LocalFileSystem.Drives
If ADrive.IsReady Then
TreeView1.Nodes.Add , , ADrive.driveletter & ":\", ADrive
AddFolder (ADrive.driveletter & ":\")
End If
Next ADrive
End Sub
Register to rate this FAQ  : BAD 1 2 3 4 5 6 7 8 9 10 GOOD
Please Note: 1 is Bad, 10 is Good :-)

Part and Inventory Search

Back
Top