FileSystemObject

Maintained on

While VBA offers traditional functions like Dir and statements like Kill for file and folder operations, FileSystemObject (FSO) provides a more powerful and flexible approach.

This article explains everything from the basics to practical applications of FileSystemObject in a beginner-friendly way.

What is FileSystemObject?

FileSystemObject is an object for accessing the Windows file system. It’s part of the Microsoft Scripting Runtime library and provides a unified interface for creating, deleting, copying, moving, and reading/writing files and folders.

Key Features of FileSystemObject

  • Object-oriented: Treats files and folders as objects
  • Feature-rich: Supports virtually all file and folder operations
  • Text file handling: Simple reading and writing of text files
  • Error handling: Provides detailed error information
  • Cross-platform: Shares the same object model with Windows Script Host

Comparison with Traditional VBA Functions

OperationTraditional MethodFileSystemObject
File existence checkDir functionFileExists method
Delete fileKill statementDeleteFile method
Create folderMkDir statementCreateFolder method
Read textLine Input #ReadLine method
Get file attributesGetAttr functionFile.Attributes property
About Reference Setup

While setting a reference to “Microsoft Scripting Runtime” is recommended for FileSystemObject, you can also use it without reference setup by using CreateObject("Scripting.FileSystemObject").

Basic Usage of FileSystemObject

Creating an Instance

To use FileSystemObject, you first need to create an instance.

Using Reference Setup

In the VBA Editor, go to Tools → References and check “Microsoft Scripting Runtime”.

Using
Dim fso As Scripting.FileSystemObject
Set fso = New Scripting.FileSystemObject

' Your code here...

' Cleanup
Set fso = Nothing

This method works without reference setup, making it more portable across different environments.

Using
Dim fso As Object
Set fso = CreateObject("Scripting.FileSystemObject")

' Your code here...

' Cleanup
Set fso = Nothing
Recommended Approach

Using CreateObject is recommended unless you have a specific reason otherwise, as it doesn’t require reference setup and works across different environments.

File Operations

Checking File Existence

Check
Sub CheckFileExists()
    Dim fso As Object
    Set fso = CreateObject("Scripting.FileSystemObject")

    Dim filePath As String
    filePath = "C:\Temp\sample.txt"

    If fso.FileExists(filePath) Then
        MsgBox "File exists"
    Else
        MsgBox "File does not exist"
    End If

    Set fso = Nothing
End Sub

Copying Files

Copy
Sub CopyFile()
    Dim fso As Object
    Set fso = CreateObject("Scripting.FileSystemObject")

    Dim sourceFile As String
    Dim destFile As String

    sourceFile = "C:\Temp\original.xlsx"
    destFile = "C:\Backup\copy.xlsx"

    ' Copy file (True allows overwrite)
    fso.CopyFile sourceFile, destFile, True

    MsgBox "File copied successfully"

    Set fso = Nothing
End Sub

Moving Files

Move
Sub MoveFile()
    Dim fso As Object
    Set fso = CreateObject("Scripting.FileSystemObject")

    Dim sourceFile As String
    Dim destFile As String

    sourceFile = "C:\Temp\file.txt"
    destFile = "C:\Archive\file.txt"

    ' Move file
    fso.MoveFile sourceFile, destFile

    MsgBox "File moved successfully"

    Set fso = Nothing
End Sub

Deleting Files

Delete
Sub DeleteFile()
    Dim fso As Object
    Set fso = CreateObject("Scripting.FileSystemObject")

    Dim filePath As String
    filePath = "C:\Temp\delete_me.txt"

    If fso.FileExists(filePath) Then
        ' Delete file (True forces deletion)
        fso.DeleteFile filePath, True
        MsgBox "File deleted successfully"
    Else
        MsgBox "File does not exist"
    End If

    Set fso = Nothing
End Sub
Deletion is Permanent

When you delete a file with DeleteFile, it’s permanently deleted and not moved to the Recycle Bin. Always include confirmation before execution.

Getting File Information

Get
Sub GetFileInfo()
    Dim fso As Object
    Set fso = CreateObject("Scripting.FileSystemObject")

    Dim filePath As String
    filePath = "C:\Temp\sample.xlsx"

    If fso.FileExists(filePath) Then
        Dim file As Object
        Set file = fso.GetFile(filePath)

        Debug.Print "File Name: " & file.Name
        Debug.Print "Path: " & file.Path
        Debug.Print "Size: " & file.Size & " bytes"
        Debug.Print "Created: " & file.DateCreated
        Debug.Print "Modified: " & file.DateLastModified
        Debug.Print "Accessed: " & file.DateLastAccessed

        Set file = Nothing
    End If

    Set fso = Nothing
End Sub

Folder Operations

Creating Folders

Create
Sub CreateFolder()
    Dim fso As Object
    Set fso = CreateObject("Scripting.FileSystemObject")

    Dim folderPath As String
    folderPath = "C:\Temp\NewFolder"

    If Not fso.FolderExists(folderPath) Then
        fso.CreateFolder folderPath
        MsgBox "Folder created successfully"
    Else
        MsgBox "Folder already exists"
    End If

    Set fso = Nothing
End Sub

Creating Nested Folders

Create
Sub CreateNestedFolders()
    Dim fso As Object
    Set fso = CreateObject("Scripting.FileSystemObject")

    Dim basePath As String
    Dim folders() As Variant
    Dim currentPath As String
    Dim i As Integer

    basePath = "C:\Projects"
    folders = Array("2025", "Reports", "Monthly")
    currentPath = basePath

    For i = LBound(folders) To UBound(folders)
        currentPath = currentPath & "\" & folders(i)

        If Not fso.FolderExists(currentPath) Then
            fso.CreateFolder currentPath
        End If
    Next i

    MsgBox "Folder structure created: " & currentPath

    Set fso = Nothing
End Sub

Deleting Folders

Delete
Sub DeleteFolder()
    Dim fso As Object
    Set fso = CreateObject("Scripting.FileSystemObject")

    Dim folderPath As String
    folderPath = "C:\Temp\OldFolder"

    If fso.FolderExists(folderPath) Then
        ' True deletes even if folder contains files
        fso.DeleteFolder folderPath, True
        MsgBox "Folder deleted successfully"
    Else
        MsgBox "Folder does not exist"
    End If

    Set fso = Nothing
End Sub

Listing Folder Contents

List
Sub ListFolderContents()
    Dim fso As Object
    Set fso = CreateObject("Scripting.FileSystemObject")

    Dim folderPath As String
    Dim folder As Object
    Dim file As Object
    Dim subFolder As Object

    folderPath = "C:\Documents"

    If fso.FolderExists(folderPath) Then
        Set folder = fso.GetFolder(folderPath)

        ' List files
        Debug.Print "=== Files ==="
        For Each file In folder.Files
            Debug.Print file.Name & " (" & file.Size & " bytes)"
        Next file

        ' List subfolders
        Debug.Print "=== Subfolders ==="
        For Each subFolder In folder.SubFolders
            Debug.Print "[" & subFolder.Name & "]"
        Next subFolder
    End If

    Set fso = Nothing
End Sub

Text File Operations

Writing to Text Files

Write
Sub WriteTextFile()
    Dim fso As Object
    Dim ts As Object

    Set fso = CreateObject("Scripting.FileSystemObject")

    ' Create new file (True = overwrite if exists)
    Set ts = fso.CreateTextFile("C:\Temp\output.txt", True)

    ts.WriteLine "Line 1: Hello, World!"
    ts.WriteLine "Line 2: This is VBA."
    ts.Write "Line 3: No line break at the end"

    ts.Close

    MsgBox "File written successfully"

    Set ts = Nothing
    Set fso = Nothing
End Sub

Reading Text Files

Read
Sub ReadTextFile()
    Dim fso As Object
    Dim ts As Object
    Dim content As String

    Set fso = CreateObject("Scripting.FileSystemObject")

    If fso.FileExists("C:\Temp\input.txt") Then
        ' Open for reading (1 = ForReading)
        Set ts = fso.OpenTextFile("C:\Temp\input.txt", 1)

        ' Read entire content
        content = ts.ReadAll

        ts.Close

        Debug.Print content
    End If

    Set ts = Nothing
    Set fso = Nothing
End Sub

Reading Line by Line

Read
Sub ReadLineByLine()
    Dim fso As Object
    Dim ts As Object
    Dim lineNum As Integer
    Dim lineText As String

    Set fso = CreateObject("Scripting.FileSystemObject")

    If fso.FileExists("C:\Temp\data.txt") Then
        Set ts = fso.OpenTextFile("C:\Temp\data.txt", 1)

        lineNum = 0
        Do While Not ts.AtEndOfStream
            lineNum = lineNum + 1
            lineText = ts.ReadLine

            Debug.Print lineNum & ": " & lineText
        Loop

        ts.Close
    End If

    Set ts = Nothing
    Set fso = Nothing
End Sub

Appending to Text Files

Append
Sub AppendToTextFile()
    Dim fso As Object
    Dim ts As Object

    Set fso = CreateObject("Scripting.FileSystemObject")

    ' Open for appending (8 = ForAppending)
    Set ts = fso.OpenTextFile("C:\Temp\log.txt", 8, True)

    ts.WriteLine Format(Now, "yyyy-mm-dd hh:nn:ss") & " - New log entry"

    ts.Close

    Set ts = Nothing
    Set fso = Nothing
End Sub

Practical Examples

Batch Renaming Files

Batch
Sub BatchRenameFiles()
    Dim fso As Object
    Dim folder As Object
    Dim file As Object
    Dim newName As String
    Dim counter As Integer

    Set fso = CreateObject("Scripting.FileSystemObject")
    Set folder = fso.GetFolder("C:\Photos")

    counter = 1
    For Each file In folder.Files
        If LCase(fso.GetExtensionName(file.Name)) = "jpg" Then
            newName = "Photo_" & Format(counter, "000") & ".jpg"
            file.Name = newName
            counter = counter + 1
        End If
    Next file

    MsgBox "Renamed " & (counter - 1) & " files"

    Set fso = Nothing
End Sub
Recursive
Sub SearchFilesRecursively()
    Dim fso As Object
    Set fso = CreateObject("Scripting.FileSystemObject")

    ' Start recursive search
    Call ProcessFolder(fso.GetFolder("C:\Projects"), "*.xlsx")

    Set fso = Nothing
End Sub

Sub ProcessFolder(folder As Object, pattern As String)
    Dim file As Object
    Dim subFolder As Object
    Dim fso As Object

    Set fso = CreateObject("Scripting.FileSystemObject")

    ' Process files in current folder
    For Each file In folder.Files
        If LCase(file.Name) Like LCase(pattern) Then
            Debug.Print file.Path
        End If
    Next file

    ' Process subfolders
    For Each subFolder In folder.SubFolders
        Call ProcessFolder(subFolder, pattern)
    Next subFolder
End Sub

Summary

FileSystemObject is a powerful tool for file and folder operations in VBA. Key points:

  • Create instances with CreateObject for portability
  • Use FileExists and FolderExists to check before operations
  • Be careful with delete operations—they’re permanent
  • Text file operations are simple with TextStream
  • Supports recursive subfolder processing

Master FileSystemObject to handle complex file operations efficiently in your VBA projects.

#VBA #FileSystemObject #File Operations #Folder Operations