Project.Change event (Project)
Occurs when a change is made to data in the project. An action affecting several items at once is considered to be one change.
Syntax
expression. Change
( _pj_
)
expression A variable that represents a Project object.
Parameters
Name | Required/Optional | Data type | Description |
---|---|---|---|
pj | Required | Project | The project that changed. |
Return value
Nothing
Remarks
The Change event does not occur for actions such as switching views, applying filters, changing formatting, and so on.
Project events don't occur when the project is embedded in another document or application.
Example
The following example shows how the ProjectTaskNew event can trap project-level events. In this case, the App_ProjectTaskNew event handler sets the global ProjTaskNew variable that the Change event handler uses. Use similar code with the ProjectResourceNew and ProjectAssignmentNew events.
- Create a new class module named EventClassModule, and then insert the following code:
Option Explicit
Option Base 1
Public WithEvents App As Application
Public WithEvents Proj As Project
Dim NewTaskIDs() As Integer
Dim NumNewTasks As Integer
Dim ProjTaskNew As Boolean
Private Sub App_ProjectTaskNew(ByVal pj As Project, ByVal ID As Long)
NumNewTasks = NumNewTasks + 1
If ProjTaskNew Then
ReDim Preserve NewTaskIDs(NumNewTasks) As Integer
Else
ReDim NewTaskIDs(NumNewTasks) As Integer
End If
NewTaskIDs(NumNewTasks) = ID
ProjTaskNew = True
End Sub
Private Sub Proj_Change(ByVal pj As Project)
Dim NewTaskID As Variant
If ProjTaskNew Then
For Each NewTaskID In NewTaskIDs
MsgBox "New Task Name: " & ActiveProject.Tasks.UniqueID(NewTaskID).Name
Next NewTaskID
NumNewTasks = 0
ProjTaskNew = False
End If
End Sub
- In a separate module, insert the following code:
Option Explicit
Dim X As New EventClassModule
Sub Initialize_App()
Set X.App = MSProject.Application
Set X.Proj = Application.ActiveProject
End Sub
Run the Initialize_App procedure to start listening to the events.
Create a new task. The event handler shows a message box every time a new task is added.
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.