Visio (的 Cell.FormulaU 屬性)

會取得或設定 Cell 物件的通用語法公式。 讀取/寫入。

語法

運算式FormulaU

表達 代表 Cell 物件的變數。

傳回值

字串

註解

如果儲存格的公式受到 GUARD 函數的保護,您必須使用 FormulaForceU 屬性變更此儲存格的公式。

注意事項

從 Microsoft Visio 2000 開始,您可以使用本機和通用名稱來參照 Visio 圖形、主圖形、檔、頁面、列、附加元件、儲存格、超連結、樣式、字型、主圖形快捷方式、UI 物件和圖層。 例如,當使用者為圖形命名時,使用者會指定本機名稱。 從 Microsoft Office Visio 2003 開始,ShapeSheet 試算表只會在儲存格公式和值中顯示通用名稱。 (在舊版中,使用者介面中看不到通用名稱。)

身為開發人員,如果您不希望每次將方案本土化時就要變更名稱,可以在程式中使用通用名稱。 使用 Formula 屬性以本機語法取得儲存格的公式字串,或使用本機和通用語法的混合來設定它。 使用 FormulaU 屬性可取得或剖析通用語法中的公式。 當您使用 FormulaU時,小數點一律為 「.」,分隔符號一律為 「,」,而且您必須使用通用單位字串 (以取得通用字串的詳細資料,請 參閱關於量值 單位) 。

如果您的 Visual Studio 解決方案包含 Microsoft.Office.Interop.Visio 參考,則此屬性會對應至下列類型:

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

範例

這個 Microsoft Visual Basic for Applications (VBA) 宏會示範如何使用 FormulaU 屬性來設定 ShapeSheet 儲存格的公式。 它會在頁面上繪製矩形,然後將圖形的線條變更為弧線來彎曲矩形的線條。 然後,它會在第一個矩形的斜線內繪製內部矩形。

 
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

支援和意見反應

有關於 Office VBA 或這份文件的問題或意見反應嗎? 如需取得支援服務並提供意見反應的相關指導,請參閱 Office VBA 支援與意見反應