Freigeben über


Reports.Copy-Methode (Project)

Kopiert einen benutzerdefinierten Bericht und erstellt einen neuen Bericht mit demselben Inhalt.

Syntax

Ausdruck. Copy (Source, NewName)

Ausdruck Eine Variable, die ein Reports-Objekt darstellt.

Parameter

Name Erforderlich/Optional Datentyp Beschreibung
Source Erforderlich Variant Name oder Report-Objekt des zu kopierenden Berichts.
Newname Erforderlich String Name des neuen Berichts.
Source Erforderlich Variant
Newname Erforderlich String

Rückgabewert

Report

Der neue Bericht.

Beispiel

Das CopyAReport-Makro überprüft, ob der angegebene zu kopierende Bericht vorhanden ist, und überprüft, ob der neue Bericht bereits vorhanden ist. Das Makro verwendet dann eine der Varianten des Source-Parameters , um eine Kopie des Berichts zu erstellen, und zeigt dann den neuen Bericht an.

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

Siehe auch

Report-Objekt des Reports-Objekts

Support und Feedback

Haben Sie Fragen oder Feedback zu Office VBA oder zu dieser Dokumentation? Unter Office VBA-Support und Feedback finden Sie Hilfestellung zu den Möglichkeiten, wie Sie Support erhalten und Feedback abgeben können.