FileSystemObjectまとめ

FileSystemObjectとは

フォルダやファイルの操作をするためのオブジェクト。略して「FSO」と呼ばれる

メソッドとプロパティの一覧:FileSystemObject オブジェクト

ライブラリの参照設定

「Microsoft Scripting Runtime」

CreateObjectで使う方法

参照設定したくない場合はこれを書く

Dim FSO As Object
Set FSO = CreateObject(“Scripting.FileSystemObject”)

フォルダの操作

フォルダの存在確認:FolderExists

Sub CheckFolderExistence()
    Dim fso As Scripting.FileSystemObject
    Dim folderPath As String
    Dim folderExists As Boolean
    
    ' フォルダのパスを指定します
    folderPath = "C:\YourFolderPath\" 
    
    ' FileSystemObjectのインスタンスを作成します
    Set fso = New Scripting.FileSystemObject
    
    ' フォルダの存在確認を行います
    folderExists = fso.FolderExists(folderPath)
    
    ' 結果を表示します
    If folderExists Then
        MsgBox "指定したフォルダは存在します。", vbInformation
    Else
        MsgBox "指定したフォルダは存在しません。", vbExclamation
    End If
    
End Sub

新しいフォルダの作成:CreateFolder

Sub CreateNewFolder()
    Dim fso As Scripting.FileSystemObject
    Dim parentFolderPath As String
    Dim newFolderName As String
    Dim newFolderPath As String
    
    ' 新しいフォルダを作成する親フォルダのパスを指定します
    parentFolderPath = "C:\YourParentFolderPath\"
    
    ' 新しいフォルダの名前を指定します
    newFolderName = "NewFolder" 
    
    ' 新しいフォルダのパスを作成します
    newFolderPath = parentFolderPath & newFolderName
    
    ' FileSystemObjectのインスタンスを作成します
    Set fso = New Scripting.FileSystemObject
    
    ' 新しいフォルダを作成します
    If Not fso.FolderExists(newFolderPath) Then
        fso.CreateFolder newFolderPath
        MsgBox "新しいフォルダが作成されました。", vbInformation
    Else
        MsgBox "指定したフォルダは既に存在します。", vbExclamation
    End If

End Sub

フォルダの削除:DeleteFolder

Sub DeleteFolderUsingFSO()
    Dim fso As New Scripting.FileSystemObject
    Dim folderPath As String

    ' 削除したいフォルダのパスを指定します。
    folderPath = "C:\Path\To\Your\Folder"

    ' フォルダが存在するか確認します。
    If fso.FolderExists(folderPath) Then
        ' フォルダを削除します。
        fso.DeleteFolder folderPath
        MsgBox "フォルダが削除されました。", vbInformation
    Else
        MsgBox "指定されたフォルダが見つかりません。", vbExclamation
    End If

End Sub

ファイルの操作

ファイルの存在確認:FileExists

Sub CheckFileExistenceUsingFSO()
    Dim fso As New Scripting.FileSystemObject
    Dim filePath As String

    ' 存在を確認したいファイルのパスを指定します。
    filePath = "C:\Path\To\Your\File.txt"

    ' ファイルが存在するか確認します。
    If fso.FileExists(filePath) Then
        MsgBox "指定されたファイルが存在します。", vbInformation
    Else
        MsgBox "指定されたファイルが見つかりません。", vbExclamation
    End If

End Sub

新しいファイルの作成:CreateTextFile

Sub CreateNewFileUsingFSO()
    Dim fso As New Scripting.FileSystemObject
    Dim filePath As String
    Dim fileObject As Scripting.TextStream

    ' 新しいファイルの作成先を指定します。
    filePath = "C:\Path\To\Your\NewFile.txt"

    ' ファイルを作成します。
    Set fileObject = fso.CreateTextFile(filePath)

    ' ファイルへの書き込みが必要な場合はここに追加します。
    ' fileObject.WriteLine "Hello, this is a new file!"
    ' ...

    ' ファイルを閉じます。
    fileObject.Close

    MsgBox "新しいファイルが作成されました。", vbInformation
End Sub

ファイルをコピーする:Copy

マウスでできるコピペ操作と違って、
プログラミングではコピー後のパスとファイル名を自分で指定しておく必要がある

Sub CopyFileUsingFSO()
    Dim fso As Scripting.FileSystemObject
    Dim sourcePath As String, destinationPath As String
    Dim sourceFile As Scripting.File

    ' FSOオブジェクトを作成
    Set fso = New Scripting.FileSystemObject

    ' コピー元のファイルパスとコピー後のファイルパスを指定
    sourcePath = "C:\SourceFolder\file.txt"
    destinationPath = "C:\DestinationFolder\file.txt"

    ' コピー元のファイルが存在することを確認
    If Not fso.FileExists(sourcePath) Then
        MsgBox "コピー元のファイルが見つかりません。", vbExclamation
        Exit Sub
    End If

    ' コピー元のファイルオブジェクトを取得
    Set sourceFile = fso.GetFile(sourcePath)

    ' ファイルをコピー
    sourceFile.Copy destinationPath

    ' メッセージボックスを表示して処理が完了したことを通知
    MsgBox "ファイルが正常にコピーされました。", vbInformation

End Sub

ファイルの移動:Move

移動先のフォルダパスは、最後のバックスラッシュまでつけないと失敗するので注意
(失敗すると、「フォルダ名+ファイル名」に名前を変更して保存される。
 つまり「最後にバックスラッシュがない文字列」=「ファイル名の一部」と認識される)

Sub MoveFileUsingFSO()
    Dim fso As Scripting.FileSystemObject
    Dim sourcePath As String, destinationPath As String
    Dim sourceFile As Scripting.File

    ' FSOオブジェクトを作成
    Set fso = New Scripting.FileSystemObject

    ' 移動元のファイルパスと移動先のフォルダパスを指定
    sourcePath = "C:\SourceFolder\file.txt"
    destinationPath = "C:\DestinationFolder\"

    ' 移動元のファイルが存在することを確認
    If Not fso.FileExists(sourcePath) Then
        MsgBox "移動元のファイルが見つかりません。", vbExclamation
        Exit Sub
    End If

    ' 移動元のファイルオブジェクトを取得
    Set sourceFile = fso.GetFile(sourcePath)

    ' ファイルを移動
    sourceFile.Move destinationPath & sourceFile.Name

    ' メッセージボックスを表示して処理が完了したことを通知
    MsgBox "ファイルが正常に移動されました。", vbInformation

End Sub

ファイルの削除:DeleteFile

一度削除すると復元できないので注意(ゴミ箱にも残らない)

Sub DeleteFileUsingFSO()
    Dim fso As Scripting.FileSystemObject
    Dim filePath As String

    ' FSOオブジェクトを作成
    Set fso = New Scripting.FileSystemObject

    ' 削除したいファイルのパスを指定
    filePath = "C:\FolderPath\file.txt"

    ' ファイルが存在するか確認
    If Not fso.FileExists(filePath) Then
        MsgBox "削除するファイルが見つかりません。", vbExclamation
        Exit Sub
    End If

    ' ファイルを削除
    fso.DeleteFile filePath

    ' メッセージボックスを表示して処理が完了したことを通知
    MsgBox "ファイルが正常に削除されました。", vbInformation

End Sub

情報の取得

指定したフォルダの中身一覧をPrintする

この場合のフォルダパスは最後にバックスラッシュなくてもOK

Sub ListFoldersAndFilesUsingFSO()
    Dim fso As Scripting.FileSystemObject
    Dim folderPath As String
    Dim folder As Scripting.folder
    Dim subFolder As Scripting.folder
    Dim file As Scripting.file
    
    ' FSOオブジェクトを作成
    Set fso = New Scripting.FileSystemObject

    ' フォルダのパスを指定
    folderPath = "C:\FolderPath\"

    ' フォルダが存在するか確認
    If Not fso.FolderExists(folderPath) Then
        MsgBox "指定されたフォルダが見つかりません。", vbExclamation
        Exit Sub
    End If

    ' フォルダオブジェクトを取得
    Set folder = fso.GetFolder(folderPath)

    ' フォルダ内のフォルダとファイルの一覧を表示
    For Each subFolder In folder.SubFolders
        Debug.Print "フォルダ: " & subFolder.Path
    Next subFolder

    For Each file In folder.Files
        Debug.Print "ファイル: " & file.Path
    Next file

End Sub

特定の拡張子のファイルだけ表示する

Sub ListFilesWithExtensionUsingFSO()
    Dim fso As Scripting.FileSystemObject
    Dim folderPath As String
    Dim folder As Scripting.folder
    Dim file As Scripting.file
    Dim targetExtension As String
    
    ' FSOオブジェクトを作成
    Set fso = New Scripting.FileSystemObject

    ' フォルダのパスを指定
    folderPath = "C:\FolderPath\"

    ' 検索する拡張子を指定(例:".txt")
    targetExtension = ".txt"

    ' フォルダが存在するか確認
    If Not fso.FolderExists(folderPath) Then
        MsgBox "指定されたフォルダが見つかりません。", vbExclamation
        Exit Sub
    End If

    ' フォルダオブジェクトを取得
    Set folder = fso.GetFolder(folderPath)

    ' フォルダ内のファイルを一覧表示
    For Each file In folder.Files
        If LCase(Right(file.Name, Len(targetExtension))) = LCase(targetExtension) Then
            Debug.Print file.Path
        End If
    Next file

End Sub

テキストファイルを読み取る

文字コード「UTF-8」は文字化けするので注意
メモ帳で名前をつけて保存するときに文字コード「ANSI」にすれば文字化けしない

Sub ReadTextFileUsingFSO()
    Dim fso As Scripting.FileSystemObject
    Dim filePath As String
    Dim fileStream As Scripting.TextStream
    Dim fileContent As String

    ' FSOオブジェクトを作成
    Set fso = New Scripting.FileSystemObject

    ' 読み取るテキストファイルのパスを指定
    filePath = "C:\FilePath\file.txt"

    ' ファイルが存在するか確認
    If Not fso.FileExists(filePath) Then
        MsgBox "指定されたファイルが見つかりません。", vbExclamation
        Exit Sub
    End If

    ' テキストファイルを開く
    Set fileStream = fso.OpenTextFile(filePath, ForReading)

    ' ファイルの内容をすべて読み込む
    fileContent = fileStream.ReadAll

    ' ファイルを閉じる
    fileStream.Close

    ' メッセージボックスにファイルの内容を表示
    MsgBox fileContent

End Sub

実践例

指定したフォルダ内の全ファイルをバックアップするツール

ユーザーによるフォルダとバックアップ先の選択を実装

Public Sub BackupFilesUsingFSO()
    Dim fso As Scripting.FileSystemObject
    Dim sourceFolderPath As String, backupFolderPath As String
    Dim sourceFolder As Scripting.folder
    Dim sourceFile As Scripting.file

    ' FSOオブジェクトを作成
    Set fso = New Scripting.FileSystemObject

    ' ユーザーによるフォルダの選択ダイアログを表示し、フォルダのパスを取得
    sourceFolderPath = GetFolderPath()
    
    ' ユーザーがフォルダを選択しなかった場合は処理を終了
    If sourceFolderPath = "" Then
        Exit Sub
    End If

    ' ユーザーによるバックアップ先の選択ダイアログを表示し、フォルダのパスを取得
    backupFolderPath = GetFolderPath()
    
    ' ユーザーがバックアップ先を選択しなかった場合は処理を終了
    If backupFolderPath = "" Then
        Exit Sub
    End If

    ' フォルダオブジェクトを取得
    Set sourceFolder = fso.GetFolder(sourceFolderPath)

    ' フォルダ内のファイルをバックアップ
    For Each sourceFile In sourceFolder.Files
        ' バックアップ先のパスを生成(元のフォルダと同じファイル名でバックアップする)
        Dim backupFilePath As String
        backupFilePath = backupFolderPath & fso.GetFileName(sourceFile.Path)

        ' ファイルをコピー(バックアップ)
        sourceFile.Copy backupFilePath
    Next sourceFile

    ' メッセージボックスを表示して処理が完了したことを通知
    MsgBox "ファイルのバックアップが正常に完了しました。", vbInformation

    ' オブジェクトを解放
    Set fso = Nothing
    Set sourceFolder = Nothing
    Set sourceFile = Nothing
End Sub

' ユーザーによるフォルダの選択ダイアログを表示し、選択されたフォルダのパスを取得する関数
Private Function GetFolderPath() As String
    Dim folderDialog As FileDialog
    Set folderDialog = Application.FileDialog(msoFileDialogFolderPicker)

    With folderDialog
        .Title = "フォルダを選択してください"
        If .Show = -1 Then
            GetFolderPath = .SelectedItems(1) & "\"
        Else
            GetFolderPath = ""
        End If
    End With

    Set folderDialog = Nothing
End Function

仕様メモFSO,オブジェクト

Posted by rafavba