Connect.FromPart-Eigenschaft (Visio)
Gibt den Teil eines Shapes zurück, aus dem eine Verbindung stammt. Schreibgeschützt.
Syntax
Ausdruck. FromPart
Ausdruck Eine Variable, die ein Connect-Objekt darstellt.
Rückgabewert
Ganze Zahl
Hinweise
Die folgenden Konstanten, die in der Microsoft Visio-Typbibliothek deklariert werden, zeigen Rückgabewerte für die FromPart-Eigenschaft an.
Konstante | Wert |
---|---|
visConnectFromError | -1 |
visFromNone | 0 |
visLeftEdge | 1 |
visCenterEdge | 2 |
visRightEdge | 3 |
visBottomEdge | 4 |
visMiddleEdge | 5 |
visTopEdge | 6 |
visBeginX | 7 |
visBeginY | 8 |
visBegin | 9 |
visEndX | 10 |
visEndY | 11 |
visEnd | 12 |
visFromAngle | 13 |
visFromPin | 14 |
visControlPoint | 100 + auf Null basierendem Zeilenindex (z. B. visControlPoint = 100, wenn sich der Kontrollpunkt in Zeile 0 befindet; visControlPoint = 101 wenn sich der Kontrollpunkt in Zeile 1 befindet) |
Beispiel
Dieses VBA-Makro (Microsoft Visual Basic für Applikationen) veranschaulicht, wie Sie Verbindungsinformationen aus einer Visio-Zeichnung extrahieren. Das Beispiel zeigt die Verbindungsinformationen im Direktfenster an.
Dieses Beispiel setzt voraus, dass ein aktives Dokument mindestens zwei verbundene Shapes enthält.
Public Sub FromPart_Example()
Dim vsoShapes As Visio.Shapes
Dim vsoShape As Visio.Shape
Dim vsoConnectFrom As Visio.Shape
Dim intFromData As Integer
Dim strFrom As String
Dim vsoConnects As Visio.Connects
Dim vsoConnect As Visio.Connect
Dim intCurrentShapeIndex As Integer
Dim intCounter As Integer
Set vsoShapes = ActivePage.Shapes
'For each shape on the page, get its connections.
For intCurrentShapeIndex = 1 To vsoShapes.Count
Set vsoShape = vsoShapes(intCurrentShapeIndex)
Set vsoConnects = vsoShape.Connects
'For each connection, get the shape it originates from
'and the part of the shape it originates from,
'and print that information in the Immediate window.
For intCounter = 1 To vsoConnects.Count
Set vsoConnect = vsoConnects(intCounter)
Set vsoConnectFrom = vsoConnect.FromSheet
intFromData = vsoConnect.FromPart
'FromPart property values
If intFromData = visConnectError Then
strFrom = "error"
ElseIf intFromData = visNone Then
strFrom = "none"
ElseIf intFromData = visLeftEdge Then
strFrom = "left"
ElseIf intFromData = visCenterEdge Then
strFrom = "center"
ElseIf intFromData = visRightEdge Then
strFrom = "right"
ElseIf intFromData = visBottomEdge Then
strFrom = "bottom"
ElseIf intFromData = visMiddleEdge Then
strFrom = "middle"
ElseIf intFromData = visTopEdge Then
strFrom = "top"
ElseIf intFromData = visBeginX Then
strFrom = "beginX"
ElseIf intFromData = visBeginY Then
strFrom = "beginY"
ElseIf intFromData = visBegin Then
strFrom = "begin"
ElseIf intFromData = visEndX Then
strFrom = "endX"
ElseIf intFromData = visEndY Then
strFrom = "endY"
ElseIf intFromData = visEnd Then
strFrom = "end"
ElseIf intFromData >= visControlPoint Then
strFrom = "controlPt_" & _
Str(intFromData - visControlPoint + 1)
Else
strFrom = "???"
End If
Debug.Print vsoConnectFrom.Name & " " & strFrom
Next intCounter
Next intCurrentShapeIndex
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.