How to Use VBA Macros to Copy Data to Another Workbook

Bottom Line: Learn how to use VBA macros to copy & paste data from one Excel workbook to another, including adding data to the bottom of an existing range or replacing data.

Skill Level: Intermediate

Video Tutorial

Watch on YouTube & Subscribe to our Channel

Download the Excel Files

Follow along with the video above using the same Excel files that I use. You can download them by clicking below. Here's the workbook that I copy data from in my example:

And here's the workbook that I copy data to.  This is the one that has all the macro code in it:

Copy Data from One Workbook to Another Using Excel Macros

There are a few ways to copy & paste data with VBA. We are first going to use the Range.Copy method. This allows us to perform the entire action in one line of code.

  Workbooks("New Data.xlsx").Worksheets("Export").Range("A2:D9").Copy _
    Workbooks("Reports.xlsm").Worksheets("Data").Range("A2")

The Range.Copy method has an optional Destination parameter that allows us to specify the range we want to paste to.

We reference the source workbook, worksheet, and range that we want to copy from. For the Destination parameter we reference the destination workbook, worksheet, and the beginning cell of the range to paste to.

Copy Data to Another Workbook Using Macros

The Range.Copy method does a regular copy and paste that includes formatting and formulas. If you just want to paste values, there is an example below.

Important Points to Remember

When using this macro to copy data from one workbook to another, keep these points in mind.

  • You must reference the correct file extension in the Workbooks property (see video above for details).
  • Workbooks do not have to be macro enabled for this to work.
  • This code can be stored in a separate workbook, such as your Personal Macro Workbook, if you choose. (Learn how to create a Personal Macro Workbook here.)
  • You do not need to select or activate the workbooks, worksheets, or even ranges first. This is because the code already specifies those details.
  • Both workbooks must be open when using this code. But the process of opening and closing workbooks can be automated with more code:
Sub OpenWorkbook()
'Open a workbook

  'Open method requires full file path to be referenced.
  Workbooks.Open "C:\Users\username\Documents\New Data.xlsx"
  
  'Open method has additional parameters
  'Workbooks.Open(FileName, UpdateLinks, ReadOnly, Format, Password, WriteResPassword, IgnoreReadOnlyRecommended, Origin, Delimiter, Editable, Notify, Converter, AddToMru, Local, CorruptLoad)
  'Help page: https://docs.microsoft.com/en-us/office/vba/api/excel.workbooks.open

End Sub


Sub CloseWorkbook()
'Close a workbook

  Workbooks("New Data.xlsx").Close SaveChanges:=True
  
  'Close method has additional parameters
  'Workbooks.Close(SaveChanges, Filename, RouteWorkbook)
  'Help page: https://docs.microsoft.com/en-us/office/vba/api/excel.workbook.close
  
End Sub

PasteSpecial Method to Paste Values, Formats, etc.

When pasting data into the destination workbook using VBA, you can also use any of the normal Paste Special features.

There is an example macro below. You'll notice that my example uses the PasteValues type, but you could also use PasteFormulas, PasteFormats, or any of the other PasteSpecial options available. Here is a list of the PasteTypes.

  'Copy range to clipboard
  Workbooks("New Data.xlsx").Worksheets("Export").Range("A2:D9").Copy
  
  'PasteSpecial to paste values, formulas, formats, etc.
  Workbooks("Reports.xlsm").Worksheets("Data").Range("A2").PasteSpecial Paste:=xlPasteValues
  

To learn more about PasteSpecial options, check out my video series on Copy and Paste with VBA.

Pasting Below the Last Cell

Sometimes the size of your data ranges in the source and destination files will change every time you run the macro. For example, you may have a daily task of adding new entries from an exported sheet to a master list in another workbook.

Copy Data to Another Workbook below existing entries

In that case, you'll want to add the new entries directly below the last entry on your destination sheet. To do that, you can use the following macro.

Sub Copy_Paste_Below_Last_Cell()
'Find the last used row in both sheets and copy and paste data below existing data.

Dim wsCopy As Worksheet
Dim wsDest As Worksheet
Dim lCopyLastRow As Long
Dim lDestLastRow As Long

  'Set variables for copy and destination sheets
  Set wsCopy = Workbooks("New Data.xlsx").Worksheets("Export 2")
  Set wsDest = Workbooks("Reports.xlsm").Worksheets("All Data")
    
  '1. Find last used row in the copy range based on data in column A
  lCopyLastRow = wsCopy.Cells(wsCopy.Rows.Count, "A").End(xlUp).Row
    
  '2. Find first blank row in the destination range based on data in column A
  'Offset property moves down 1 row
  lDestLastRow = wsDest.Cells(wsDest.Rows.Count, "A").End(xlUp).Offset(1).Row

  '3. Copy & Paste Data
  wsCopy.Range("A2:D" & lCopyLastRow).Copy _
    wsDest.Range("A" & lDestLastRow)

This code pastes your source data just below the existing destination sheet data.

In addition to finding the last row in a range or sheet, you can find the last column or cell as well. Checkout my post and video on 3 ways to find the last used row or column to learn more.

Clearing the Destination Range Before Pasting

Instead of adding to a list in your destination range, you may prefer to clear the existing range before pasting the new data. You can do that with this macro.

Sub Clear_Existing_Data_Before_Paste()

Dim wsCopy As Worksheet
Dim wsDest As Worksheet
Dim lCopyLastRow As Long
Dim lDestLastRow As Long

  Set wsCopy = Workbooks("New Data.xlsx").Worksheets("Export 2")
  Set wsDest = Workbooks("Reports.xlsm").Worksheets("All Data")
    
    '1. Find last used row in the copy range based on data in column A
    lCopyLastRow = wsCopy.Cells(wsCopy.Rows.Count, "A").End(xlUp).Row
      
    '2. Find first blank row in the destination range based on data in column A
    'Offset property moves down 1 row
    lDestLastRow = wsDest.Cells(wsDest.Rows.Count, "A").End(xlUp).Offset(1).Row
    
    '3. Clear contents of existing data range
    wsDest.Range("A2:D" & lDestLastRow).ClearContents

    '4. Copy & Paste Data
    wsCopy.Range("A2:D" & lCopyLastRow).Copy _
      wsDest.Range("A2")

End Sub

Running that macro will remove any existing data in the destination range before inserting the data from the source worksheet.

Alternative Code for Copying Data to Your Current Workbook

I wanted to also present to you a slightly different option for your macro. Instead of identifying the destination workbook by name, you can use the ThisWorkbook property. This can be done as long as the macro is stored in the destination (or source) workbook.

By doing this, you avoid having to change the code in the event you change the file name for your destination workbook. Here is the VBA code that uses ThisWorkbook.

  Workbooks("New Data.xlsx").Worksheets("Export").Range("A2:D9").Copy _
    ThisWorkbook.Worksheets("Data").Range("A2")

This reminds me that VBA will always assume that the macro you want to run applies to the active workbook if you don't specify a workbook in each line of code. I talk about that critical assumption and other important points about running VBA code in this video on VBA Assumptions.

Copy Paste Between Sheets in Same Workbook

You can modify any of the examples above to copy & paste between sheets in the same workbook. Just use the same workbook reference for the copy and destination ranges. Here is an example.

  'Copy range to clipboard
  Workbooks("New Data.xlsx").Worksheets("Export").Range("A2:D9").Copy
  
  'PasteSpecial to paste values, formulas, formats, etc.
  Workbooks("New Data.xlsm").Worksheets("Data").Range("A2").PasteSpecial Paste:=xlPasteValues
  

You won't always need to specify the workbook, but it is a good habit to get into. Otherwise, VBA makes assumptions that can get you in trouble.

Conclusion

I hope these tips and macros help save you time when copying data between workbooks. Automating this boring task will help prevent errors and make it easy for others to update your reports.

Please leave a comment below with any questions or suggestions. Thank you! 🙂

200 comments

Your email address will not be published. Required fields are marked *

  • Sub Clear_Existing_Data_Before_Paste()

    Dim wsCopy As Worksheet
    Dim wsDest As Worksheet
    Dim lCopyLastRow As Long
    Dim lDestLastRow As Long

    Set wsCopy = Workbooks(“New Data.xlsx”).Worksheets(“Export 2”)
    Set wsDest = Workbooks(“Reports.xlsm”).Worksheets(“All Data”)

    ‘1. Find last used row in the copy range based on data in column A
    lCopyLastRow = wsCopy.Cells(wsCopy.Rows.Count, “A”).End(xlUp).Row

    ‘2. Find first blank row in the destination range based on data in column A
    ‘Offset property moves down 1 row
    lDestLastRow = wsDest.Cells(wsDest.Rows.Count, “A”).End(xlUp).Offset(1).Row

    ‘3. Clear contents of existing data range
    wsDest.Range(“A2:D” & lDestLastRow).ClearContents

    ‘4. Copy & Paste Data
    wsCopy.Range(“A2:D” & lCopyLastRow).Copy _
    wsDest.Range(“A2”)

    End Sub

    How can we use paste special to the avobe vba codes.

  • Code is giving error of

    BASIC runtime error.
    ‘1’
    An exception occurred
    Type: com.sun.star.container.NoSuchElementException
    Message: .

  • Hello,

    could someone help me combine these macros. I need copy data from several workbooks (for example named A,B,C,…) to the one which will be summary. In workbooks there will be a list of workers by calendar week in columns. A separate column every week. The list of workers will not be the same every week. I need to have a list of workers from branches (workbooks A,B,C,… in the summary workbook.
    Thank you in advance.

  • I need to copy the data from the new week’s file every week.

    E.g. this week I will be copying from x week 42, and next week I will need to copy from week 43 etc..

    Each each’s file also has it’s own folder named after the new week.

    How do I incorporate a code that will look up the new week?

  • Hey there
    is there a way to change the name of the origin workbook

    “Set wsCopy = Workbooks(“New Data.xlsx”).Worksheets(“Export 2″)”

    the “New Data.xlsx” can that be filled in based on a cell value?

  • How to save to SharePoint files would be good. Took a bit of time but I got there.

    very clear and straight forward tutorial. None of this Microsoft example which complicates things, when you just want the basics.

    Thank you very much.

  • I congratulate you on your ability to present essentially complicated matter in a clear way.
    It is a rare talent, as some people enjoy revelling in the complexity of their subject.
    I’m just starting out with VB, and am very pleased I have come across your materials.

Generic filters
Exact matches only

Excel Shortcuts List

keyboard shortcuts list banner

Learn over 270 Excel keyboard & mouse shortcuts for Windows & Mac.

Excel Shortcuts List

Join Our Weekly Newsletter

The Excel Pro Tips Newsletter is packed with tips & techniques to help you master Excel.

Join Our Free Newsletter