Reports.Copy method (Project)

Copies a custom report and creates a new report with the same content.

Syntax

expression.Copy (Source, NewName)

expression A variable that represents a 'Reports' object.

Parameters

Name Required/Optional Data type Description
Source Required Variant Name or Report object of the report to copy.
NewName Required String Name of the new report.
Source Required Variant
NewName Required String

Return value

Report

The new report.

Example

The CopyAReport macro checks whether the specified report to copy exists, and checks whether the new report already exists. The macro then uses one of the variants of the Source parameter to create a copy of the report, and then displays the new report.

Sub CopyAReport()
    Dim reportName As String
    Dim newReportName As String
    Dim newExists As Boolean
    Dim oldExists As Boolean
    Dim report2Copy As Report
    Dim newReport As Report
    
    reportName = "Table Tests"
    newReportName = "New Table Tests"
    oldExists = ActiveProject.Reports.IsPresent(reportName)
    newExists = ActiveProject.Reports.IsPresent(newReportName)
    
    Debug.Print "oldExists " & CStr(oldExists) & "; newExists " & newExists
    
    If oldExists And Not newExists Then
        Set report2Copy = ActiveProject.Reports(reportName)
        
        ' Use either of the following two statements.
        'Set newReport = ActiveProject.Reports.Copy(report2Copy, newReportName)
        Set newReport = ActiveProject.Reports.Copy(reportName, newReportName)
       
        newReport.Apply
    End If
    
    If (oldExists = False) Then
         MsgBox Prompt:="The requested report to copy, '" & reportName _
            & "', does not exist.", Title:="Report copy error"
    ElseIf newExists Then
        MsgBox Prompt:="The new report '" & newReportName _
            & "' already exists.", Title:="Report copy error"
    Else
        MsgBox Prompt:="The new report '" & newReportName & "'" _
            & vbCrLf & "is copied from '" & reportName & "'.", _
            Title:="Report copy success"
    End If
End Sub

See also

Reports Object Report Object

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.