Compartir a través de


Propiedad Cell.Precedents (Visio)

Devuelve una matriz de celdas ShapeSheet de las que depende la fórmula de otra celda. Solo lectura.

Sintaxis

expresión. Precedentes

Expresión Variable que representa un objeto Cell .

Valor devuelto

Cell()

Comentarios

La propiedad Precedents devuelve una matriz de las celdas que hacen que el objeto Cell primario vuelva a calcular su valor cuando cambie su fórmula o valor.

Ejemplo:

La siguiente macro de Microsoft Visual Basic para Aplicaciones (VBA) muestra cómo usar la propiedad Precedents para mostrar una lista de celdas de las que depende la celda "Scratch.X1" de una forma. La macro dibuja un rectángulo en la página activa, agrega una sección Scratch a la ShapeSheet del rectángulo y, a continuación, escribe una fórmula en una celda de esa sección que se usa para inclinar los lados del rectángulo hacia adentro, cambiando cada uno de los lados de los rectángulos a un arco. Dado que la fórmula usada para inclinar los lados del rectángulo depende del ancho y el alto del rectángulo, la celda que contiene la fórmula, Scratch.X1, depende de las celdas Width y Height de la forma del rectángulo, lo que hace que estas celdas precedan.

Public Sub Precedents_Example() 
 
 Dim acellPrecedentCells() As Visio.Cell 
 Dim vsoCell As Visio.Cell 
 Dim vsoShape As Visio.Shape 
 Dim strBowCell As String 
 Dim strBowFormula As String 
 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" 
 
 'Draw a rectangle on the active page 
 Set vsoShape = ActivePage.DrawRectangle(1, 5, 5, 1) 
 
 'Add a scratch section and then 
 vsoShape.AddSection visSectionScratch 
 
 'Add a row to the scratch section 
 vsoShape.AddRow visSectionScratch, visRowScratch, 0 
 
 'Place the value of strBowFormula into Scratch.X1 
 'Set the Cell object to the Scratch.X1 and set formula 
 Set vsoCell = vsoShape.Cells(strBowCell) 
 
 'Set up the offset for the arc 
 vsoCell.Formula = strBowFormula 
 
 'Bow in or curve the original rectangle's lines by changing 
 'each row to an arc 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 
 
 'Get the array of precedent cells 
 acellPrecedentCells = vsoShape.Cells("Scratch.X1").Precedents 
 
 'List the cell names and their associated formula 
 For intCounter = LBound(acellPrecedentCells) To UBound(acellPrecedentCells) 
 Set vsoCell = acellPrecedentCells(intCounter) 
 Debug.Print vsoCell.Name & " has this formula: " & vsoCell.Formula 
 Next 
 
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.