Previous Document Next Document

Object Model Reference : Classes : S : SegmentRange : Methods : SegmentRange.Remove


SegmentRange.Remove

Sub Remove(Index As Long)

Description

Member of SegmentRange

The Remove method removes a specified segment from a segment range without affecting the segment itself.

Parameter
Description
Index
Specifies the segment to be removed

VBA example

The following VBA example highlights each curve segment that is adjacent to a cusp node, using a red stroke.

Sub Test()
 Dim s As Shape
 Dim sgr As SegmentRange
 Dim seg As Segment
 Dim i As Long
 Set sgr = ActiveShape.Curve.Segments.All
 For i = sgr.Count To 1 Step -1
  Set seg = sgr(i)
  If seg.Type = cdrLineSegment Then
   sgr.Remove i
  Else
   If seg.StartNode.Type <> cdrCuspNode And seg.EndNode.Type <> cdrCuspNode Then
    sgr.Remove i
   End If
  End If
 Next i
 For Each seg In sgr
  Set s = ActiveLayer.CreateCurveSegment(seg.StartNode.PositionX, seg.StartNode.PositionY, _
   seg.EndNode.PositionX, seg.EndNode.PositionY, _
   seg.StartingControlPointLength, seg.StartingControlPointAngle, _
   seg.EndingControlPointLength, seg.EndingControlPointAngle)
  s.Outline.Width = 0.01
  s.Outline.Color.RGBAssign 255, 0, 0
 Next seg
End Sub

Previous Document Next Document Back to Top

Copyright 2013 Corel Corporation. All rights reserved.