CurrentProject object (Access)

The CurrentProject object refers to the project for the current Microsoft Access project (.adp) or Access database.

Remarks

The CurrentProject object has several collections that contain specific AccessObject objects within the current database. The following table lists the name of each collection and the types of objects it contains.

Collections Object type
AllForms All forms
AllReports All reports
AllMacros All macros
AllModules All modules

Note

The collections in the preceding table contain all of the respective objects in the database regardless if they are opened or closed.

For example, an AccessObject object representing a form is a member of the AllForms collection, which is a collection of AccessObject objects within the current database. Within the AllForms collection, individual members of the collection are indexed beginning with zero. Refer to an individual AccessObject object in the AllForms collection either by referring to the form by name, or by referring to its index within the collection. If you want to refer to a specific object in the AllForms collection, it's better to refer to it by name because an item's collection index may change. If the object name includes a space, the name must be surrounded by brackets ([ ]).

Syntax Example
AllForms!formname AllForms!OrderForm
AllForms![form name] AllForms![Order Form]
AllForms("formname") AllForms("OrderForm")
AllForms(index) AllForms(0)

Example

The following example prints some current property settings of the CurrentProject object, and then sets an option to display hidden objects within the application.

Sub ApplicationInformation() 
 ' Print name and type of current object. 
 Debug.Print Application.CurrentProject.FullName 
 Debug.Print Application.CurrentProject.ProjectType 
 ' Set Hidden Objects option under Show on View Tab 
 'of the Options dialog box. 
 Application.SetOption "Show Hidden Objects", True 
End Sub

The next example shows how to use the CurrentProject object by using Automation from another Microsoft Office application. First, from the other application, create a reference to Microsoft Access by choosing References on the Tools menu in the Module window. Select the check box next to Microsoft Access Object Library, and then enter the following code in a Visual Basic module within that application and call the GetAccessData procedure.

The example passes a database name and report name to a procedure that creates a new instance of the Application class, opens the database, and verifies that the specified report exists by using the CurrentProject object and AllReports collection.

Sub GetAccessData() 
' Declare object variable in declarations section of a module 
 Dim appAccess As Access.Application 
 Dim strDB As String 
 Dim strReportName As String 
 
 strDB = "C:\Program Files\Microsoft " _ 
          & "Office\Office11\Samples\Northwind.mdb" 
 strReportName = InputBox("Enter name of report to be verified", _ 
                          "Report Verification") 
 VerifyAccessReport strDB, strReportName 
End Sub 
 
Sub VerifyAccessReport(strDB As String, _ 
                       strReportName As String) 
 ' Return reference to Microsoft Access 
 ' Application object. 
 Set appAccess = New Access.Application 
 ' Open database in Microsoft Access. 
 appAccess.OpenCurrentDatabase strDB 
 ' Verify report exists. 
 On Error Goto ErrorHandler 
 IsObject appAccess.CurrentProject.AllReports(strReportName) 
 MsgBox "Report " & strReportName & _ 
        " verified within " & appAccess.CurrentProject.Name & " database."
 appAccess.CloseCurrentDatabase 
 Set appAccess = Nothing 
Exit Sub 
ErrorHandler: 
 MsgBox "Report " & strReportName & _ 
        " does not exist within " & appAccess.CurrentProject.Name & " database."
 appAccess.CloseCurrentDatabase 
 Set appAccess = Nothing 
End Sub

Methods

Properties

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.