Compartir a través de


Propiedad Cell.FormulaU (Visio)

Obtiene o establece la fórmula de sintaxis universal para un objeto Cell. Lectura y escritura.

Sintaxis

expresión. FormulaU

Expresión Variable que representa un objeto Cell .

Valor devuelto

Cadena

Comentarios

Si la fórmula de una celda está protegida con la función GUARD, debe utilizar la propiedad FormulaForceU para cambiar dicha fórmula.

Nota:

A partir de Microsoft Visio 2000, puede usar nombres locales y universales para hacer referencia a formas, patrones, documentos, páginas, filas, complementos, celdas, hipervínculos, estilos, fuentes, accesos directos maestros, objetos de interfaz de usuario y capas de Visio. Cuando un usuario asigna un nombre a una forma, por ejemplo, el usuario especifica un nombre local. A partir de Microsoft Office Visio 2003, la hoja de cálculo ShapeSheet solo muestra nombres universales en fórmulas y valores de celda. (En versiones anteriores, los nombres universales no eran visibles en la interfaz de usuario).

Como programador, puede usar nombres universales en un programa cuando no desee cambiar un nombre cada vez que localice una solución. Use la propiedad Formula para obtener la cadena de fórmula de una celda en la sintaxis local o para usar una combinación de sintaxis local y universal al establecerla. Use la propiedad FormulaU para obtener o analizar una fórmula en sintaxis universal. Si usa FormulaU, el separador decimal es siempre ".", el delimitador es siempre "," y debe usar cadenas de unidades universales (si desea información detallada acerca de las cadenas universales, vea el tema sobre las unidades de medida).

Si la solución de Visual Studio incluye la referencia Microsoft.Office.Interop.Visio , esta propiedad se asigna a los tipos siguientes:

  • Microsoft.Office.Interop.Visio.IVCell.FormulaU

Ejemplo:

Esta macro de Microsoft Visual Basic para Aplicaciones (VBA) muestra cómo utilizar la propiedad FormulaU para establecer la fórmula para una celda ShapeSheet. 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 FormulaU_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.FormulaU = 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.FormulaU = "-" & 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.FormulaU = "Width * 0 + " & strBowCell  
    Set vsoCell = vsoShape.CellsSRC(intIndex, 1, 1)  
    vsoCell.FormulaU = "Height * 0 + " & strBowCell  
 
    'Draw the inner rectangle bottom line. 
    Set vsoCell = vsoShape.CellsSRC(intIndex, 2, 0)  
    vsoCell.FormulaU = "Width * 1 - " & strBowCell  
    Set vsoCell = vsoShape.CellsSRC(intIndex, 2, 1)  
    vsoCell.FormulaU = "Height * 0 + " & strBowCell  
 
    'Draw the inner rectangle right side line. 
    Set vsoCell = vsoShape.CellsSRC(intIndex, 3, 0)  
    vsoCell.FormulaU = "Width * 1 - " & strBowCell  
    Set vsoCell = vsoShape.CellsSRC(intIndex, 3, 1)  
    vsoCell.FormulaU = "Height * 1 - " & strBowCell  
 
    'Draw the inner rectangle top line. 
    Set vsoCell = vsoShape.CellsSRC(intIndex, 4, 0)  
    vsoCell.FormulaU = "Width * 0 + " & strBowCell  
    Set vsoCell = vsoShape.CellsSRC(intIndex, 4, 1)  
    vsoCell.FormulaU = "Height * 1 - " & strBowCell  
 
    'Draw the inner rectangle left side line. 
    Set vsoCell = vsoShape.CellsSRC(intIndex, 5, 0)  
    vsoCell.FormulaU = "Geometry2.X1"  
    Set vsoCell = vsoShape.CellsSRC(intIndex, 5, 1)  
    vsoCell.FormulaU = "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.