Report object (Access)
A Report object refers to a particular Microsoft Access report.
Remarks
A Report object is a member of the Reports collection, which is a collection of all currently open reports. Within the Reports collection, individual reports are indexed beginning with zero. Refer to an individual Report object in the Reports collection either by referring to the report by name, or by referring to its index within the collection. If the report name includes a space, the name must be surrounded by brackets ([ ]).
Syntax | Example |
---|---|
Reports!reportname | Reports!OrderReport |
Reports![report name] | Reports![Order Report] |
Reports("reportname") | Reports("OrderReport") |
Reports(index) | Reports(0) |
Note
Each Report object has a Controls collection, which contains all controls on the report. Refer to a control on a report either by implicitly or explicitly referring to the Controls collection. Your code will be faster if you refer to the Controls collection implicitly. The following examples show two of the ways you might refer to a control named NewData on a report called OrderReport.
' Implicit reference.
Reports!OrderReport!NewData
' Explicit reference.
Reports!OrderReport.Controls!NewData
Example
The following example shows how to use the NoData event of a report to prevent the report from opening when there is no data to be displayed.
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
The following example shows how to use the Page event to add a watermark to a report before it is printed.
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
The following example shows how to set the BackColor property of a control based on its value.
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
The following example shows how to format a report to show progress bars. The example uses a pair of rectangle controls, boxInside and boxOutside, to create a progress bar based on the value of AvgOfRating. The progress bars are visible only when the report is opened in Print Preview mode or it is printed.
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
Events
- Activate
- ApplyFilter
- Click
- Close
- Current
- DblClick
- Deactivate
- Error
- Filter
- GotFocus
- KeyDown
- KeyPress
- KeyUp
- Load
- LostFocus
- MouseDown
- MouseMove
- MouseUp
- MouseWheel
- NoData
- Open
- Page
- Resize
- Timer
- Unload
Methods
Properties
- ActiveControl
- AllowLayoutView
- AllowReportView
- Application
- AutoCenter
- AutoResize
- BorderStyle
- Caption
- CloseButton
- ControlBox
- Controls
- Count
- CurrentRecord
- CurrentView
- CurrentX
- CurrentY
- Cycle
- DateGrouping
- DefaultControl
- DefaultView
- Dirty
- DisplayOnSharePointSite
- DrawMode
- DrawStyle
- DrawWidth
- FastLaserPrinting
- FillColor
- FillStyle
- Filter
- FilterOn
- FilterOnLoad
- FitToPage
- FontBold
- FontItalic
- FontName
- FontSize
- FontUnderline
- ForeColor
- FormatCount
- GridX
- GridY
- GroupLevel
- GrpKeepTogether
- HasData
- HasModule
- Height
- HelpContextId
- HelpFile
- Hwnd
- InputParameters
- KeyPreview
- LayoutForPrint
- Left
- MenuBar
- MinMaxButtons
- Modal
- Module
- MouseWheel
- Moveable
- MoveLayout
- Name
- NextRecord
- OnActivate
- OnApplyFilter
- OnClick
- OnClose
- OnCurrent
- OnDblClick
- OnDeactivate
- OnError
- OnFilter
- OnGotFocus
- OnKeyDown
- OnKeyPress
- OnKeyUp
- OnLoad
- OnLostFocus
- OnMouseDown
- OnMouseMove
- OnMouseUp
- OnNoData
- OnOpen
- OnPage
- OnResize
- OnTimer
- OnUnload
- OpenArgs
- OrderBy
- OrderByOn
- OrderByOnLoad
- Orientation
- Page
- PageFooter
- PageHeader
- Pages
- Painting
- PaintPalette
- PaletteSource
- Parent
- Picture
- PictureAlignment
- PictureData
- PicturePages
- PicturePalette
- PictureSizeMode
- PictureTiling
- PictureType
- PopUp
- PrintCount
- Printer
- PrintSection
- Properties
- PrtDevMode
- PrtDevNames
- PrtMip
- RecordLocks
- Recordset
- RecordSource
- RecordSourceQualifier
- Report
- RibbonName
- ScaleHeight
- ScaleLeft
- ScaleMode
- ScaleTop
- ScaleWidth
- ScrollBars
- Section
- ServerFilter
- Shape
- ShortcutMenuBar
- ShowPageMargins
- Tag
- TimerInterval
- Toolbar
- Top
- UseDefaultPrinter
- Visible
- Width
- WindowHeight
- WindowLeft
- WindowTop
- WindowWidth
See also
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.