diagrams-lib-0.4: Embedded domain-specific language for declarative graphics

Maintainerdiagrams-discuss@googlegroups.com

Diagrams.Segment

Contents

Description

Generic functionality for constructing and manipulating linear or cubic Bezier segments.

Synopsis

Constructing segments

data Segment v Source

The atomic constituents of paths are segments, which are single straight lines or cubic Bezier curves. Segments are translationally invariant, that is, they have no particular "location" and are unaffected by translations. They are, however, affected by other transformations such as rotations and scales.

Constructors

Linear v

A linear segment with given offset.

Cubic v v v

A cubic bezier segment specified by three offsets from the starting point to the first control point, second control point, and ending point, respectively.

Instances

Functor Segment 
Eq v => Eq (Segment v) 
Ord v => Ord (Segment v) 
Show v => Show (Segment v) 
(InnerSpace v, OrderedField (Scalar v)) => Boundable (Segment v)

The bounding function for a segment is based at the segment's start.

HasLinearMap v => Transformable (Segment v) 
(Show v, HasLinearMap v) => Renderable (Segment v) ShowBackend 

straight :: v -> Segment vSource

straight v constructs a translationally invariant linear segment with direction and length given by the vector v.

bezier3 :: v -> v -> v -> Segment vSource

bezier3 v1 v2 v3 constructs a translationally invariant cubic Bezier curve where the offsets from the first endpoint to the first and second control point and endpoint are respectively given by v1, v2, and v3.

Computing with segments

atParam :: (VectorSpace v, Num (Scalar v)) => Segment v -> Scalar v -> vSource

atParam yields a parametrized view of segments as continuous functions [0,1] -> v, which give the offset from the start of the segment for each value of the parameter between 0 and 1. It is designed to be used infix, like seg `atParam` 0.5.

segOffset :: Segment v -> vSource

Compute the offset from the start of a segment to the end. Note that in the case of a Bezier segment this is not the same as the length of the curve itself; for that, see arcLength.

reverseSegment :: AdditiveGroup v => Segment v -> Segment vSource

Reverse the direction of a segment.

splitAtParam :: VectorSpace v => Segment v -> Scalar v -> (Segment v, Segment v)Source

splitAtParam splits a segment s into two new segments (l,r) at the parameter t where l corresponds to the portion of s for parameter values from 0 to t and r for s from t to 1. The following should hold for splitting:

 paramSplit s t u
   | u < t     = atParam s u == atParam l (u / t)
   | otherwise = atParam s u == atParam s t ^+^ atParam l ((u - t) / (1.0 - t))
   where (l,r) = splitAtParam s t

That is to say, the parameterization scales linearly with splitting.

splitAtParam can also be used with parameters outside the range (0,1). For example, using the parameter 2 gives two result segments where the first is the original segment extended to the parameter 2, and the second result segment travels backwards from the end of the first to the end of the original segment.

arcLength :: (InnerSpace v, Floating (Scalar v), Ord (Scalar v)) => Segment v -> Scalar v -> Scalar vSource

arcLength s m approximates the arc length of the segment curve s with accuracy of at least plus or minus m. For a Cubic segment this is computed by subdividing until the arc length of the path through the control points is within m of distance from start to end.

arcLengthToParam :: (InnerSpace v, Floating (Scalar v), Ord (Scalar v), AdditiveGroup v) => Segment v -> Scalar v -> Scalar v -> Scalar vSource

arcLengthToParam s l m converts the absolute arc length l, measured from the segment starting point, to a parameter on the segment s, with accuracy of at least plus or minus m. Works for any arc length, and may return any parameter value (not just parameters between 0 and 1).

Adjusting segments

adjustSegment :: (InnerSpace v, OrderedField (Scalar v)) => Segment v -> AdjustOpts v -> Segment vSource

Adjust the length of a segment. The second parameter is an option record which controls how the adjustment should be performed; see AdjustOpts.

data AdjustOpts v Source

How should a segment, trail, or path be adjusted?

Constructors

ALO 

Instances

data AdjustMethod v Source

What method should be used for adjusting a segment, trail, or path?

Constructors

ByParam (Scalar v)

Extend by the given parameter value (use a negative parameter to shrink)

ByAbsolute (Scalar v)

Extend by the given arc length (use a negative length to shrink)

ToAbsolute (Scalar v)

Extend or shrink to the given arc length

Instances

data AdjustSide Source

Which side of a segment, trail, or path should be adjusted?

Constructors

Start

Adjust only the beginning

End

Adjust only the end

Both

Adjust both sides equally

adjustSegmentToParams :: (Fractional (Scalar v), VectorSpace v) => Segment v -> Scalar v -> Scalar v -> Segment vSource

Given a segment and parameters t1, t2, produce the segment which lies on the (infinitely extended) original segment beginning at t1 and ending at t2.

Fixed (absolutely located) segments

data FixedSegment v Source

FixedSegments are like Segments except that they have absolute locations.

Constructors

FLinear (Point v) (Point v) 
FCubic (Point v) (Point v) (Point v) (Point v) 

mkFixedSeg :: AdditiveGroup v => Point v -> Segment v -> FixedSegment vSource

Create a FixedSegment from a starting point and a Segment.

fAtParam :: VectorSpace v => FixedSegment v -> Scalar v -> Point vSource

Compute the point on a fixed segment at a given parameter. A parameter of 0 corresponds to the starting point and 1 corresponds to the ending point.