Task.GroupBySummary 属性 (Project)
如果任务视图中的选定项位于组摘要行中,则为 True;否则为 False。 只读 Boolean。
语法
expression。 GroupBySummary
表达 一个代表 Task 对象的变量。
备注
将一个 分组依据命令应用到任务视图中,组摘要行在 任务名称列中显示的组定义。 如果所选单元格位于分组摘要行, 摘要分组 属性为 True 。
摘要分组 属性是可通过 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 支持和反馈,获取有关如何接收支持和提供反馈的指南。