Partager via


Propriété Connect.FromPart (Visio)

Renvoie la partie d'une forme à l'origine d'une connexion. En lecture seule.

Syntaxe

expression. FromPart

expression Variable qui représente un objet Connect .

Valeur renvoyée

Entier

Remarques

Les constantes suivantes, déclarées dans la bibliothèque de types de Microsoft Visio, indiquent les valeurs renvoyées par la propriété FromPart.

Constante Valeur
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 + index de ligne de base 0 (par exemple, visControlPoint = 100 si le point de contrôle se trouve à la ligne 0 ; visControlPoint = 101 si le point de contrôle se trouve à la ligne 1)

Exemple

Cette macro Microsoft Visual Basic pour Applications (VBA) indique comment extraire des informations de connexion à partir d'un dessin Visio. L'exemple affiche les informations de connexion dans la fenêtre Exécution.

L'exemple implique qu'il y ait un document actif contenant au moins deux formes connectées.

 
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

Assistance et commentaires

Avez-vous des questions ou des commentaires sur Office VBA ou sur cette documentation ? Consultez la rubrique concernant l’assistance pour Office VBA et l’envoi de commentaires afin d’obtenir des instructions pour recevoir une assistance et envoyer vos commentaires.