Style.CellsSRC 属性 (Visio)

返回代表由内容、行和列索引标识的 ShapeSheet 单元格的 Cell 对象。 此为只读属性。

语法

expression. CellsSRC( _Section_ , _Row_ , _Column_ )

表达 一个代表 Style 对象的变量。

参数

名称 必需/可选 数据类型 说明
Section 必需 Integer 单元格的内容索引。
必需 Integer 单元格的行索引。
必需 Integer 单元格的列索引。

返回值

Cell

备注

要通过形状公式的内容、行和列索引访问该形状公式,请使用 CellsSRC 属性。 Visio 类型库将节、行和列索引的常量分别声明为 VisSectionIndicesVisRowIndicesVisCellIndices 的成员。

如果节、行和列的索引值未标识实际单元格,则 CellsSRC 属性可能会引发异常,具体取决于节。 但是,即使未引发异常,对返回的对象调用的后续方法也会失败。 通过使用 CellsSRCExists 属性可以确定具有特定索引值的单元格是否存在。

CellsSRC 属性通常用来遍历内容或行中的单元格。 要检索单个单元格,请使用 Cells 属性并且指定单元格名称。 例如:

Set vsoCell = Cells("PinX")

示例

以下 Microsoft Visual Basic for Applications (VBA) 宏显示如何使用 CellsSRC 属性通过特定 ShapeSheet 单元格的内容、行和列索引设置该单元格。 该宏在页面上绘制一个矩形,然后通过将该形状的线条更改为弧形使矩形的线条成为弓形或曲线。 然后,该宏在第一个矩形的弓形线条内绘制一个内部矩形。

 
Public Sub CellsSRC_Example() 
 
 Dim vsoPage As Visio.Page 
 Dim vsoShape As Visio.Shape 
 Dim vsoCell As Visio.Cell 
 Dim strBowCell As String 
 Dim strBowFormula As String 
 Dim intIndex As Integer 
 Dim intCounter As Integer 
 
 'Set the value of the strBowCell string. 
 strBowCell = "Scratch.X1" 
 
 'Set the value of the strBowFormula string. 
 strBowFormula = "=Min(Width, Height) / 5" 
 
 Set vsoPage = ActivePage 
 
 'If there isn't an active page, set vsoPage 
 'to the first page of the active document. 
 If vsoPage Is Nothing Then 
 Set vsoPage = ActiveDocument.Pages(1) 
 End If 
 
 'Draw a rectangle on the active page. 
 Set vsoShape = vsoPage.DrawRectangle(1, 5, 5, 1) 
 
 'Add a scratch section to the shape's ShapeSheet 
 vsoShape.AddSection visSectionScratch 
 
 'Add a row to the scratch section. 
 vsoShape.AddRow visSectionScratch, visRowScratch, 0 
 
 'Set vsoCell to the Scratch.X1 cell and set its formula. 
 Set vsoCell = vsoShape.Cells(strBowCell) 
 vsoCell.Formula = strBowFormula 
 
 'Bow in or curve the rectangle's lines by changing 
 'each row type from LineTo to ArcTo and entering the bow value. 
 For intCounter = 1 To 4 
 vsoShape.RowType(visSectionFirstComponent, visRowVertex + intCounter) = visTagArcTo 
 Set vsoCell = vsoShape.CellsSRC(visSectionFirstComponent, visRowVertex + intCounter, 2) 
 vsoCell.Formula = "-" & strBowCell 
 Next intCounter 
 
 'Create an inner rectangle. 
 'Set the section index for the inner rectangle's Geometry section. 
 intIndex = visSectionFirstComponent + 1 
 
 'Add an inner rectangle Geometry section. 
 vsoShape.AddSection intIndex 
 
 'Add the first 2 rows to the section. 
 vsoShape.AddRow intIndex, visRowComponent, visTagComponent 
 vsoShape.AddRow intIndex, visRowVertex, visTagMoveTo 
 
 'Add 4 LineTo rows to the section 
 For intCounter = 1 To 4 
 vsoShape.AddRow intIndex, visRowLast, visTagLineTo 
 Next intCounter 
 
 'Set the inner rectangle start point cell formulas. 
 Set vsoCell = vsoShape.CellsSRC(intIndex, 1, 0) 
 vsoCell.Formula = "Width * 0 + " & strBowCell 
 Set vsoCell = vsoShape.CellsSRC(intIndex, 1, 1) 
 vsoCell.Formula = "Height * 0 + " & strBowCell 
 
 'Draw the inner rectangle bottom line. 
 Set vsoCell = vsoShape.CellsSRC(intIndex, 2, 0) 
 vsoCell.Formula = "Width * 1 - " & strBowCell 
 Set vsoCell = vsoShape.CellsSRC(intIndex, 2, 1) 
 vsoCell.Formula = "Height * 0 + " & strBowCell 
 
 'Draw the inner rectangle right side line. 
 Set vsoCell = vsoShape.CellsSRC(intIndex, 3, 0) 
 vsoCell.Formula = "Width * 1 - " & strBowCell 
 Set vsoCell = vsoShape.CellsSRC(intIndex, 3, 1) 
 vsoCell.Formula = "Height * 1 - " & strBowCell 
 
 'Draw the inner rectangle top line. 
 Set vsoCell = vsoShape.CellsSRC(intIndex, 4, 0) 
 vsoCell.Formula = "Width * 0 + " & strBowCell 
 Set vsoCell = vsoShape.CellsSRC(intIndex, 4, 1) 
 vsoCell.Formula = "Height * 1 - " & strBowCell 
 
 'Draw the inner rectangle left side line. 
 Set vsoCell = vsoShape.CellsSRC(intIndex, 5, 0) 
 vsoCell.Formula = "Geometry2.X1" 
 Set vsoCell = vsoShape.CellsSRC(intIndex, 5, 1) 
 vsoCell.Formula = "Geometry2.Y1" 
 
End Sub

支持和反馈

有关于 Office VBA 或本文档的疑问或反馈? 请参阅 Office VBA 支持和反馈,获取有关如何接收支持和提供反馈的指南。