Select Folder from Dialog Box

B

BillCPA

Is there a way to display a dialog box of folders and files and return a
Folder Name to the VBA code (instead of a file name)?
 
D

David Horowitz

Bill,
I don't think you can using the standard VBA means.
I did find some code on the internet at
http://www.codeguru.com/forum/showthread.php?s=&threadid=209798
which I modified very slightly and works pretty well.
You need to put it into a code module, can't be in ThisDocument.
HTH.
'-------------CODE------------
'This module contains all the declarations to use the
'Windows 95 Shell API to use the browse for folders
'dialog box. To use the browse for folders dialog box,
'please call the BrowseForFolders function using the
'syntax: stringFolderPath=BrowseForFolders(Hwnd,TitleOfDialog)
'
'For contacting information, see other module

Option Explicit

Public 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

Public Const BIF_RETURNONLYFSDIRS = 1
Public Const MAX_PATH = 260

Public Declare Sub CoTaskMemFree Lib "ole32.dll" (ByVal hMem As Long)
Public Declare Function lstrcat Lib "kernel32" Alias "lstrcatA" (ByVal
lpString1 As String, ByVal lpString2 As String) As Long
Public Declare Function SHBrowseForFolder Lib "shell32" (lpbi As BrowseInfo)
As Long
Public Declare Function SHGetPathFromIDList Lib "shell32" (ByVal pidList As
Long, ByVal lpBuffer As String) As Long

Public Function BrowseForFolder(hwndOwner As Long, sPrompt As String) As
String

'declare variables to be used
Dim iNull As Integer
Dim lpIDList As Long
Dim lResult As Long
Dim sPath As String
Dim udtBI As BrowseInfo

'initialise variables
With udtBI
.hwndOwner = hwndOwner
.lpszTitle = lstrcat(sPrompt, "")
.ulFlags = BIF_RETURNONLYFSDIRS
End With

'Call the browse for folder API
lpIDList = SHBrowseForFolder(udtBI)

'get the resulting string path
If lpIDList Then
sPath = String$(MAX_PATH, 0)
lResult = SHGetPathFromIDList(lpIDList, sPath)
Call CoTaskMemFree(lpIDList)
iNull = InStr(sPath, vbNullChar)
If iNull Then sPath = Left$(sPath, iNull - 1)
End If

'If cancel was pressed, sPath = ""
BrowseForFolder = sPath

End Function

' Here's where we call it.
Sub ShowIt()
MsgBox BrowseForFolder(0, "Please select a folder.")
End Sub
'--------END OF CODE----------
I didn't specify the HWnd parameter - if that's important to you, you can
use it.
 
B

BillCPA

That was really nice of you to do that - thanks.

I won't get to play with it until tomorrow, but I'll post what happens.
 
S

Steve Yandl

Below is an example that might do what you want. The only hitch is that
because it's a file picker, the user must pick a file and then the parent
folder will be determined. You could use the msoFileDialogFolderPicker to
do that but then you don't see the contained files in each folder. In the
case of the Shell.Application's browseforfolder, you can include files with
a folder picker but selecting a file rather than a folder will return an
error.

'------------------------------------

Sub GetFolderFromDialog()

Dim fd As FileDialog
Dim vrtSelectedItem As Variant
Dim strPathName As String
Dim strMyDocsPath As String

Set fso = CreateObject("Scripting.FileSystemObject")

' Determine Path to MyDocuments Folder
Set objShell = CreateObject("Shell.Application")
Set objMyDocsFldr = objShell.Namespace(&H5&)
strMyDocsPath = objMyDocsFldr.Self.Path

Set fd = Application.FileDialog(msoFileDialogFilePicker)

With fd
.Filters.Clear
.InitialFileName = strMyDocsPath
.AllowMultiSelect = False
.ButtonName = "Select..."
If .Show = -1 Then
vrtSelectedItem = .SelectedItems(1)
End If
End With

MsgBox fso.GetParentFolderName(vrtSelectedItem)

Set fd = Nothing
Set objMyDocsFldr = Nothing
Set objShell = Nothing
Set fso = Nothing

End Sub
'-----------------------------------

Steve Yandl
 
D

David Horowitz

Bill, Steve's got a good solution there too --- need to know more about what
you want the user to see - do you want the user to see files or only files?
If they can see files, do you want them to select a file or a folder?
If all you want is to get the folder name from the selected file, that could
be simple...
Let us know when you get back to it tomorrow.
 
L

Laura Leader

David,

That code is a life saver for me today. Thanks so much for posting this!

Laura Leader



David Horowitz wrote:

Bill,I don't think you can using the standard VBA means.
01-Apr-09

Bill,
I don't think you can using the standard VBA means.
I did find some code on the internet at
http://www.codeguru.com/forum/showthread.php?s=&threadid=209798
which I modified very slightly and works pretty well.
You need to put it into a code module, can't be in ThisDocument.
HTH.
'-------------CODE------------
'This module contains all the declarations to use the
'Windows 95 Shell API to use the browse for folders
'dialog box. To use the browse for folders dialog box,
'please call the BrowseForFolders function using the
'syntax: stringFolderPath=BrowseForFolders(Hwnd,TitleOfDialog)
'
'For contacting information, see other module

Option Explicit

Public 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

Public Const BIF_RETURNONLYFSDIRS = 1
Public Const MAX_PATH = 260

Public Declare Sub CoTaskMemFree Lib "ole32.dll" (ByVal hMem As Long)
Public Declare Function lstrcat Lib "kernel32" Alias "lstrcatA" (ByVal
lpString1 As String, ByVal lpString2 As String) As Long
Public Declare Function SHBrowseForFolder Lib "shell32" (lpbi As BrowseInfo)
As Long
Public Declare Function SHGetPathFromIDList Lib "shell32" (ByVal pidList As
Long, ByVal lpBuffer As String) As Long

Public Function BrowseForFolder(hwndOwner As Long, sPrompt As String) As
String

'declare variables to be used
Dim iNull As Integer
Dim lpIDList As Long
Dim lResult As Long
Dim sPath As String
Dim udtBI As BrowseInfo

'initialise variables
With udtBI
.hwndOwner = hwndOwner
.lpszTitle = lstrcat(sPrompt, "")
.ulFlags = BIF_RETURNONLYFSDIRS
End With

'Call the browse for folder API
lpIDList = SHBrowseForFolder(udtBI)

'get the resulting string path
If lpIDList Then
sPath = String$(MAX_PATH, 0)
lResult = SHGetPathFromIDList(lpIDList, sPath)
Call CoTaskMemFree(lpIDList)
iNull = InStr(sPath, vbNullChar)
If iNull Then sPath = Left$(sPath, iNull - 1)
End If

'If cancel was pressed, sPath = ""
BrowseForFolder = sPath

End Function

' Here's where we call it.
Sub ShowIt()
MsgBox BrowseForFolder(0, "Please select a folder.")
End Sub
'--------END OF CODE----------
I didn't specify the HWnd parameter - if that's important to you, you can
use it.
--
David Horowitz
Lead Technologist
Soundside Inc.
www.soundside.biz

Previous Posts In This Thread:

Select Folder from Dialog Box
Is there a way to display a dialog box of folders and files and return a
Folder Name to the VBA code (instead of a file name)?

--
Bill @ UAMS

Bill,I don't think you can using the standard VBA means.
Bill,
I don't think you can using the standard VBA means.
I did find some code on the internet at
http://www.codeguru.com/forum/showthread.php?s=&threadid=209798
which I modified very slightly and works pretty well.
You need to put it into a code module, can't be in ThisDocument.
HTH.
'-------------CODE------------
'This module contains all the declarations to use the
'Windows 95 Shell API to use the browse for folders
'dialog box. To use the browse for folders dialog box,
'please call the BrowseForFolders function using the
'syntax: stringFolderPath=BrowseForFolders(Hwnd,TitleOfDialog)
'
'For contacting information, see other module

Option Explicit

Public 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

Public Const BIF_RETURNONLYFSDIRS = 1
Public Const MAX_PATH = 260

Public Declare Sub CoTaskMemFree Lib "ole32.dll" (ByVal hMem As Long)
Public Declare Function lstrcat Lib "kernel32" Alias "lstrcatA" (ByVal
lpString1 As String, ByVal lpString2 As String) As Long
Public Declare Function SHBrowseForFolder Lib "shell32" (lpbi As BrowseInfo)
As Long
Public Declare Function SHGetPathFromIDList Lib "shell32" (ByVal pidList As
Long, ByVal lpBuffer As String) As Long

Public Function BrowseForFolder(hwndOwner As Long, sPrompt As String) As
String

'declare variables to be used
Dim iNull As Integer
Dim lpIDList As Long
Dim lResult As Long
Dim sPath As String
Dim udtBI As BrowseInfo

'initialise variables
With udtBI
.hwndOwner = hwndOwner
.lpszTitle = lstrcat(sPrompt, "")
.ulFlags = BIF_RETURNONLYFSDIRS
End With

'Call the browse for folder API
lpIDList = SHBrowseForFolder(udtBI)

'get the resulting string path
If lpIDList Then
sPath = String$(MAX_PATH, 0)
lResult = SHGetPathFromIDList(lpIDList, sPath)
Call CoTaskMemFree(lpIDList)
iNull = InStr(sPath, vbNullChar)
If iNull Then sPath = Left$(sPath, iNull - 1)
End If

'If cancel was pressed, sPath = ""
BrowseForFolder = sPath

End Function

' Here's where we call it.
Sub ShowIt()
MsgBox BrowseForFolder(0, "Please select a folder.")
End Sub
'--------END OF CODE----------
I didn't specify the HWnd parameter - if that's important to you, you can
use it.
--
David Horowitz
Lead Technologist
Soundside Inc.
www.soundside.biz

That was really nice of you to do that - thanks.
That was really nice of you to do that - thanks.

I will not get to play with it until tomorrow, but I will post what happens.

--
Bill @ UAMS


:

Below is an example that might do what you want.
Below is an example that might do what you want. The only hitch is that
because it's a file picker, the user must pick a file and then the parent
folder will be determined. You could use the msoFileDialogFolderPicker to
do that but then you don't see the contained files in each folder. In the
case of the Shell.Application's browseforfolder, you can include files with
a folder picker but selecting a file rather than a folder will return an
error.

'------------------------------------

Sub GetFolderFromDialog()

Dim fd As FileDialog
Dim vrtSelectedItem As Variant
Dim strPathName As String
Dim strMyDocsPath As String

Set fso = CreateObject("Scripting.FileSystemObject")

' Determine Path to MyDocuments Folder
Set objShell = CreateObject("Shell.Application")
Set objMyDocsFldr = objShell.Namespace(&H5&)
strMyDocsPath = objMyDocsFldr.Self.Path

Set fd = Application.FileDialog(msoFileDialogFilePicker)

With fd
.Filters.Clear
.InitialFileName = strMyDocsPath
.AllowMultiSelect = False
.ButtonName = "Select..."
If .Show = -1 Then
vrtSelectedItem = .SelectedItems(1)
End If
End With

MsgBox fso.GetParentFolderName(vrtSelectedItem)

Set fd = Nothing
Set objMyDocsFldr = Nothing
Set objShell = Nothing
Set fso = Nothing

End Sub
'-----------------------------------

Steve Yandl




Bill, Steve's got a good solution there too --- need to know more about what
Bill, Steve's got a good solution there too --- need to know more about what
you want the user to see - do you want the user to see files or only files?
If they can see files, do you want them to select a file or a folder?
If all you want is to get the folder name from the selected file, that could
be simple...
Let us know when you get back to it tomorrow.
--
David Horowitz
Lead Technologist
Soundside Inc.
www.soundside.biz


Submitted via EggHeadCafe - Software Developer Portal of Choice
Join Lists with LINQ - SharePoint 2010
http://www.eggheadcafe.com/tutorial...6e-7d3fb7d38eca/join-lists-with-linq--sh.aspx
 
D

David Horowitz

Laura, thanks for making good use of it (from about a year ago! - ah, the
internet!).
I re-read it, and I wonder if the standard Word FileDialog would have worked
for Bill, something using
Application.FileDialog(msoFileDialogFolderPicker)
It's different than the BrowseForFolder dialog, but works equally well and
without all the Win32 API code.
Dave
 

Ask a Question

Want to reply to this thread or ask your own question?

You'll need to choose a username for the site, which only take a couple of moments. After that, you can post your question and our members will help you out.

Ask a Question

Top