Application.IsCheckedOut property (Project)

Gets whether an open project is checked out from Project Web App by the user. Read-only Boolean.

Syntax

expression. IsCheckedOut

expression A variable that represents an Application object.

Parameters

Name Required/Optional Data type Description
ProjectName Required String The name of a project that is open in Project Professional.

Remarks

For a project that is open in Project Professional, the IsCheckedOut property value is True if the project is checked out by the current user. If the specified project is not checked out by the current user (that is, the project is open but in a read-only mode), or is checked out by a different user, the IsCheckedOut value is False.

The IsCheckedOut property returns run-time error 1004, "An unexpected error occurred with the method" in the following cases:

  • The specified project is not open in Project Professional.

  • The specified project is a local project file such as Project1.mpp.

Example

The following example determines whether an open project is an enterprise project and is checked out. If the project is not checked out, the example tries to check out the project. If the project is checked out by another user, Project shows a dialog box with the message, "To check out, DOMAIN\UserName must close the project in their session or contact your administrator to check in the project."

Sub CheckOutOpenEnterpriseProjects()
    Dim openProjects As Projects
    Dim proj As Project
    
    Set openProjects = Application.Projects
    
    On Error Resume Next
    
    For Each proj In openProjects
        If Application.IsCheckedOut(proj.Name) Then
            If proj.Type = pjProjectTypeEnterpriseCheckedOut Then
                Debug.Print "'" & proj.Name & "'" & " is already checked out."
            ElseIf proj.Type = pjProjectTypeNonEnterprise Then
                Debug.Print "'" & proj.Name & "'" & " is not an enterprise project."
            End If
        Else
            proj.CheckoutProject
            Debug.Print "Attempted to check out: '" & proj.Name & "'"
        End If
    Next proj
End Sub

Property value

BOOL

See also

Application Object Project.Type Property

Project.CheckoutProject Method

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.