Report.Open event (Access)

The Open event occurs before a report is previewed or printed.

Syntax

expression.Open (Cancel)

expression A variable that represents a Report object.

Parameters

Name Required/Optional Data type Description
Cancel Required Integer The setting determines if the opening of the form or report occurs. Setting the Cancel argument to True (1) cancels the opening of the form or report.

Return value

Nothing

Remarks

For example, an Open macro or event procedure can open a custom dialog box in which the user enters the criteria to filter the set of records to display on a form or the date range to include for a report.

When you open a report based on an underlying query, Microsoft Access runs the Open macro or event procedure before it runs the underlying query for the report. This enables the user to specify criteria for the report before it opens; for example, in a custom dialog box you display when the Open event occurs.

If your application can have more than one form loaded at a time, use the Activate and Deactivate events instead of the Open event to display and hide custom toolbars when the focus moves to a different form.

When the Close event occurs, you can open another window or request the user's name to make a log entry indicating who used the form or report.

If you are trying to decide whether to use the Open or Load event for your macro or event procedure, one significant difference is that the Open event can be canceled, but the Load event can't. For example, if you are dynamically building a record source for a form in an event procedure for the form's Open event, you can cancel opening the form if there are no records to display. Similarly, the Unload event can be canceled, but the Close event can't.

Example

The following example shows how to use a Structured Query Language (SQL) statement to establish the data source of a report as it is opened.

Private Sub Report_Open(Cancel As Integer)

    On Error GoTo Error_Handler

    Me.Caption = "My Application"

    DoCmd.OpenForm FormName:="frmReportSelector_MemberList", _
    Windowmode:=acDialog

    'Cancel the report if "cancel" was selected on the dialog form.

    If Forms!frmReportSelector_MemberList!txtContinue = "no" Then
        Cancel = True
        GoTo Exit_Procedure
    End If
    Me.RecordSource = ReplaceWhereClause(Me.RecordSource, _
      Forms!frmReportSelector_MemberList!txtWhereClause)

Exit_Procedure:
    Exit Sub

Error_Handler:
    MsgBox Err.Number & ": " & Err.Description
    Resume Exit_Procedure
    Resume

End Sub

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.