ShapeRange.Distribute method (Publisher)

Evenly distributes the shapes in the specified shape range.

Syntax

expression.Distribute (DistributeCmd, RelativeTo)

expression A variable that represents a ShapeRange object.

Parameters

Name Required/Optional Data type Description
DistributeCmd Required MsoDistributeCmd Specifies whether shapes are to be distributed horizontally or vertically. Can be one of the MsoDistributeCmd constants declared in the Microsoft Office type library.
RelativeTo Required MsoTriState Specifies whether to distribute the shapes evenly over the entire horizontal or vertical space on the page or within the horizontal or vertical space that the range of shapes originally occupies.

Remarks

Shapes are distributed so that there is an equal amount of space between one shape and the next. If the shapes are so large that they overlap when distributed over the available space, they are distributed so that there is an equal amount of overlap between one shape and the next.

The RelativeTo parameter can be one of the MsoTriState constants declared in the Microsoft Office type library and shown in the following table.

Constant Description
msoFalse Distributes the shapes within the horizontal or vertical space that the range of shapes originally occupies.
msoTrue Distributes the shapes evenly over the entire horizontal or vertical space on the page.

When RelativeTo is msoTrue, shapes are distributed so that the distance between the two outer shapes and the edges of the page is the same as the distance between one shape and the next. If the shapes must overlap, the two outer shapes are moved to the edges of the page.

When RelativeTo is msoFalse, the two outer shapes are not moved; only the positions of the inner shapes are adjusted.

The z-order of shapes is unaffected by this method.

Example

This example defines a shape range that contains all the AutoShapes on the first page of the active publication, and then horizontally distributes the shapes in this range.

' Number of shapes on the page. 
Dim intShapes As Integer 
' Number of AutoShapes on the page. 
Dim intAutoShapes As Integer 
' An array of the names of the AutoShapes. 
Dim arrAutoShapes() As String 
' A looping variable. 
Dim shpLoop As Shape 
' A placeholder variable for the range containing AutoShapes. 
Dim shpRange As ShapeRange 
 
With ActiveDocument.Pages(1).Shapes 
 ' Count all the shapes on the page. 
 intShapes = .Count 
 
 ' Proceed only if there's at least one shape. 
 If intShapes > 1 Then 
 intAutoShapes = 0 
 ReDim arrAutoShapes(1 To intShapes) 
 
 ' Loop through the shapes on the page and add the names 
 ' of any AutoShapes to an array. 
 For Each shpLoop In ActiveDocument.Pages(1).Shapes 
 If shpLoop.Type = msoAutoShape Then 
 intAutoShapes = intAutoShapes + 1 
 arrAutoShapes(intAutoShapes) = shpLoop.Name 
 End If 
 Next shpLoop 
 
 ' Proceed only if there's at least one AutoShape. 
 If intAutoShapes > 1 Then 
 ReDim Preserve arrAutoShapes(1 To intAutoShapes) 
 
 ' Create a shape range containing all the AutoShapes. 
 Set shpRange = .Range(Index:=arrAutoShapes) 
 
 ' Distribute the AutoShapes horizontally 
 ' in the space they already occupy. 
 shpRange.Distribute _ 
 DistributeCmd:=msoDistributeHorizontally, RelativeTo:=msoFalse 
 End If 
 End If 
End With 

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.