Application.CodeContextObject property (Access)

Use the CodeContextObject property to determine the object in which a macro or Visual Basic code is executing. Read-only Object.

Syntax

expression.CodeContextObject

expression A variable that represents an Application object.

Remarks

The CodeContextObject property is set by Microsoft Access and is read-only in all views.

The ActiveControl, ActiveDatasheet, ActiveForm, and ActiveReport properties of the Screen object always return the object that currently has the focus. The object with the focus may or may not be the object where a macro or Visual Basic code is currently running, for example, when Visual Basic code runs in the Timer event on a hidden form.

Example

In the following example, the CodeContextObject property is used in a function to identify the name of the object in which an error occurred. The object name is then used in the message box title as well as in the body of the error message. The Error statement is used in the command button's click event to generate the error for this example.

Private Sub Command1_Click() 
 On Error GoTo Command1_Err 
 Error 11 ' Generate divide-by-zero error. 
 Exit Sub 
 
 Command1_Err: 
 If ErrorMessage("Command1_Click() Event", vbYesNo + _ 
 vbInformation, Err) = vbYes Then 
 Exit Sub 
 Else 
 Resume 
 End If 
End Sub 
 
Function ErrorMessage(strText As String, intType As Integer, _ 
 intErrVal As Integer) As Integer 
 Dim objCurrent As Object 
 Dim strMsgboxTitle As String 
 Set objCurrent = CodeContextObject 
 strMsgboxTitle = "Error in " & objCurrent.Name 
 strText = strText & "Error #" & intErrVal _ 
 & " occurred in " & objCurrent.Name 
 ErrorMessage = MsgBox(strText, intType, strMsgboxTitle) 
 Err = 0 
End Function

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.