Page.ShapeIDsToUniqueIDs method (Visio)

Returns an array of unique IDs of shapes on the page, as specified by their shape IDs.

Syntax

expression. ShapeIDsToUniqueIDs( _ShapeIDs()_ , _UniqueIDArgs_ , _GUIDs()_ )

expression An expression that returns a Page object.

Parameters

Name Required/Optional Data type Description
ShapeIDs() Required Long An array of type Long of shape IDs corresponding to a set of shapes on the active drawing page.
UniqueIDArgs Required VisUniqueIDArgs Gets, deletes, or makes the unique ID of a Shape object. See Remarks for possible values.
GUIDs() Required String Out parameter. An empty array that the method fills with unique IDs of type String corresponding to the shapes specified in ShapeIDs()

Return value

Nothing

Remarks

Microsoft Visio identifies shapes by two different IDs: shape IDs and unique IDs. Shape IDs are numeric and uniquely identify shapes within the scope of an individual drawing page. They are not unique within a wider scope, however.

Unique IDs are globally unique identifiers (GUIDs). They are unique within the scope of the application.

To convert between shape IDs and unique IDs, you can use two methods of the Page object, ShapeIDsToUniqueIDs and UniqueIDsToShapeIDs.

By default, a shape does not have a unique ID. A shape acquires a unique ID only if you set its Shape.UniqueID property. If a Shape object has a unique ID, no other shape in any other document will have the same ID.

The UniqueIDArgs parameter sets and controls the behavior of the UniqueID property for all the shapes in ShapeIDs(). UniqueIDArgs should have one of the following values declared in the Visio type library in VisUniqueIDArgs.

Constant Value Description
visGetGUID 0 Returns the unique ID string only if the shape already has a unique ID. Otherwise it returns a zero-length string ("").
visGetOrMakeGUID 1 Returns the unique ID string of the shape. If the shape does not yet have a unique ID, it assigns one to the shape and returns the new ID.
visDeleteGUID 2 Deletes the unique ID of a shape and returns a zero-length string ("").
visGetOrMakeGUIDWithUndo 3 Returns the unique ID string of the shape. If the shape does not already have a unique ID, assigns one to the shape and returns the new ID. Undoable.
visDeleteGUIDWithUndo 4 Clears the unique ID of a shape and returns a zero-length string (""). Undoable.

Example

The following Microsoft Visual Basic for Applications (VBA) macro shows how to use the ShapeIDsToUniqueIDs method to determine the unique IDs of the shapes on the page passed to the method. It iterates through all the shapes on the active drawing page, using the Shape.UniqueID property to get the shape IDs of the shapes, and then passes an array of those IDs to the ShapeIDsToUniqueIDs method as the ShapeIDs() parameter to get the unique IDs of the shapes. For the UniqueIDArgs parameter, it passes the value visGetOrMakeGUID, telling Visio to create a unique ID for any shape that doesn't already have one. It prints the unique IDs and shape IDs to the Immediate window.

Before running this macro, open a Visio drawing and place several shapes on the active drawing page.

Public Sub ShapeIDsToUniqueIDs_Example()
    Dim vsoShape As Visio.Shape 
    Dim intArrayCounter As Integer 
     
    intShapeCount = ActivePage.Shapes.Count 
     
    ReDim alngShapeIDs(intShapeCount - 1) As Long 
    ReDim astrUniqueIDs(intShapeCount - 1) As String 
     
    intArrayCounter = 0 
         
    For Each vsoShape In ActivePage.Shapes 
        alngShapeIDs(intArrayCounter) = vsoShape.ID 
        Debug.Print alngShapeIDs(intArrayCounter) 
        intArrayCounter = intArrayCounter + 1 
    Next 
     
    ActivePage.ShapeIDsToUniqueIDs alngShapeIDs, visGetOrMakeGUID, astrUniqueIDs 
     
    intArrayCounter = 0 
     
    For intArrayCounter = LBound(astrUniqueIDs) To UBound(astrUniqueIDs) 
        Debug.Print astrUniqueIDs(intArrayCounter) 
    Next 
 
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.