ThreeDFormat.ExtrusionColorType property (PowerPoint)

Returns or sets a value that indicates whether the extrusion color is based on the extruded shape's fill (the front face of the extrusion) and automatically changes when the shape's fill changes, or whether the extrusion color is independent of the shape's fill. Read/write.

Syntax

expression. ExtrusionColorType

expression A variable that represents an ThreeDFormat object.

Return value

MsoExtrusionColorType

Remarks

The value of the ExtrusionColorType property can be one of these MsoExtrusionColorType constants.

Constant Description
msoExtrusionColorAutomatic Extrusion color is based on shape fill.
msoExtrusionColorCustom Extrusion color is independent of shape fill.
msoExtrusionColorTypeMixed Extrusion color is partially independent of shape fill.

Example

If shape one on myDocument has an automatic extrusion color, this example gives the extrusion a custom yellow color.

Set myDocument = ActivePresentation.Slides(1)

With myDocument.Shapes(1).ThreeD

    If .ExtrusionColorType = msoExtrusionColorAutomatic Then

        .ExtrusionColor.RGB = RGB(240, 235, 16)

    End If

End With

See also

ThreeDFormat Object

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.