Share via


Objet Report (Access)

Un objet Report fait référence à un rapport Microsoft Access particulier.

Remarques

Un objet Report est membre de la collection Reports , qui est une collection de tous les rapports actuellement ouverts. Dans la collection Reports, l'indexation des rapports individuels commence à zéro. Faites référence à un objet Report individuel dans la collection Reports en faisant référence au rapport par son nom ou en faisant référence à son index dans la collection. Si le nom du rapport inclut un espace, il doit être entouré de crochets ([ ]).

Syntaxe Exemple
Rapports ! reportname Reports!OrderReport
Rapports ! [nom du rapport] Reports![État Commande]
Reports(« reportname ») Reports("OrderReport")
Reports(index) Reports(0)

Remarque

Chaque objet Report possède une collection Controls qui contient tous les contrôles sur le rapport. Faites référence à un contrôle sur un rapport en faisant référence implicitement ou explicitement à la collection Controls . Votre code sera plus rapide si vous faites référence à la collection Controls de manière implicite. Les exemples suivants illustrent deux façons de faire référence à un contrôle intitulé NewData sur le rapport appelé OrderReport.

' Implicit reference. 
Reports!OrderReport!NewData
' Explicit reference. 
Reports!OrderReport.Controls!NewData

Exemple

L’exemple suivant montre comment utiliser l’événement NoData d’un rapport pour empêcher l’ouverture du rapport lorsqu’il n’y a pas de données à afficher.

Private Sub Report_NoData(Cancel As Integer)

    'Add code here that will be executed if no data
    'was returned by the Report's RecordSource
    MsgBox "No customers ordered this product this month. " & _
        "The report will now close."
    Cancel = True

End Sub

L’exemple suivant montre comment utiliser l’événement Page pour ajouter un filigrane à un rapport avant de l’imprimer.

Private Sub Report_Page()
    Dim strWatermarkText As String
    Dim sizeHor As Single
    Dim sizeVer As Single

#If RUN_PAGE_EVENT = True Then
    With Me
        '// Print page border
        Me.Line (0, 0)-(.ScaleWidth - 1, .ScaleHeight - 1), vbBlack, B
    
        '// Print watermark
        strWatermarkText = "Confidential"
        
        .ScaleMode = 3
        .FontName = "Segoe UI"
        .FontSize = 48
        .ForeColor = RGB(255, 0, 0)

        '// Calculate text metrics
        sizeHor = .TextWidth(strWatermarkText)
        sizeVer = .TextHeight(strWatermarkText)
        
        '// Set the print location
        .CurrentX = (.ScaleWidth / 2) - (sizeHor / 2)
        .CurrentY = (.ScaleHeight / 2) - (sizeVer / 2)
    
        '// Print the watermark
        .Print strWatermarkText
    End With
#End If

End Sub

L’exemple suivant montre comment définir la propriété BackColor d’un contrôle en fonction de sa valeur.

Private Sub SetControlFormatting()
    If (Me.AvgOfRating >= 8) Then
        Me.AvgOfRating.BackColor = vbGreen
    ElseIf (Me.AvgOfRating >= 5) Then
        Me.AvgOfRating.BackColor = vbYellow
    Else
        Me.AvgOfRating.BackColor = vbRed
    End If
End Sub

Private Sub Detail_Format(Cancel As Integer, FormatCount As Integer)
    ' size the width of the rectangle
    Dim lngOffset As Long
    lngOffset = (Me.boxInside.Left - Me.boxOutside.Left) * 2
    Me.boxInside.Width = (Me.boxOutside.Width * (Me.AvgOfRating / 10)) - lngOffset
    
    ' do conditional formatting for the control in print preview
    SetControlFormatting
End Sub

Private Sub Detail_Paint()
    ' do conditional formatting for the control in report view
    SetControlFormatting
End Sub

L’exemple suivant montre comment mettre en forme un rapport pour afficher les barres de progression. L’exemple utilise une paire de contrôles rectangulaires, boxInside et boxOutside, pour créer une barre de progression basée sur la valeur de AvgOfRating. Les barres de progression sont visibles uniquement quand le rapport est ouvert dans le mode Aperçu avant impression ou quand il est imprimé.

Private Sub Report_Load()
    If (Me.CurrentView = AcCurrentView.acCurViewPreview) Then
        Me.boxInside.Visible = True
        Me.boxOutside.Visible = True
    Else
        Me.boxInside.Visible = False
        Me.boxOutside.Visible = False
    End If
End Sub

Private Sub Detail_Format(Cancel As Integer, FormatCount As Integer)
    ' size the width of the rectangle
    Dim lngOffset As Long
    lngOffset = (Me.boxInside.Left - Me.boxOutside.Left) * 2
    Me.boxInside.Width = (Me.boxOutside.Width * (Me.AvgOfRating / 10)) - lngOffset
    
    ' do conditional formatting for the control in print preview
    SetControlFormatting
End Sub

Événements

Méthodes

Propriétés

Voir aussi

Assistance et commentaires

Avez-vous des questions ou des commentaires sur Office VBA ou sur cette documentation ? Consultez la rubrique concernant l’assistance pour Office VBA et l’envoi de commentaires afin d’obtenir des instructions pour recevoir une assistance et envoyer vos commentaires.