Intro to VBA FSO CopyFile

The FSO CopyFile method is a quick VBA way to copy a file from one location to another. Use the VBA CopyFile FileSystemObject (FSO) to copy a file to another folder. The FSO is part of Windows Script Host which provides scripting abilities like batch files.

If you haven’t already done so, check out our Introduction to the VBA FileSystemObject for a general introduction to the FSO and all its functions.

Even though copying a file sounds easy enough, there are surprisingly many potential pitfalls associated with it. For this reason, it should be emphasized right from the outset that you should always incorporate error handling into your code when you’re accessing a computer’s file system.

In this tutorial we’ll first present the basic setup for copying a file with the FSO CopyFile function and then we’ll show you exactly how to invoke this function. After this, to help you avoid the potential pitfalls, we’ll also present a more sophisticated procedure which includes error handling. This will ensure that you don’t make mistakes when you’re handling your own files.

With this in mind, let’s start with the basic setup!


Basic setup - VBA FSO CopyFile

Note, before you run the code below, you must first make sure that “Microsoft Scripting Runtime” is ticked under Options > Tools > References… in the Visual Basic Editor.

Next, insert the code below into a standard code module:

VBA Copy a File Macro

Sub CopyFileWithFSOBasic(SourceFilePath As String, DestPath As String, OverWrite As Boolean)
' (1) copies one file from one folder to another folder with the VBA FileSystemObject
' (2) contains no error handling (safeguards) --> Not recommended!
' (3) requires a reference to the object library "Microsoft Scripting Runtime" under Options > Tools > References in the VBE.

    Dim FSO As Scripting.FileSystemObject
    
    Set FSO = New Scripting.FileSystemObject
    Call FSO.CopyFile(SourceFilePath, DestPath, OverWrite)

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

CAUTION: The procedure above contains no safeguards (error handling) and it is not recommended to use the functions of the FileSystemObject this way, unless you know exactly what you’re doing! Later in this tutorial, we’ll show you an augmented CopyFile procedure which incorporates error handling.

You invoke the procedure like this:

Sub FSOCopyFileDemo()
Call CopyFileWithFSOBasic("C:\MyFiles\Test.xlsm", "C:\MyBackup\", False)
End Sub

The first parameter, “C:\MyFiles\Test.xlsm” is the source file to be copied. Note, you must specify the full path to the file, starting with the drive name.

The second parameter, “C:\MyBackup", is the path to the destination folder. Notice the backslash \ at the end of the path. Without it, the procedure will copy the file to the preceding folder in the specified destination path, in this case the root of the C-drive, but the copied file will not have any extension!

The third parameter, False is a Boolean type variable which specifies whether or not you want to overwrite any existing file by the same name in the destination folder. If set to False, it means you don’t want to overwrite. When set to True, it means you do. This is very nifty, if you regularly backup the same file to a particular folder.

If you set this parameter to False and a file by the same name already exists in the destination folder, a run-time error will occur when you run the procedure, unless you incorporate error handling into your code.

One beauty of the FSO CopyFile function is that you can simultaneously copy a file and rename it in the new destination. You can use this basic macro to copy a file from one location to another while renaming it in the final destination folder by calling the CopyFile macro like this:

Call CopyFileWithFSOBasic("C:\MyFiles\Test.xlsm", "C:\MyBackup\NewFileName.xlsm", False)

In the next section, we’ll show you how to deal with all kinds of error handling contingencies!

FSO CopyFile Safeguards

It should be clear by now that you’re asking for trouble if you haphazardly try to use the FSO functions without safeguards or error handling. To discourage you from doing so, here’s a quick rundown of the problems you may encounter.

The following errors will throw an exception at run-time and cause the CopyFileWithFSOBasic procedure to halt:

  • If you fail to specify the entire path to the source file correctly.
  • If you attempt to copy the file to a destination folder that doesn’t already exist.
  • If you attempt to copy a file by the same name as a file which already exists in the destination folder without setting the Overwrite parameter to True.
  • If you try to overwrite a file in the destination folder which is open in another program or by another user on a shared network drive. In this case you’ll get a “Run-time error 70 permission denied” message, regardless of whether the Overwrite parameter was set to True or False.

Moreover, a forgotten backslash \ at the end of the destination path will create a file with no extension in the previous component of the destination path. This is not a run-time error, but it’s also not exactly the result you expected! In many ways, this is worse than a run-time error because you may think the program ran to completion, completely oblivious to the fact that it didn’t copy the file where you wanted it.

With this in mind, let’s introduce a new, more advanced, procedure which includes handling of all the above-mentioned errors.

Advanced FSO CopyFile Macro

Sub CopyFileWithFSO(SourceFilePath As String, DestPath As String, OverWrite As Boolean)
' (1) copies one file from one folder to another folder with the VBA FileSystemObject
' (2) contains extensive error handling (safeguards)
' (3) requires a reference to the object library "Microsoft Scripting Runtime" under Options > Tools > References... in the Visual Basic Editor.

    Dim blFileExists As Boolean, blSourceErr As Boolean
    Dim strFileName As String, strSuccessMsg As String, strNewDestPath As String, strNewSourcePath As String
    Dim FSO As Scripting.FileSystemObject
    Dim strErrMsg As String
    
    Set FSO = New Scripting.FileSystemObject
    
    With FSO
        
        strNewDestPath = .BuildPath(.GetAbsolutePathName(DestPath), "\")
        strFileName = .GetFileName(SourceFilePath)
    
        'check if the source file exists
        If Not .FileExists(SourceFilePath) Then
            
            ' check if the root drive was specified
            If .DriveExists(Left(SourceFilePath, 2)) Then
                blSourceErr = True
            
            ' the provided source path is incomplete
            ' build new path and ask the user if he accepts the suggestion
            Else
                strNewSourcePath = .BuildPath(.GetAbsolutePathName(SourceFilePath), "")
                If Not MsgBox("The source path " & Chr(34) & SourceFilePath & Chr(34) & _
                    " is incomplete. Will you accept the following suggestion: " _
                    & Chr(34) & strNewSourcePath & Chr(34) & "?", vbYesNo, "Confirm new source path") = vbYes Then _
                        blSourceErr = True
            End If
            
            ' error
            If blSourceErr Then _
                strErrMsg = "The source file," & Chr(34) & strFileName & Chr(34) & _
                        " does not exist, or the specified path to the file, " & Chr(34) & _
                        Replace(SourceFilePath, strFileName, "") & Chr(34) & " is incorrect."
        
        ' check if the destination folder already exists
        ElseIf Not .FolderExists(strNewDestPath) Then
        
            ' prompt the user if the destination folder should be created
            If MsgBox("The destination folder, " & Chr(34) & strNewDestPath & Chr(34) & ", does not exist. Do you want to create it?", vbYesNo, _
                "Create new folder?") = vbYes Then
                .CreateFolder (strNewDestPath)
            Else
                strErrMsg = "The destination folder could not be created."
            End If
        
        ' check if the file already exists in the destination folder
        Else
            blFileExists = .FileExists(strNewDestPath & strFileName)
            If Not OverWrite Then
                If blFileExists Then _
                    strErrMsg = "The file, " & Chr(34) & strFileName & Chr(34) & _
                        ", already exists in the destination folder, " & Chr(34) & _
                        strNewDestPath & Chr(34) & "."
            End If
        End If
        
        ' attempt to copy file
        If strErrMsg = vbNullString Then
            On Error Resume Next
            If strNewSourcePath = vbNullString Then strNewSourcePath = SourceFilePath
            Call .CopyFile(strNewSourcePath, strNewDestPath, OverWrite)
            If Err.Number <> 0 Then strErrMsg = "Run-time error " & Err.Number & Chr(10) & Err.Description
            On Error GoTo 0
        End If
        
        ' succesful copy
        If strErrMsg = vbNullString Then
            strSuccessMsg = "The file" & Chr(34) & strFileName & Chr(34) & " was copied to " & _
                Chr(34) & strNewDestPath & Chr(34) & "."
            If blFileExists Then strSuccessMsg = strSuccessMsg & Chr(10) & _
                "(Note, the existing file in the destination folder was overwritten)."
            MsgBox strSuccessMsg, vbInformation, "File copied"
        
        ' error
        Else
            MsgBox strErrMsg, vbCritical, "Error!"
        End If
        
    End With

End Sub

When you execute the procedure above, you’ll either get a success message or an error message, depending on whether or not you specified the parameters to the procedure correctly. One limitation of the advanced CopyFileWithFSO macro is that you can’t rename the file when copying it, like you can with the CopyFileWithFSOBasic macro presented at the top of this tutorial. That’s just a byproduct of the error handling logic, but you can change it if you like!

If you did everything correctly, a reassuring message like this will appear:

VBA CopyFile Success Message.png
VBA CopyFile Success Message

CopyFile FSO Error Handling

However, if you didn’t get the success message, another message box was displayed to you explaining what went wrong. Let’s go through these error messages and explain the additional FSO functions we sprinkled into the CopyFileWithFSO procedure to detect potential errors in the parameters passed to it.

  • Does the source file exist?
    • We use the FSO .FileExists function to test this. Next, we check if the root drive was specified in the file path. If not, we use the .BuildPath function to create a complete path and then prompt the user if they’ll accept the new path before moving on. If the user doesn’t accept this suggestion, the procedure terminates with an error message explaining why it terminated.
  • Does the destination folder already exist?
    • We use the FSO .FolderExists function to test this. If the folder doesn’t exist, we prompt the user if they want to create it. If they click OK, we use the FSO .CreateFolder function to create the folder and proceed to the error check. If the user clicks Cancel, the procedure terminates with an error message explaining why it terminated.
  • Does the file already exist in the destination folder?
    • Again, we use the .FileExists FSO function for testing, but we then move on to test if the OverWrite parameter of the procedure was set to True or False. If a file by the same name as the source file already exists in the destination folder and the parameter was set to False (i.e. “don’t overwrite”), the procedure terminates with an error message explaining why it terminated.
  • Given a file by the same name as the source file already exists in the destination folder, is this file locked for editing by another application or user?
    • This is only relevant if the OverWrite parameter has been set to True. Unfortunately, neither the standard Excel functions, the FSO nor any other intuitive object library includes a function for determining whether a file is already open. Thus, the easiest way to check this is to wrap the FSO .FileCopy function with On Error Resume Next and On Error Goto 0. If the file in the destination folder we’re trying to overwrite is locked for editing, it cannot be overwritten and attempting to do so will normally cause an error at run-time. However, with the On Error Resume Next statement, we tell Excel to ignore errors and we collect the description of any error we encounter with the Err.Description property of the Err object. Again, if the procedure encounters an error, it terminates with an error message explaining why it terminated. On a final note, it should be mentioned that source files that are locked for editing can be copied!

Next, let’s discuss some intriguing and powerful applications of the CopyFile function and the CopyFileWithFSO procedure!


CopyFile VBA Ideas

There are two common purposes for using the CopyFile function:

  • Backup of files. Perhaps you want to automatically back up files that meet your specified criteria without manually accessing their containing folders yourself? No problem! Even if you want to back up several files in one batch, you can now easily write a procedure which specifies your source files and then calls the CopyFile function repeatedly.
  • Collection of data. For instance, suppose you want to distribute an Excel Workbook to your coworkers with the purpose of collecting data from them to be stored on a shared network drive. To this end, you could write a procedure with a file picker dialog box that lets the user specify the files you’ve requested. After parsing the specified files, you could then copy them to the appropriate network destination folders.

Look forward future tutorials where you’ll learn about other specific applications of the FSO and how to incorporate safeguards into them!

If you haven’t already done so, please subscribe to my free wellsrPRO VBA Training Program using the form below. It’s worth it!