Shape.SetFormulas method (Visio)

Sets the formulas of one or more cells.

Syntax

expression. SetFormulas( _SRCStream()_ , _formulaArray()_ , _Flags_ )

expression A variable that represents a Shape object.

Parameters

Name Required/Optional Data type Description
SID_SRCStream() Required Integer Stream identifying cells to be modified.
formulaArray() Required Variant Formulas to be assigned to identified cells.
Flags Required Integer Flags that influence the behavior of SetFormulas.

Return value

Integer

Remarks

The SetFormulas method behaves like the Formula property except that you can use it to set the formulas of many cells at once, rather than one cell at a time.

For Shape objects, you can use the SetFormulas method to set results of any set of cells. You tell the SetFormulas method which cells you want to set by passing an array of integers in SID_SRCStream(). SID_SRCStream() is a one-dimensional array of 2-byte integers.

For Shape objects, SID_SRCStream() should be a one-dimensional array of 3 n 2-byte integers for n >= 1. The SetFormulas method interprets the stream as:

{sectionIdx, rowIdx, cellIdx }n

where sectionIdx is the section index of the desired cell, rowIdx is its row index, and cellIdx is its cell index.

The formulaArray() parameter should be a one-dimensional array of 1 <= m variants. Each Variant should be a String, a reference to a String, or Empty. If formulaArray(i) is empty, the i 'th cell will be set to the formula in formulaArray(j) , where j is the index of the most recent prior entry that is not empty. If there is no prior entry that is not empty, the corresponding cell is not altered. If fewer formulas than cells are specified ( m < n ), the i 'th cell, i > m , will be set to the same formula as was chosen to set the m 'th cell to. Thus to set many cells to the same formula, you need pass only one copy of the formula.

The Flags argument should be a bitmask of the following values.

Constant Value Description
visSetBlastGuards &H2 Override present cell values even if they're guarded.
visSetTestCircular &H4 Test for establishment of circular cell references.
visSetUniversalSyntax &H8 Formulas are in universal syntax.

The value returned by the SetFormulas method is the number of entries in SID_SRCStream() that were successfully processed. If i < n entries process correctly, but an error occurs on the i + 1st entry, the SetFormulas method raises an exception and returns i. Otherwise, n is returned.

Example

The following macro shows how to use the SetFormulas method. It assumes that there is an active Microsoft Office Visio page that has at least three shapes on it. It uses the GetFormulas method to get the width of shape 1, the height of shape 2, and the angle of shape 3. It then uses SetFormulas to set the width of shape 1 to the height of shape 2 and the height of shape 2 to the width of shape 1. The angle of shape 3 is left unaltered.

This example uses the GetFormulas method of the Page object to get three cell formulas and the SetFormulas method of the same object to set the formulas. The input array has four slots for each cell, as it also would for Master objects. For Shape or Style objects, only three slots are needed for each cell (section, row, and cell).

 
Public Sub SetFormulas_Example() 
 
 On Error GoTo HandleError 
 
 Dim aintSheetSectionRowColumn(1 To 3 * 4) As Integer 
 aintSheetSectionRowColumn(1) = ActivePage.Shapes(1).ID 
 aintSheetSectionRowColumn(2) = visSectionObject 
 aintSheetSectionRowColumn(3) = visRowXFormOut 
 aintSheetSectionRowColumn(4) = visXFormWidth 
 
 aintSheetSectionRowColumn(5) = ActivePage.Shapes(2).ID 
 aintSheetSectionRowColumn(6) = visSectionObject 
 aintSheetSectionRowColumn(7) = visRowXFormOut 
 aintSheetSectionRowColumn(8) = visXFormHeight 
 
 aintSheetSectionRowColumn(9) = ActivePage.Shapes(3).ID 
 aintSheetSectionRowColumn(10) = visSectionObject 
 aintSheetSectionRowColumn(11) = visRowXFormOut 
 aintSheetSectionRowColumn(12) = visXFormAngle 
 
 'Return the formulas of the cells. 
 Dim avarFormulaArray() As Variant 
 ActivePage.GetFormulas aintSheetSectionRowColumn, avarFormulaArray 
 
 'Use SetFormulas to: 
 ' - Set the width of shape 1 to height of shape 2. 
 ' - Set height of shape 2 to width of shape 1. 
 ' Note: avarFormulaArray() is indexed from 0 to 2. 
 Dim varTemp As variant 
 varTemp = avarFormulaArray(0) 
 avarFormulaArray(0) = avarFormulaArray(1) 
 avarFormulaArray(1) = varTemp 
 
 'Pass the same array back to SetFormulas that we 
 'just passed to GetFormulas, leaving angle alone. By setting 
 'the sheet ID entry in the third slot of the 
 'aintSheetSectionRowColumn array to visInvalShapeID, 
 'we tell SetFormulas to ignore that slot. 
 aintSheetSectionRowColumn (9) = visInvalShapeID 
 
 'Tell Microsoft Visio to set the formulas of the cells. 
 ActivePage.SetFormulas aintSheetSectionRowColumn, avarFormulaArray, 0 
 
 Exit Sub 
 
HandleError: 
 
 MsgBox "Error" 
 
 Exit Sub 
 
End Sub

Support and feedback

Have questions or feedback about Office VBA or this documentation? Please see Office VBA support and feedback for guidance about the ways you can receive support and provide feedback.