Task.ActualOvertimeCost property (Project)

Gets the actual overtime cost for a task. Read-only Variant.

Syntax

expression. ActualOvertimeCost

expression A variable that represents a Task object.

Example

The following example shows the cost of overtime by calculating the total cost of tasks with overtime work, as well as breaking down the individual costs per task.

Sub PriceOfOvertime() 
 Dim T As Task 
 Dim Price As Variant, Breakdown As String 
 
 For Each T In ActiveProject.Tasks 
 If Not (T Is Nothing) Then 
 If T.ActualOvertimeWork <> 0 Then 
 Price = Price + T.ActualOvertimeCost 
 Breakdown = Breakdown & T.Name & ": " & _ 
 ActiveProject.CurrencySymbol & _ 
 T.ActualOvertimeCost & vbCrLf 
 End If 
 End If 
 Next T 
 
 If Breakdown <> "" Then 
 MsgBox Breakdown & vbCrLf & "Total: " & _ 
 ActiveProject.CurrencySymbol & Price 
 End If 
 
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.