Freigeben über


Shape.CellsSRC-Eigenschaft (Visio)

Gibt ein Cell-Objekt zurück, das eine ShapeSheet-Zelle darstellt, die nach Abschnitts-, Zeilen- und Spaltenindizes identifiziert wird. Schreibgeschützt.

Syntax

Ausdruck. CellsSRC( _Section_ , _Row_ , _Column_ )

expression Eine Variable, die ein Shape-Objekt darstellt.

Parameter

Name Erforderlich/Optional Datentyp Beschreibung
Section Erforderlich Integer Der Abschnittsindex der Zelle.
Row Erforderlich Integer Der Zeilenindex der Zelle.
Spalte Erforderlich Integer Der Spaltenindex der Zelle.

Rückgabewert

Cell

Hinweise

Verwenden Sie die CellsSRC-Eigenschaft, um auf eine beliebige Shape-Formel nach seinem Abschnitts-, Zeilen- und Spaltenindizes zuzugreifen. Konstanten für Abschnitts-, Zeilen- und Spaltenindizes werden von der Visio-Typbibliothek als Member von VisSectionIndices, VisRowIndices bzw . VisCellIndices deklariert.

Die CellsSRC-Eigenschaft löst möglicherweise eine Ausnahme aus, wenn Indexwerte für Abschnitt, Zeile und Spalte abhängig vom Abschnitt keine tatsächliche Zelle identifizieren. Nachfolgende Methoden, die für das zurückgegebene Objekt aufgerufen werden, können auch dann nicht ausgeführt werden, wenn keine Ausnahme ausgelöst wurde. Sie können bestimmen, ob eine Zelle mit bestimmten Indexwerten vorhanden ist, indem Sie die CellsSRCExists-Eigenschaft verwenden.

Die CellsSRC-Eigenschaft wird in der Regel verwendet, um die Zellen in einem Abschnitt oder einer Zeile zu durchlaufen. Verwenden Sie die Cells-Eigenschaft, um eine einzelne Zelle abzurufen, und geben Sie einen Zellennamen an. Zum Beispiel:

Set vsoCell = Cells("PinX")

Wenn Ihre Visual Studio-Lösung die Referenz Microsoft.Office.Interop.Visio enthält, wird diese Eigenschaft den folgenden Typen zugeordnet:

  • Microsoft.Office.Interop.Visio.IVShape.get_CellsSRC

Beispiel

Das folgende VBA-Makro (Microsoft Visual Basic für Applikationen) zeigt, wie die CellsSRC-Eigenschaft verwendet werden kann, um eine bestimmt ShapeSheet-Zelle nach Abschnitts-, Zeilen- und Spaltenindex festzulegen. Es wird ein Rechteck auf ein Zeichenblatt gezeichnet, dessen Linien gebogen oder gekrümmt werden, indem die Linien des Shapes in Bögen geändert werden. Anschließend zeichnet das Makro ein inneres Rechteck, das innerhalb der gebogenen Linien des ersten Rechtecks liegt.

 
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

Support und Feedback

Haben Sie Fragen oder Feedback zu Office VBA oder zu dieser Dokumentation? Unter Office VBA-Support und Feedback finden Sie Hilfestellung zu den Möglichkeiten, wie Sie Support erhalten und Feedback abgeben können.