Compartir a través de


Propiedad Style.CellsSRC (Visio)

Devuelve un objeto Cell que representa una celda ShapeSheet identificada por índices de sección, de fila y de columna. Solo lectura.

Sintaxis

expresión. CellsSRC( _Section_ , _Row_ , _Column_ )

Expresión Variable que representa un objeto Style .

Parameters

Nombre Obligatorio/opcional Tipo de datos Descripción
Section Obligatorio Integer Índice de sección de la celda.
Fila Obligatorio Integer Índice de fila de la celda.
Columna Obligatorio Integer Índice de columna de la celda.

Valor devuelto

Cell

Comentarios

Para tener acceso a las fórmulas de las formas por sus índices de sección, fila y columna, use la propiedad CellsSRC. La biblioteca de tipos de Visio declara constantes para índices de sección, fila y columna como miembros de VisSectionIndices, VisRowIndices y VisCellIndices, respectivamente.

La propiedad CellsSRC podría generar una excepción si los valores de índice de sección, fila y columna no identifican una celda real, según la sección. Sin embargo, aun cuando no se genere ninguna excepción, los métodos posteriores invocados en el objeto devuelto producirán un error. Para determinar si existe una celda con valores de índice concretos puede utilizar la propiedad CellsSRCExists.

Por lo general, la propiedad CellsSRC se utiliza para recorrer en iteración las celdas de una sección o una fila. Para recuperar una sola celda, utilice la propiedad Cells y especifique el nombre de la celda. Por ejemplo:

Set vsoCell = Cells("PinX")

Ejemplo:

La siguiente macro de Microsoft Visual Basic para Aplicaciones (VBA) muestra cómo utilizar la propiedad CellsSRC para establecer una celda ShapeSheet por sus índices de sección, de fila y de columna. Dibuja un rectángulo en una página y curva las líneas de dicho rectángulo convirtiendo las líneas de la forma en arcos. A continuación, dibuja un rectángulo inscrito dentro de las líneas curvadas del primer rectángulo.

 
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

Soporte técnico y comentarios

¿Tiene preguntas o comentarios sobre VBA para Office o esta documentación? Vea Soporte técnico y comentarios sobre VBA para Office para obtener ayuda sobre las formas en las que puede recibir soporte técnico y enviar comentarios.