Compartir por


Objeto Report (Access)

Un objeto Report hace referencia a un informe en particular de Microsoft Access.

Observaciones

Un objeto Report es miembro de la colección Reports , que es una colección de todos los informes abiertos actualmente. En la colección Reports los informes individuales se indexan a partir de cero. Haga referencia a un objeto Report individual de la colección Reports haciendo referencia al informe por su nombre o haciendo referencia a su índice dentro de la colección. Si el nombre del informe incluye un espacio, el nombre debe estar encerrado entre corchetes ([ ]).

Sintaxis Ejemplo
¡Informes! reportname Reports!OrderReport
¡Informes! [nombre del informe] Reports![Order Report]
Reports("reportname") Reports("OrderReport")
Reports(index) Reports(0)

Nota:

Cada objeto Informe tiene una colección Controles, que contiene todos los controles del informe. Consulte un control de un informe haciendo referencia implícita o explícitamente a la colección Controls . El código será más rápido si hace referencia a la colección Controles implícitamente. En los ejemplos siguientes se muestran dos maneras de hacer referencia a un control denominado NewData en el informe llamado OrderReport:

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

Ejemplo

En el ejemplo siguiente se muestra cómo usar el evento NoData de un informe para evitar que el informe se abra cuando no se muestre ningún dato.

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

En el ejemplo siguiente se muestra cómo usar el evento Page para agregar una marca de agua a un informe antes de imprimirlo.

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

En el ejemplo siguiente se muestra cómo establecer la propiedad BackColor de un control basándose en su valor.

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

El ejemplo siguiente muestra cómo dar formato a un informe para mostrar las barras de progreso. En el ejemplo se usa un par de controles de rectángulo boxInside y boxOutside, para crear una barra de progreso con el valor de AvgOfRating. Las barras de progreso son visibles solo cuando se abre el informe en el modo Vista preliminar o se imprime.

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

Eventos

Métodos

Propiedades

Vea también

Soporte técnico y comentarios

¿Tiene preguntas o comentarios sobre VBA para Office o esta documentación? Vea Soporte técnico y comentarios sobre VBA para Office para obtener ayuda sobre las formas en las que puede recibir soporte técnico y enviar comentarios.