Range.Copy method (Excel)
Copies the range to the specified range or to the Clipboard.
Note
Interested in developing solutions that extend the Office experience across multiple platforms? Check out the new Office Add-ins model. Office Add-ins have a small footprint compared to VSTO Add-ins and solutions, and you can build them by using almost any web programming technology, such as HTML5, JavaScript, CSS3, and XML.
Syntax
expression.Copy (Destination)
expression A variable that represents a Range object.
Parameters
Name | Required/Optional | Data type | Description |
---|---|---|---|
Destination | Optional | Variant | Specifies the new range to which the specified range will be copied. If this argument is omitted, Microsoft Excel copies the range to the Clipboard. |
Return value
Variant
Example
The following code example copies the formulas in cells A1:D4 on Sheet1 into cells E5:H8 on Sheet2.
Worksheets("Sheet1").Range("A1:D4").Copy _
destination:=Worksheets("Sheet2").Range("E5:H8")
The following code example inspects the value in column D for each row on Sheet1. If the value in column D equals A, the entire row is copied onto SheetA in the next empty row. If the value equals B, the row is copied onto SheetB.
Public Sub CopyRows()
Sheets("Sheet1").Select
' Find the last row of data
FinalRow = Cells(Rows.Count, 1).End(xlUp).Row
' Loop through each row
For x = 2 To FinalRow
' Decide if to copy based on column D
ThisValue = Cells(x, 4).Value
If ThisValue = "A" Then
Cells(x, 1).Resize(1, 33).Copy
Sheets("SheetA").Select
NextRow = Cells(Rows.Count, 1).End(xlUp).Row + 1
Cells(NextRow, 1).Select
ActiveSheet.Paste
Sheets("Sheet1").Select
ElseIf ThisValue = "B" Then
Cells(x, 1).Resize(1, 33).Copy
Sheets("SheetB").Select
NextRow = Cells(Rows.Count, 1).End(xlUp).Row + 1
Cells(NextRow, 1).Select
ActiveSheet.Paste
Sheets("Sheet1").Select
End If
Next x
End Sub
Support and feedback
Have questions or feedback about Office VBA or this documentation? Please see Office VBA support and feedback for guidance about the ways you can receive support and provide feedback.