Previous Document Next Document

Object Model Reference : Classes : O : Outline : Properties : Outline.Color


Outline.Color

Property Color As Color

Description

Member of Outline

The Color property returns or specifies the color of an outline.

VBA example 1

The following VBA example converts to grayscale all outline colors of all objects on the active page.

Sub Test()
 Dim s As Shape
 For Each s In ActivePage.Shapes
  If s.Outline.Type = cdrOutline Then
   s.Outline.Color.ConvertToGray
  End If
 Next s
End Sub
VBA example 2

The following VBA example creates a copy of the selected object’s outline as a set of shapes — one for each curve segment. It then applies a color that gradually changes from black to red to each subsequent segment, causing the effect of a fountain fill on path.

Sub Test()
 Dim seg As Segment
 Dim sr As New ShapeRange
 Dim s As Shape, st As Shape
 Dim Steps As Long
 Set s = ActiveShape
 Optimization = True
 If s Is Nothing Then
  MsgBox "Nothing is selected."
  Exit Sub
 End If
 If s.Type <> cdrCurveShape Then
  MsgBox "A curve must be selected. Try again."
  Exit Sub
 End If
 If s.Outline.Type = cdrNoOutline Then
  MsgBox "The curve must have an outline. Try again."
  Exit Sub
 End If
 Steps = s.Curve.Segments.Count
 For Each seg In s.Curve.Segments
  Select Case seg.Type
   Case cdrLineSegment
    Set st = ActiveLayer.CreateLineSegment( _
      seg.StartNode.PositionX, seg.StartNode.PositionY, _
      seg.EndNode.PositionX, seg.EndNode.PositionY)
   Case cdrCurveSegment
    Set st = ActiveLayer.CreateCurveSegment( _
      seg.StartNode.PositionX, seg.StartNode.PositionY, _
      seg.EndNode.PositionX, seg.EndNode.PositionY, _
      seg.StartingControlPointLength, _
      seg.StartingControlPointAngle, _
      seg.EndingControlPointLength, _
      seg.EndingControlPointAngle)
  End Select
  st.Outline.Width = s.Outline.Width
  st.Outline.Color.RGBAssign 255 * seg.Index / Steps, 0, 0
  sr.Add st
 Next seg
 sr.Group
 Optimization = False
 ActiveWindow.Refresh
End Sub

Previous Document Next Document Back to Top

Copyright 2013 Corel Corporation. All rights reserved.