This macro opens a folder using VBA. If the folder is already opened in a Windows Explorer window, it will show the open window instead of opening a new window.

All you have to do is copy and paste the OpenFolder VBA subroutine and pass the macro a string with the folder you want to open.

The OpenFolderDemo macro shows an example of how to call the subroutine. Play around with it by passing it things like Application.Path or ActiveWorkbook.Path.

July 2018 Update: The original OpenFolder macro would not restore a folder if it was previously minimized, but the new and improved macro published below will. This version was developed in response to a reader comment.


Open Folder Using VBA

'--------------------------------------------
Private Const SW_RESTORE = 9

#If VBA7 Then
    Private Declare PtrSafe Function ShowWindow Lib "user32" (ByVal hwnd As Long, ByVal nCmdShow As Long) As Long
    Private Declare PtrSafe Function IsIconic Lib "user32.dll" (ByVal hwnd As Long) As Long
#Else
    Private Declare Function ShowWindow Lib "user32" (ByVal hwnd As Long, ByVal nCmdShow As Long) As Long
    Private Declare Function IsIconic Lib "user32.dll" (ByVal hwnd As Long) As Long
#End If

Private Sub OpenFolder(strDirectory As String)
'DESCRIPTION: Open folder if not already open. Otherwise, activate the already opened window
'DEVELOPER: Ryan Wells (wellsr.com)
'INPUT: Pass the procedure a string representing the directory you want to open
Dim pID As Variant
Dim sh As Variant
On Error GoTo 102:
Set sh = CreateObject("shell.application")
For Each w In sh.Windows
    If w.Name = "Windows Explorer" Or w.Name = "File Explorer" Then
        If w.document.folder.self.Path = strDirectory Then
            'if already open, bring it front
            If CBool(IsIconic(w.hwnd)) Then ' If it's minimized, show it
                w.Visible = False
                w.Visible = True
                ShowWindow w.hwnd, SW_RESTORE
            Else
                w.Visible = False
                w.Visible = True
            End If
            Exit Sub
        End If
    End If
Next
'if you get here, the folder isn't open so open it
pID = Shell("explorer.exe " & strDirectory, vbNormalFocus)
102:
End Sub
Sub OpenFolderDemo()
'Demo - opens the folder location saved to the variable strPath
Dim strPath As String
strPath = "C:\Windows"
Call OpenFolder(strPath)
End Sub

Make powerful macros with our free VBA Developer Kit

It’s easy to copy and paste a macro like this, but it’s harder make one on your own. To help you make macros like this, we built a free VBA Developer Kit and wrote the Big Book of Excel VBA Macros full of hundreds of pre-built macros to help you master file I/O, arrays, strings and more - grab your free copy below.

I'll take a free VBA Developer Kit

This is the original macro, which will not restore a folder if it was previously minimized. I’m going to continue to include here for completeness.

Private Sub OpenFolder_old(strDirectory As String)
'DESCRIPTION: Open folder if not already open. Otherwise, activate the already opened window
'DEVELOPER: Ryan Wells (wellsr.com)
'INPUT: Pass the procedure a string representing the directory you want to open
Dim pID As Variant
Dim sh As Variant
On Error GoTo 102:
Set sh = CreateObject("shell.application")
For Each w In sh.Windows
    If w.Name = "Windows Explorer" Or w.Name = "File Explorer" Then
        If w.document.folder.self.Path = strDirectory Then
            'if already open, bring it front
            w.Visible = False
            w.Visible = True
            Exit Sub
        End If
    End If
Next
'if you get here, the folder isn't open so open it
pID = Shell("explorer.exe " & strDirectory, vbNormalFocus)
102:
End Sub

I hope you found this VBA Code Library example helpful. For more VBA tips, techniques, and tactics, subscribe to our VBA Insiders email series using the form below.