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

Copyright(c) 2011-2013 diagrams-lib team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone
LanguageHaskell2010

Diagrams.Segment

Contents

Description

A segment is a translation-invariant, atomic path. Currently, there are two types: linear (i.e. just a straight line to the endpoint) and cubic Bézier curves (i.e. a curve to an endpoint with two control points). This module contains tools for creating and manipulating segments, as well as a definition of segments with a fixed location (useful for backend implementors).

Generally speaking, casual users of diagrams should not need this module; the higher-level functionality provided by Diagrams.Trail, Diagrams.TrailLike, and Diagrams.Path should usually suffice. However, directly manipulating segments can occasionally be useful.

Synopsis

Open/closed tags

data Open Source

Type tag for open segments.

data Closed Source

Type tag for closed segments.

Instances

(VectorSpace v, Num (Scalar v)) => EndValues (Tangent (Segment Closed v)) 
(VectorSpace v, Num (Scalar v)) => Parametric (Tangent (Segment Closed v)) 
(OrderedField (Scalar v), InnerSpace v) => Measured (SegMeasure v) (Segment Closed v) 
(InnerSpace v, OrderedField (Scalar v)) => Enveloped (Segment Closed v)

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

Traced (Segment Closed R2) 
(InnerSpace v, Floating (Scalar v), Ord (Scalar v), AdditiveGroup v) => HasArcLength (Segment Closed v) 
(VectorSpace v, Fractional (Scalar v)) => Sectionable (Segment Closed v) 
(VectorSpace v, Num (Scalar v)) => EndValues (Segment Closed v) 
Num (Scalar v) => DomainBounds (Segment Closed v) 
(VectorSpace v, Num (Scalar v)) => Parametric (Segment Closed v)

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.

type Codomain (Tangent (Segment Closed v)) = Codomain (Segment Closed v) 
type Codomain (Segment Closed v) = v 

Segment offsets

data Offset c v where Source

The offset of a segment is the vector from its starting point to its end. The offset for an open segment is determined by the context, i.e. its endpoint is not fixed. The offset for a closed segment is stored explicitly, i.e. its endpoint is at a fixed offset from its start.

Constructors

OffsetOpen :: Offset Open v 
OffsetClosed :: !v -> Offset Closed v 

Instances

Functor (Offset c) 
Eq v => Eq (Offset c v) 
Ord v => Ord (Offset c v) 
Show v => Show (Offset c v) 
HasLinearMap v => Transformable (Offset c v) 
type V (Offset c v) = v 

segOffset :: Segment Closed v -> v Source

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

Constructing and modifying segments

data Segment c v Source

The atomic constituents of the concrete representation currently used for trails are segments, currently limited to single straight lines or cubic Bézier 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 !(Offset c v)

A linear segment with given offset.

Cubic !v !v !(Offset c v)

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

Instances

Functor (Segment c) 
(VectorSpace v, Num (Scalar v)) => EndValues (Tangent (Segment Closed v)) 
(VectorSpace v, Num (Scalar v)) => Parametric (Tangent (Segment Closed v)) 
(OrderedField (Scalar v), InnerSpace v) => Measured (SegMeasure v) (Segment Closed v) 
Eq v => Eq (Segment c v) 
Ord v => Ord (Segment c v) 
Show v => Show (Segment c v) 
(InnerSpace v, OrderedField (Scalar v)) => Enveloped (Segment Closed v)

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

Traced (Segment Closed R2) 
HasLinearMap v => Transformable (Segment c v) 
(InnerSpace v, Floating (Scalar v), Ord (Scalar v), AdditiveGroup v) => HasArcLength (Segment Closed v) 
(VectorSpace v, Fractional (Scalar v)) => Sectionable (Segment Closed v) 
(VectorSpace v, Num (Scalar v)) => EndValues (Segment Closed v) 
Num (Scalar v) => DomainBounds (Segment Closed v) 
(VectorSpace v, Num (Scalar v)) => Parametric (Segment Closed v)

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.

HasLinearMap v => Renderable (Segment c v) NullBackend 
(Show v, HasLinearMap v) => Renderable (Segment o v) ShowBackend 
type Codomain (Tangent (Segment Closed v)) = Codomain (Segment Closed v) 
type V (Segment c v) = v 
type Codomain (Segment Closed v) = v 

straight :: v -> Segment Closed v Source

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

bezier3 :: v -> v -> v -> Segment Closed v Source

bezier3 c1 c2 x constructs a translationally invariant cubic Bézier curve where the offsets from the first endpoint to the first and second control point and endpoint are respectively given by c1, c2, and x.

bézier3 :: v -> v -> v -> Segment Closed v Source

bézier3 is the same as bezier3, but with more snobbery.

reverseSegment :: AdditiveGroup v => Segment Closed v -> Segment Closed v Source

Reverse the direction of a segment.

Fixed (absolutely located) segments

data FixedSegment v Source

FixedSegments are like Segments except that they have absolute locations. FixedSegment v is isomorphic to Located (Segment Closed v), as witnessed by mkFixedSeg and fromFixedSeg, but FixedSegment is convenient when one needs the absolute locations of the vertices and control points.

Constructors

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

fromFixedSeg :: AdditiveGroup v => FixedSegment v -> Located (Segment Closed v) Source

Convert a FixedSegment back into a located Segment.

Segment measures

Trails store a sequence of segments in a fingertree, which can automatically track various monoidal "measures" on segments.

newtype ArcLength v Source

A type to represent the total arc length of a chain of segments. The first component is a "standard" arc length, computed to within a tolerance of 10e-6. The second component is a generic arc length function taking the tolerance as an argument.

Constructors

ArcLength (Sum (Interval (Scalar v)), Scalar v -> Sum (Interval (Scalar v))) 

getArcLengthCached :: ArcLength v -> Interval (Scalar v) Source

Project out the cached arc length, stored together with error bounds.

getArcLengthFun :: ArcLength v -> Scalar v -> Interval (Scalar v) Source

Project out the generic arc length function taking the tolerance as an argument.

getArcLengthBounded :: (Num (Scalar v), Ord (Scalar v)) => Scalar v -> ArcLength v -> Interval (Scalar v) Source

Given a specified tolerance, project out the cached arc length if it is accurate enough; otherwise call the generic arc length function with the given tolerance.

newtype TotalOffset v Source

A type to represent the total cumulative offset of a chain of segments.

Constructors

TotalOffset v 

data OffsetEnvelope v Source

A type to represent the offset and envelope of a chain of segments. They have to be paired into one data structure, since combining the envelopes of two consecutive chains needs to take the offset of the the offset of the first into account.

Constructors

OffsetEnvelope 

type SegMeasure v = SegCount ::: (ArcLength v ::: (OffsetEnvelope v ::: ())) Source

SegMeasure collects up all the measurements over a chain of segments.