Dir Function for File Operations

Maintained on

The Dir function is one of the most fundamental and essential functions when working with files and folders in VBA. It’s indispensable for tasks like retrieving file lists from specific folders or checking file existence.

This article covers everything from basic usage to advanced techniques, including comparisons with FileSystemObject, accompanied by practical code examples.

When You Need the Dir Function

In practice, you’ll use the Dir function in situations like these:

  • Batch processing multiple files: Open all Excel files in a folder for data aggregation
  • File existence checks: Verify a specific file exists before processing
  • Creating backup files: Add sequential numbers when saving if a file already exists
  • Log file management: Delete old log files
  • Report generation: Search for files matching a specific pattern and create a list
  • Data migration: Import all CSV files from a folder

Dir Function Basics

Basic Syntax

Dir([pathname], [attributes])

The Dir function returns the name of the first file or folder that matches the specified pattern.

Simplest Usage

dir_basic.bas
Sub DirBasic()
    Dim fileName As String

    ' Get the first file in the current folder
    fileName = Dir("*.*")

    Debug.Print "First file: " & fileName
End Sub
チェック

When calling Dir for the first time, specify the path. For subsequent calls, call it without arguments to get the next file.

Retrieving a File List

dir_file_list.bas
Sub GetFileList()
    Dim folderPath As String
    Dim fileName As String

    ' Specify the folder path
    folderPath = "C:\Users\YourName\Documents\"

    ' Get the first file
    fileName = Dir(folderPath & "*.*")

    ' Loop through all files
    Do While fileName <> ""
        Debug.Print fileName

        ' Get the next file
        fileName = Dir()
    Loop
End Sub
チェック

The Dir function requires a path on the first call, then call Dir() without arguments to retrieve the next file with the same search criteria. It returns an empty string ("") when all files have been retrieved.

Using Wildcards

The Dir function supports pattern matching with wildcards (* and ?):

  • * (asterisk): Matches zero or more of any characters
  • ? (question mark): Matches any single character
dir_wildcards.bas
Sub WildcardExamples()
    Dim fileName As String
    Dim folderPath As String

    folderPath = "C:\Data\"

    ' All files
    Debug.Print "=== All Files ==="
    fileName = Dir(folderPath & "*.*")
    Do While fileName <> ""
        Debug.Print fileName
        fileName = Dir()
    Loop

    ' Excel files only
    Debug.Print "=== Excel Files ==="
    fileName = Dir(folderPath & "*.xlsx")
    Do While fileName <> ""
        Debug.Print fileName
        fileName = Dir()
    Loop

    ' Specific pattern (files starting with Report_)
    Debug.Print "=== Report_* ==="
    fileName = Dir(folderPath & "Report_*.xlsx")
    Do While fileName <> ""
        Debug.Print fileName
        fileName = Dir()
    Loop

    ' 3-character file names
    Debug.Print "=== 3-Character Names ==="
    fileName = Dir(folderPath & "???.txt")
    Do While fileName <> ""
        Debug.Print fileName
        fileName = Dir()
    Loop
End Sub

Processing Files by Extension

Listing Excel Files

dir_excel_files.bas
Sub GetExcelFiles()
    Dim folderPath As String
    Dim fileName As String
    Dim fileCount As Integer

    folderPath = "C:\Reports\"
    fileCount = 0

    ' Search for .xlsx files
    fileName = Dir(folderPath & "*.xlsx")

    Do While fileName <> ""
        fileCount = fileCount + 1
        Debug.Print fileCount & ": " & fileName
        fileName = Dir()
    Loop

    ' Include .xlsm files as well
    Debug.Print "=== Macro-Enabled Files ==="
    fileName = Dir(folderPath & "*.xlsm")

    Do While fileName <> ""
        fileCount = fileCount + 1
        Debug.Print fileCount & ": " & fileName
        fileName = Dir()
    Loop

    MsgBox "Total: " & fileCount & " Excel files", vbInformation
End Sub

Processing Multiple Extensions

dir_multiple_extensions.bas
Sub ProcessMultipleExtensions()
    Dim folderPath As String
    Dim extensions() As Variant
    Dim ext As Variant
    Dim fileName As String

    folderPath = "C:\Documents\"
    extensions = Array("*.xlsx", "*.xlsm", "*.xls", "*.csv")

    For Each ext In extensions
        Debug.Print "=== " & ext & " ==="
        fileName = Dir(folderPath & ext)

        Do While fileName <> ""
            Debug.Print fileName
            fileName = Dir()
        Loop
    Next ext
End Sub

Checking File Existence

Basic Existence Check

dir_file_exists.bas
Function FileExists(filePath As String) As Boolean
    ' Returns True if file exists, False otherwise
    FileExists = (Dir(filePath) <> "")
End Function

Sub TestFileExists()
    Dim testPath As String
    testPath = "C:\Temp\sample.xlsx"

    If FileExists(testPath) Then
        MsgBox "File exists!", vbInformation
    Else
        MsgBox "File not found.", vbExclamation
    End If
End Sub

Creating Backup Files with Sequential Numbers

dir_backup_sequential.bas
Function GetNextBackupFileName(basePath As String, baseName As String, ext As String) As String
    Dim counter As Integer
    Dim testFileName As String

    counter = 1

    Do
        testFileName = basePath & baseName & "_" & Format(counter, "000") & ext

        If Dir(testFileName) = "" Then
            ' File doesn't exist, we can use this name
            GetNextBackupFileName = testFileName
            Exit Function
        End If

        counter = counter + 1
    Loop While counter < 1000

    ' Maximum limit reached
    GetNextBackupFileName = ""
End Function

Sub CreateBackup()
    Dim backupPath As String
    backupPath = GetNextBackupFileName("C:\Backup\", "data", ".xlsx")

    If backupPath <> "" Then
        ' Copy file to backup path
        Debug.Print "Backup file: " & backupPath
    Else
        MsgBox "Unable to create backup file.", vbCritical
    End If
End Sub

Working with Folders

Using File Attributes

The Dir function can retrieve folder names using the vbDirectory attribute:

dir_folders.bas
Sub GetFolders()
    Dim folderPath As String
    Dim itemName As String

    folderPath = "C:\Users\YourName\"

    ' Get files and folders with vbDirectory attribute
    itemName = Dir(folderPath & "*", vbDirectory)

    Do While itemName <> ""
        ' Check if it's a directory
        If (GetAttr(folderPath & itemName) And vbDirectory) = vbDirectory Then
            ' Skip . and ..
            If itemName <> "." And itemName <> ".." Then
                Debug.Print "[Folder] " & itemName
            End If
        Else
            Debug.Print "[File] " & itemName
        End If

        itemName = Dir()
    Loop
End Sub
チェック

When using vbDirectory, both files and folders are returned. You need to check each item with GetAttr to determine whether it’s a folder.

Practical Examples

Collecting All Excel Files for Summary

dir_collect_data.bas
Sub CollectExcelData()
    Dim folderPath As String
    Dim fileName As String
    Dim wb As Workbook
    Dim summarySheet As Worksheet
    Dim outputRow As Long

    folderPath = "C:\MonthlyReports\"
    Set summarySheet = ThisWorkbook.Sheets("Summary")
    outputRow = 2

    ' Get Excel files
    fileName = Dir(folderPath & "*.xlsx")

    Application.ScreenUpdating = False

    Do While fileName <> ""
        ' Open the workbook
        Set wb = Workbooks.Open(folderPath & fileName, ReadOnly:=True)

        ' Copy data (example: value from cell A1)
        summarySheet.Cells(outputRow, 1).Value = fileName
        summarySheet.Cells(outputRow, 2).Value = wb.Sheets(1).Range("A1").Value

        ' Close the workbook
        wb.Close SaveChanges:=False

        outputRow = outputRow + 1
        fileName = Dir()
    Loop

    Application.ScreenUpdating = True
    MsgBox "Data collection complete!", vbInformation
End Sub

Deleting Old Files

dir_delete_old_files.bas
Sub DeleteOldFiles()
    Dim folderPath As String
    Dim fileName As String
    Dim filePath As String
    Dim fileDate As Date
    Dim cutoffDate As Date
    Dim deleteCount As Integer

    folderPath = "C:\Logs\"
    cutoffDate = Date - 30  ' Delete files older than 30 days
    deleteCount = 0

    fileName = Dir(folderPath & "*.log")

    Do While fileName <> ""
        filePath = folderPath & fileName
        fileDate = FileDateTime(filePath)

        If fileDate < cutoffDate Then
            Kill filePath
            deleteCount = deleteCount + 1
            Debug.Print "Deleted: " & fileName
        End If

        fileName = Dir()
    Loop

    MsgBox deleteCount & " files deleted.", vbInformation
End Sub

Dir Function vs FileSystemObject

FeatureDir FunctionFileSystemObject
Reference SetupNot requiredRecommended
SpeedFastSlightly slower
FunctionalityLimitedRich
Recursive subfolder supportManual implementation neededBuilt-in methods
File informationBasic onlyDetailed
Memory usageLowHigher

When to Use Which?

Use Dir Function when:

  • Simple file list retrieval
  • File existence checks
  • Quick, lightweight processing needed
  • Avoiding reference setup

Use FileSystemObject when:

  • Detailed file information needed
  • Recursive subfolder processing
  • Text file read/write operations
  • Complex file operations required

Summary

The Dir function is a powerful yet simple tool in VBA for file operations. Key points:

  • Pattern matching with wildcards (*, ?)
  • Call once with path, then without arguments for subsequent files
  • Returns empty string when no more files found
  • Use with vbDirectory for folder handling (requires GetAttr check)
  • For complex operations, consider FileSystemObject

Master these basics to efficiently handle various file operations in your VBA projects.

#VBA #Dir Function #File Operations #Folder Operations #FileSystemObject