PictureFormat.HasTransparencyColor property (Publisher)
Returns a Boolean that indicates whether a transparency color has been applied to the specified picture. Read-only.
Syntax
expression.HasTransparencyColor
expression A variable that represents a PictureFormat object.
Return value
Boolean
Example
The following example returns a list of the pictures with transparency colors in the active publication.
Sub ListPicturesWithTransColors()
Dim pgLoop As Page
Dim shpLoop As Shape
For Each pgLoop In ActiveDocument.Pages
For Each shpLoop In pgLoop.Shapes
If shpLoop.Type = pbPicture Or shpLoop.Type = pbLinkedPicture Then
With shpLoop.PictureFormat
If .IsEmpty = msoFalse Then
If .HasTransparencyColor = True Then
Debug.Print .Filename
End If
End If
End With
End If
Next shpLoop
Next pgLoop
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.