PictureFormat.OriginalIsTrueColor property (Publisher)
Returns an MsoTriState constant indicating whether the specified linked picture or OLE object contains color data of 24 bits per channel or greater. Read-only.
Syntax
expression.OriginalIsTrueColor
expression A variable that represents a PictureFormat object.
Return value
MsoTriState
Remarks
This property only applies to linked pictures or OLE objects. It returns "Permission Denied" for shapes representing embedded or pasted pictures and OLE objects.
Use either of the following properties to determine whether a shape represents a linked picture:
The OriginalIsTrueColor property value can be one of the MsoTriState constants declared in the Microsoft Office type library and shown in the following table.
Constant | Description |
---|---|
msoFalse | The specified linked picture does not contain color data of 24 bits per channel or greater. |
msoTriStateMixed | Indicates a combination of msoTrue and msoFalse for the specified shape range. |
msoTrue | The specified linked picture contains color data of 24 bits per channel or greater. |
Example
The following example returns a list of pictures in the active document that are TrueColor. If a picture is linked, and the linked picture is also TrueColor, that information is also returned.
Sub PictureColorInformation()
Dim pgLoop As Page
Dim shpLoop As Shape
For Each pgLoop In ActiveDocument.Pages
For Each shpLoop In pgLoop.Shapes
If shpLoop.Type = pbLinkedPicture Or shpLoop.Type = pbPicture Then
With shpLoop.PictureFormat
If .IsEmpty = msoFalse Then
If .IsTrueColor = msoTrue Then
Debug.Print .Filename
Debug.Print "This picture is TrueColor"
If .IsLinked = msoTrue Then
If .OriginalIsTrueColor = msoTrue Then
Debug.Print "The linked picture is also TrueColor."
End If
End If
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.