Task.GroupBySummary 屬性 (Project)
如果 任務檢視中選取的專案位於群組摘要資料列中,則為 True;否則為 False。 唯讀的 Boolean。
語法
expression。 GroupBySummary
表達 代表 Task 物件的變數。
註解
當您將 群組依據] 命令套用至任務檢視時,群組摘要列會顯示 [ 任務名稱] 欄中的群組定義。 如果選取的儲存格群組摘要列中, GroupBySummary 屬性為 True 。
GroupBySummary 屬性是可透過 ActiveCell.Task
屬性,而不是透過 ActiveProject.Tasks(x)
。
範例
下列範例會套用 [工期] 群組至 [甘特圖] 檢視,然後選取檢視中每一列的第一個儲存格,並測試該列是否為群組摘要列。 此程序會繼續執行,直到碰到空的列,然後會顯示一個訊息方塊,其中會有每一列的測試結果。
Sub ShowGroupByItems()
Dim isValid As Boolean
Dim tsk As Task
Dim rowType As String
Dim msg As String
isValid = True
msg = ""
ActiveProject.Views("Gantt Chart").Apply
GroupApply Name:="Duration"
Application.SelectBeginning
' When a cell in an empty row is selected, accessing the ActiveCell.Task
' property results in error 1004.
On Error Resume Next
' Loop until a cell in an empty row is selected.
While isValid
Set tsk = ActiveCell.Task
If Err.Number > 0 Then
isValid = False
Debug.Print Err.Number
Err.Number = 0
Else
If tsk.GroupBySummary Then
rowType = "' is a group-by summary row."
Else
rowType = "' is a task row."
End If
msg = msg & "Task name: '" & tsk.Name & rowType & vbCrLf
SelectCellDown
End If
Wend
MsgBox msg, vbInformation, "GroupBy Summary for Tasks"
End Sub
支援和意見反應
有關於 Office VBA 或這份文件的問題或意見反應嗎? 如需取得支援服務並提供意見反應的相關指導,請參閱 Office VBA 支援與意見反應。