Form.Error event (Access)

The Error event occurs when a run-time error is produced in Microsoft Access when a form has the focus.

Syntax

expression.Error (DataErr, Response)

expression A variable that represents a Form object.

Parameters

Name Required/Optional Data type Description
DataErr Required Integer The error code returned by the Err object when an error occurs. Use the DataErr argument with the Error function to map the number to the corresponding error message.
Response Required Integer The setting determines whether an error message is displayed. The Response argument can be one of the following intrinsic constants.
  • acDataErrContinue Ignore the error and continue without displaying the default Microsoft Access error message. You can supply a custom error message in place of the default error message.

  • acDataErrDisplay (Default) Display the default Access error message.

Remarks

This includes Access database engine errors, but not run-time errors in Visual Basic or errors from ADO.

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

By running an event procedure or a macro when an Error event occurs, you can intercept an Access error message and display a custom message that conveys a more specific meaning for your application.

Example

The following example shows how you can replace a default error message with a custom error message. When Access returns an error message indicating it has found a duplicate key (error code 3022), this event procedure displays a message that gives more application-specific information to users.

To try the example, add the following event procedure to a form that is based on a table with a unique employee ID number as the key for each record.

Private Sub Form_Error(DataErr As Integer, Response As Integer) 
    Const conDuplicateKey = 3022 
    Dim strMsg As String 
 
    If DataErr = conDuplicateKey Then 
        Response = acDataErrContinue 
        strMsg = "Each employee record must have a unique " _ 
            & "employee ID number. Please recheck your data." 
        MsgBox strMsg 
    End If 
End Sub

The following example shows how you can replace a default error message with a custom error message.

Private Sub Form_Error(DataErr As Integer, Response As Integer)
    Select Case DataErr
        Case 2113
            MsgBox "Only numbers are acceptable in this box", vbCritical, "Call 1-800-123-4567"
            Response = acDataErrContinue
        Case 2237
            MsgBox "You can only choose from the dropdown box"
            Response = acDataErrContinue
        Case 3022
            MsgBox "You entered a value that exists already in another record"
            Response = acDataErrContinue
            SSN.Value = SSN.OldValue
        Case 3314
            MsgBox "The DOH is required, so you cannot leave this field empty"
            Response = acDataErrContinue
        Case Else
            Response = acDataErrDisplay
    End Select
    ActiveControl.Undo
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.