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

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

Diagrams.Parametric

Description

Type classes for things which are parameterized in some way, e.g. segments and trails.

Synopsis

Documentation

stdTolerance :: Fractional a => a #

The standard tolerance used by std... functions (like stdArcLength and stdArcLengthToParam, currently set at 1e-6.

type family Codomain p :: * -> * #

Codomain of parametric classes. This is usually either (V p), for relative vector results, or (Point (V p)), for functions with absolute coordinates.

Instances
type Codomain (BernsteinPoly n) # 
Instance details

Defined in Diagrams.TwoD.Segment.Bernstein

type Codomain (Located a) # 
Instance details

Defined in Diagrams.Located

type Codomain (Tangent t) # 
Instance details

Defined in Diagrams.Tangent

type Codomain (Tangent t) = V t
type Codomain (GetSegment t) # 
Instance details

Defined in Diagrams.Trail

type Codomain (FixedSegment v n) # 
Instance details

Defined in Diagrams.Segment

type Codomain (FixedSegment v n) = Point v
type Codomain (Trail v n) # 
Instance details

Defined in Diagrams.Trail

type Codomain (Trail v n) = v
type Codomain (SegTree v n) # 
Instance details

Defined in Diagrams.Trail

type Codomain (SegTree v n) = v
type Codomain (Segment Closed v n) # 
Instance details

Defined in Diagrams.Segment

type Codomain (Segment Closed v n) = v
type Codomain (Trail' l v n) # 
Instance details

Defined in Diagrams.Trail

type Codomain (Trail' l v n) = v

class Parametric p where #

Type class for parametric functions.

Methods

atParam :: p -> N p -> Codomain p (N p) #

atParam yields a parameterized view of an object as a continuous function. It is designed to be used infix, like path `atParam` 0.5.

Instances
Fractional n => Parametric (BernsteinPoly n) # 
Instance details

Defined in Diagrams.TwoD.Segment.Bernstein

(InSpace v n a, Parametric a, Codomain a ~ v) => Parametric (Located a) # 
Instance details

Defined in Diagrams.Located

Methods

atParam :: Located a -> N (Located a) -> Codomain (Located a) (N (Located a)) #

Parametric (Tangent t) => Parametric (Tangent (Located t)) # 
Instance details

Defined in Diagrams.Tangent

Methods

atParam :: Tangent (Located t) -> N (Tangent (Located t)) -> Codomain (Tangent (Located t)) (N (Tangent (Located t))) #

(Additive v, Num n) => Parametric (Tangent (FixedSegment v n)) # 
Instance details

Defined in Diagrams.Tangent

(Additive v, Num n) => Parametric (Tangent (Segment Closed v n)) # 
Instance details

Defined in Diagrams.Tangent

(Metric v, OrderedField n, Real n) => Parametric (Tangent (Trail v n)) # 
Instance details

Defined in Diagrams.Trail

Methods

atParam :: Tangent (Trail v n) -> N (Tangent (Trail v n)) -> Codomain (Tangent (Trail v n)) (N (Tangent (Trail v n))) #

(Parametric (GetSegment (Trail' c v n)), Additive v, Num n) => Parametric (Tangent (Trail' c v n)) # 
Instance details

Defined in Diagrams.Trail

Methods

atParam :: Tangent (Trail' c v n) -> N (Tangent (Trail' c v n)) -> Codomain (Tangent (Trail' c v n)) (N (Tangent (Trail' c v n))) #

(Metric v, OrderedField n, Real n) => Parametric (GetSegment (Trail v n)) # 
Instance details

Defined in Diagrams.Trail

Methods

atParam :: GetSegment (Trail v n) -> N (GetSegment (Trail v n)) -> Codomain (GetSegment (Trail v n)) (N (GetSegment (Trail v n))) #

(Metric v, OrderedField n, Real n) => Parametric (GetSegment (Trail' Loop v n)) #

The parameterization for loops wraps around, i.e. parameters are first reduced "mod 1".

Instance details

Defined in Diagrams.Trail

(Metric v, OrderedField n) => Parametric (GetSegment (Trail' Line v n)) #

Parameters less than 0 yield the first segment; parameters greater than 1 yield the last. A parameter exactly at the junction of two segments yields the second segment (i.e. the one with higher parameter values).

Instance details

Defined in Diagrams.Trail

(Additive v, Num n) => Parametric (FixedSegment v n) # 
Instance details

Defined in Diagrams.Segment

Methods

atParam :: FixedSegment v n -> N (FixedSegment v n) -> Codomain (FixedSegment v n) (N (FixedSegment v n)) #

(Metric v, OrderedField n, Real n) => Parametric (Trail v n) # 
Instance details

Defined in Diagrams.Trail

Methods

atParam :: Trail v n -> N (Trail v n) -> Codomain (Trail v n) (N (Trail v n)) #

(Metric v, OrderedField n, Real n) => Parametric (SegTree v n) # 
Instance details

Defined in Diagrams.Trail

Methods

atParam :: SegTree v n -> N (SegTree v n) -> Codomain (SegTree v n) (N (SegTree v n)) #

(Additive v, Num n) => Parametric (Segment Closed v n) #

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.

Instance details

Defined in Diagrams.Segment

Methods

atParam :: Segment Closed v n -> N (Segment Closed v n) -> Codomain (Segment Closed v n) (N (Segment Closed v n)) #

(Metric v, OrderedField n, Real n) => Parametric (Trail' l v n) # 
Instance details

Defined in Diagrams.Trail

Methods

atParam :: Trail' l v n -> N (Trail' l v n) -> Codomain (Trail' l v n) (N (Trail' l v n)) #

class DomainBounds p where #

Type class for parametric functions with a bounded domain. The default bounds are [0,1].

Note that this domain indicates the main "interesting" portion of the function. It must be defined within this range, but for some instances may still have sensible values outside.

Minimal complete definition

Nothing

Methods

domainLower :: p -> N p #

domainLower defaults to being constantly 0 (for vector spaces with numeric scalars).

domainLower :: Num (N p) => p -> N p #

domainLower defaults to being constantly 0 (for vector spaces with numeric scalars).

domainUpper :: p -> N p #

domainUpper defaults to being constantly 1 (for vector spaces with numeric scalars).

domainUpper :: Num (N p) => p -> N p #

domainUpper defaults to being constantly 1 (for vector spaces with numeric scalars).

Instances
Num n => DomainBounds (BernsteinPoly n) # 
Instance details

Defined in Diagrams.TwoD.Segment.Bernstein

DomainBounds a => DomainBounds (Located a) # 
Instance details

Defined in Diagrams.Located

Methods

domainLower :: Located a -> N (Located a) #

domainUpper :: Located a -> N (Located a) #

DomainBounds t => DomainBounds (Tangent t) # 
Instance details

Defined in Diagrams.Tangent

Methods

domainLower :: Tangent t -> N (Tangent t) #

domainUpper :: Tangent t -> N (Tangent t) #

DomainBounds t => DomainBounds (GetSegment t) # 
Instance details

Defined in Diagrams.Trail

Num n => DomainBounds (FixedSegment v n) # 
Instance details

Defined in Diagrams.Segment

Num n => DomainBounds (Trail v n) # 
Instance details

Defined in Diagrams.Trail

Methods

domainLower :: Trail v n -> N (Trail v n) #

domainUpper :: Trail v n -> N (Trail v n) #

Num n => DomainBounds (SegTree v n) # 
Instance details

Defined in Diagrams.Trail

Methods

domainLower :: SegTree v n -> N (SegTree v n) #

domainUpper :: SegTree v n -> N (SegTree v n) #

Num n => DomainBounds (Segment Closed v n) # 
Instance details

Defined in Diagrams.Segment

Num n => DomainBounds (Trail' l v n) # 
Instance details

Defined in Diagrams.Trail

Methods

domainLower :: Trail' l v n -> N (Trail' l v n) #

domainUpper :: Trail' l v n -> N (Trail' l v n) #

domainBounds :: DomainBounds p => p -> (N p, N p) #

Return the lower and upper bounds of a parametric domain together as a pair.

class (Parametric p, DomainBounds p) => EndValues p where #

Type class for querying the values of a parametric object at the ends of its domain.

Minimal complete definition

Nothing

Methods

atStart :: p -> Codomain p (N p) #

atStart is the value at the start of the domain. That is,

atStart x = x `atParam` domainLower x

This is the default implementation, but some representations will have a more efficient and/or precise implementation.

atEnd :: p -> Codomain p (N p) #

atEnd is the value at the end of the domain. That is,

atEnd x = x `atParam` domainUpper x

This is the default implementation, but some representations will have a more efficient and/or precise implementation.

Instances
Fractional n => EndValues (BernsteinPoly n) # 
Instance details

Defined in Diagrams.TwoD.Segment.Bernstein

(InSpace v n a, EndValues a, Codomain a ~ v) => EndValues (Located a) # 
Instance details

Defined in Diagrams.Located

Methods

atStart :: Located a -> Codomain (Located a) (N (Located a)) #

atEnd :: Located a -> Codomain (Located a) (N (Located a)) #

(DomainBounds t, EndValues (Tangent t)) => EndValues (Tangent (Located t)) # 
Instance details

Defined in Diagrams.Tangent

(Additive v, Num n) => EndValues (Tangent (FixedSegment v n)) # 
Instance details

Defined in Diagrams.Tangent

(Additive v, Num n) => EndValues (Tangent (Segment Closed v n)) # 
Instance details

Defined in Diagrams.Tangent

(Metric v, OrderedField n, Real n) => EndValues (Tangent (Trail v n)) # 
Instance details

Defined in Diagrams.Trail

Methods

atStart :: Tangent (Trail v n) -> Codomain (Tangent (Trail v n)) (N (Tangent (Trail v n))) #

atEnd :: Tangent (Trail v n) -> Codomain (Tangent (Trail v n)) (N (Tangent (Trail v n))) #

(Parametric (GetSegment (Trail' c v n)), EndValues (GetSegment (Trail' c v n)), Additive v, Num n) => EndValues (Tangent (Trail' c v n)) # 
Instance details

Defined in Diagrams.Trail

Methods

atStart :: Tangent (Trail' c v n) -> Codomain (Tangent (Trail' c v n)) (N (Tangent (Trail' c v n))) #

atEnd :: Tangent (Trail' c v n) -> Codomain (Tangent (Trail' c v n)) (N (Tangent (Trail' c v n))) #

(Metric v, OrderedField n, Real n) => EndValues (GetSegment (Trail v n)) # 
Instance details

Defined in Diagrams.Trail

Methods

atStart :: GetSegment (Trail v n) -> Codomain (GetSegment (Trail v n)) (N (GetSegment (Trail v n))) #

atEnd :: GetSegment (Trail v n) -> Codomain (GetSegment (Trail v n)) (N (GetSegment (Trail v n))) #

(Metric v, OrderedField n, Real n) => EndValues (GetSegment (Trail' Loop v n)) # 
Instance details

Defined in Diagrams.Trail

(Metric v, OrderedField n) => EndValues (GetSegment (Trail' Line v n)) # 
Instance details

Defined in Diagrams.Trail

(Additive v, Num n) => EndValues (FixedSegment v n) # 
Instance details

Defined in Diagrams.Segment

(Metric v, OrderedField n, Real n) => EndValues (Trail v n) # 
Instance details

Defined in Diagrams.Trail

Methods

atStart :: Trail v n -> Codomain (Trail v n) (N (Trail v n)) #

atEnd :: Trail v n -> Codomain (Trail v n) (N (Trail v n)) #

(Metric v, OrderedField n, Real n) => EndValues (SegTree v n) # 
Instance details

Defined in Diagrams.Trail

Methods

atStart :: SegTree v n -> Codomain (SegTree v n) (N (SegTree v n)) #

atEnd :: SegTree v n -> Codomain (SegTree v n) (N (SegTree v n)) #

(Additive v, Num n) => EndValues (Segment Closed v n) # 
Instance details

Defined in Diagrams.Segment

(Metric v, OrderedField n, Real n) => EndValues (Trail' l v n) # 
Instance details

Defined in Diagrams.Trail

Methods

atStart :: Trail' l v n -> Codomain (Trail' l v n) (N (Trail' l v n)) #

atEnd :: Trail' l v n -> Codomain (Trail' l v n) (N (Trail' l v n)) #

class DomainBounds p => Sectionable p where #

Type class for parametric objects which can be split into subobjects.

Minimal definition: Either splitAtParam or section, plus reverseDomain.

Minimal complete definition

reverseDomain

Methods

splitAtParam :: p -> N p -> (p, p) #

splitAtParam splits an object p into two new objects (l,r) at the parameter t, where l corresponds to the portion of p for parameter values from 0 to t and r for to that from t to 1. The following property should hold:

  prop_splitAtParam f t u =
    | u < t     = atParam f u == atParam l (u / t)
    | otherwise = atParam f u == atParam f t ??? atParam l ((u - t) / (domainUpper f - t))
    where (l,r) = splitAtParam f t

where (???) = (^+^) if the codomain is a vector type, or const flip if the codomain is a point type. Stated more intuitively, all this is to say that the parameterization scales linearly with splitting.

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

section :: p -> N p -> N p -> p #

Extract a particular section of the domain, linearly reparameterized to the same domain as the original. Should satisfy the property:

prop_section x l u t =
  let s = section x l u
  in     domainBounds x == domainBounds x
      && (x `atParam` lerp l u t) == (s `atParam` t)

That is, the section should have the same domain as the original, and the reparameterization should be linear.

section :: Fractional (N p) => p -> N p -> N p -> p #

Extract a particular section of the domain, linearly reparameterized to the same domain as the original. Should satisfy the property:

prop_section x l u t =
  let s = section x l u
  in     domainBounds x == domainBounds x
      && (x `atParam` lerp l u t) == (s `atParam` t)

That is, the section should have the same domain as the original, and the reparameterization should be linear.

reverseDomain :: p -> p #

Flip the parameterization on the domain.

Instances
Fractional n => Sectionable (BernsteinPoly n) # 
Instance details

Defined in Diagrams.TwoD.Segment.Bernstein

(InSpace v n a, Fractional n, Parametric a, Sectionable a, Codomain a ~ v) => Sectionable (Located a) # 
Instance details

Defined in Diagrams.Located

Methods

splitAtParam :: Located a -> N (Located a) -> (Located a, Located a) #

section :: Located a -> N (Located a) -> N (Located a) -> Located a #

reverseDomain :: Located a -> Located a #

(Additive v, Fractional n) => Sectionable (FixedSegment v n) # 
Instance details

Defined in Diagrams.Segment

(Metric v, OrderedField n, Real n) => Sectionable (Trail v n) #

Note that there is no Sectionable instance for Trail' Loop, because it does not make sense (splitting a loop at a parameter results in a single line, not two loops). However, it's convenient to have a Sectionable instance for Trail; if the Trail contains a loop the loop will first be cut and then splitAtParam called on the resulting line. This is semantically a bit silly, so please don't rely on it. (*E.g.* if this is really the behavior you want, consider first calling cutLoop yourself.)

Instance details

Defined in Diagrams.Trail

Methods

splitAtParam :: Trail v n -> N (Trail v n) -> (Trail v n, Trail v n) #

section :: Trail v n -> N (Trail v n) -> N (Trail v n) -> Trail v n #

reverseDomain :: Trail v n -> Trail v n #

(Metric v, OrderedField n, Real n) => Sectionable (SegTree v n) # 
Instance details

Defined in Diagrams.Trail

Methods

splitAtParam :: SegTree v n -> N (SegTree v n) -> (SegTree v n, SegTree v n) #

section :: SegTree v n -> N (SegTree v n) -> N (SegTree v n) -> SegTree v n #

reverseDomain :: SegTree v n -> SegTree v n #

(Additive v, Fractional n) => Sectionable (Segment Closed v n) # 
Instance details

Defined in Diagrams.Segment

(Metric v, OrderedField n, Real n) => Sectionable (Trail' Line v n) # 
Instance details

Defined in Diagrams.Trail

Methods

splitAtParam :: Trail' Line v n -> N (Trail' Line v n) -> (Trail' Line v n, Trail' Line v n) #

section :: Trail' Line v n -> N (Trail' Line v n) -> N (Trail' Line v n) -> Trail' Line v n #

reverseDomain :: Trail' Line v n -> Trail' Line v n #

class Parametric p => HasArcLength p where #

Type class for parametric things with a notion of arc length.

Minimal complete definition

arcLengthBounded, arcLengthToParam

Methods

arcLengthBounded :: N p -> p -> Interval (N p) #

arcLengthBounded eps x approximates the arc length of x. The true arc length is guaranteed to lie within the interval returned, which will have a size of at most eps.

arcLength :: N p -> p -> N p #

arcLength eps s approximates the arc length of x up to the accuracy eps (plus or minus).

arcLength :: Fractional (N p) => N p -> p -> N p #

arcLength eps s approximates the arc length of x up to the accuracy eps (plus or minus).

stdArcLength :: p -> N p #

Approximate the arc length up to a standard accuracy of stdTolerance (1e-6).

stdArcLength :: Fractional (N p) => p -> N p #

Approximate the arc length up to a standard accuracy of stdTolerance (1e-6).

arcLengthToParam :: N p -> p -> N p -> N p #

arcLengthToParam eps s l converts the absolute arc length l, measured from the start of the domain, to a parameter on the object s. The true arc length at the parameter returned is guaranteed to be within eps of the requested arc length.

This should work for any arc length, and may return any parameter value (not just parameters in the domain).

stdArcLengthToParam :: p -> N p -> N p #

A simple interface to convert arc length to a parameter, guaranteed to be accurate within stdTolerance, or 1e-6.

stdArcLengthToParam :: Fractional (N p) => p -> N p -> N p #

A simple interface to convert arc length to a parameter, guaranteed to be accurate within stdTolerance, or 1e-6.

Instances
(InSpace v n a, Fractional n, HasArcLength a, Codomain a ~ v) => HasArcLength (Located a) # 
Instance details

Defined in Diagrams.Located

Methods

arcLengthBounded :: N (Located a) -> Located a -> Interval (N (Located a)) #

arcLength :: N (Located a) -> Located a -> N (Located a) #

stdArcLength :: Located a -> N (Located a) #

arcLengthToParam :: N (Located a) -> Located a -> N (Located a) -> N (Located a) #

stdArcLengthToParam :: Located a -> N (Located a) -> N (Located a) #

(Metric v, OrderedField n) => HasArcLength (FixedSegment v n) # 
Instance details

Defined in Diagrams.Segment

(Metric v, OrderedField n, Real n) => HasArcLength (Trail v n) # 
Instance details

Defined in Diagrams.Trail

Methods

arcLengthBounded :: N (Trail v n) -> Trail v n -> Interval (N (Trail v n)) #

arcLength :: N (Trail v n) -> Trail v n -> N (Trail v n) #

stdArcLength :: Trail v n -> N (Trail v n) #

arcLengthToParam :: N (Trail v n) -> Trail v n -> N (Trail v n) -> N (Trail v n) #

stdArcLengthToParam :: Trail v n -> N (Trail v n) -> N (Trail v n) #

(Metric v, OrderedField n, Real n) => HasArcLength (SegTree v n) # 
Instance details

Defined in Diagrams.Trail

Methods

arcLengthBounded :: N (SegTree v n) -> SegTree v n -> Interval (N (SegTree v n)) #

arcLength :: N (SegTree v n) -> SegTree v n -> N (SegTree v n) #

stdArcLength :: SegTree v n -> N (SegTree v n) #

arcLengthToParam :: N (SegTree v n) -> SegTree v n -> N (SegTree v n) -> N (SegTree v n) #

stdArcLengthToParam :: SegTree v n -> N (SegTree v n) -> N (SegTree v n) #

(Metric v, OrderedField n) => HasArcLength (Segment Closed v n) # 
Instance details

Defined in Diagrams.Segment

(Metric v, OrderedField n, Real n) => HasArcLength (Trail' l v n) # 
Instance details

Defined in Diagrams.Trail

Methods

arcLengthBounded :: N (Trail' l v n) -> Trail' l v n -> Interval (N (Trail' l v n)) #

arcLength :: N (Trail' l v n) -> Trail' l v n -> N (Trail' l v n) #

stdArcLength :: Trail' l v n -> N (Trail' l v n) #

arcLengthToParam :: N (Trail' l v n) -> Trail' l v n -> N (Trail' l v n) -> N (Trail' l v n) #

stdArcLengthToParam :: Trail' l v n -> N (Trail' l v n) -> N (Trail' l v n) #