Form.ApplyFilter event (Access)

Occurs when a filter is applied to a form.

Syntax

expression.ApplyFilter (Cancel, ApplyType)

expression A variable that represents a Form object.

Parameters

Name Required/Optional Data type Description
Cancel Required Integer The setting determines if the ApplyFilter event occurs. Setting the Cancel argument to True cancels the ApplyFilter event and the filter is not applied to the form.
ApplyType Required Integer Returns the type of filter that was applied.

Remarks

To run a macro or event procedure when this event occurs, set the OnApplyFilter property to the name of the macro or to [Event Procedure].

Use the ApplyFilter event to:

  • Make sure that the filter that is being applied is correct. For example, you may want to be sure that any filter applied to an Orders form includes criteria restricting the OrderDate field. To do this, check the form's Filter or ServerFilter property value to make sure that this criteria is included in the WHERE clause expression.

  • Change the display of the form before the filter is applied. For example, when you apply a certain filter, you may want to disable or hide some fields that aren't appropriate for the records displayed by this filter.

  • Undo or change actions that you took when the Filter event occurred. For example, you can disable or hide some controls on the form when the user is creating the filter because you don't want these controls to be included in the filter criteria. You can then enable or show these controls after the filter is applied.

The actions in the ApplyFilter event procedure or macro occur before the filter is applied or removed, or after the Advanced Filter/Sort, Filter By Form, or Server Filter By Form window is closed, but before the form is redisplayed. The criteria you've entered in the newly created filter are available to the ApplyFilter event procedure or macro as the setting of the Filter or ServerFilter property.

Note

The ApplyFilter event doesn't occur when the user does one of the following:

  • Applies or removes a filter by using the ApplyFilter, OpenReport, or ShowAllRecords actions in a macro, or their corresponding methods of the DoCmd object in Visual Basic.
  • Uses the Close action or the Close method of the DoCmd object to close the Advanced Filter/Sort, Filter By Form, or Server Filter By Form window.
  • Sets the Filter or ServerFilter property or FilterOn or ServerFilterByForm property in a macro or Visual Basic (although you can set these properties in an ApplyFilter event procedure or macro).

Example

The following example shows how to hide the AmountDue, Tax, and TotalDue controls on an Orders form when the applied filter restricts the records to only those orders that have been paid for.

To try this example, add the following event procedure to an Orders form that contains AmountDue, Tax, and TotalDue controls. Run a filter that lists only those orders that have been paid for.

Private Sub Form_ApplyFilter(Cancel As Integer, ApplyType As Integer) 
 If Not IsNull(Me.Filter) And (InStr(Me.Filter, "Orders.Paid = -1")>0 _ 
 Or InStr(Me.Filter, "Orders.Paid = True")>0)Then 
 If ApplyType = acApplyFilter Then 
 Forms!Orders!AmountDue.Visible = False 
 Forms!Orders!Tax.Visible = False 
 Forms!Orders!TotalDue.Visible = False 
 ElseIf ApplyType = acShowAllRecords Then 
 Forms!Orders!AmountDue.Visible = True 
 Forms!Orders!Tax.Visible = True 
 Forms!Orders!TotalDue.Visible = True 
 End If 
 End If 
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.