Copyright | (c) 2013 diagrams-lib team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | diagrams-discuss@googlegroups.com |
Safe Haskell | Safe |
Language | Haskell2010 |
Type classes for things which are parameterized in some way, e.g. segments and trails.
- stdTolerance :: Fractional a => a
- type family Codomain p :: * -> *
- class Parametric p where
- class DomainBounds p where
- domainBounds :: DomainBounds p => p -> (N p, N p)
- class (Parametric p, DomainBounds p) => EndValues p where
- class DomainBounds p => Sectionable p where
- class Parametric p => HasArcLength p where
Documentation
stdTolerance :: Fractional a => a Source #
The standard tolerance used by std...
functions (like
stdArcLength
and stdArcLengthToParam
, currently set at
1e-6
.
type family Codomain p :: * -> * Source #
Codomain of parametric classes. This is usually either (V p)
, for relative
vector results, or (Point (V p))
, for functions with absolute coordinates.
type Codomain (BernsteinPoly n) Source # | |
type Codomain (Located a) Source # | |
type Codomain (Tangent t) Source # | |
type Codomain (GetSegment t) Source # | |
type Codomain (FixedSegment v n) Source # | |
type Codomain (Trail v n) Source # | |
type Codomain (SegTree v n) Source # | |
type Codomain (Segment Closed v n) Source # | |
type Codomain (Trail' l v n) Source # | |
class Parametric p where Source #
Type class for parametric functions.
Fractional n => Parametric (BernsteinPoly n) Source # | |
(InSpace v n a, Parametric a, (~) (* -> *) (Codomain a) v) => Parametric (Located a) Source # | |
Parametric (Tangent t) => Parametric (Tangent (Located t)) Source # | |
(Additive v, Num n) => Parametric (Tangent (FixedSegment v n)) Source # | |
(Additive v, Num n) => Parametric (Tangent (Segment Closed v n)) Source # | |
(Metric v, OrderedField n, Real n) => Parametric (Tangent (Trail v n)) Source # | |
(Parametric (GetSegment (Trail' c v n)), Additive v, Num n) => Parametric (Tangent (Trail' c v n)) Source # | |
(Metric v, OrderedField n, Real n) => Parametric (GetSegment (Trail v n)) Source # | |
(Metric v, OrderedField n, Real n) => Parametric (GetSegment (Trail' Loop v n)) Source # | The parameterization for loops wraps around, i.e. parameters are first reduced "mod 1". |
(Metric v, OrderedField n) => Parametric (GetSegment (Trail' Line v n)) Source # | 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). |
(Additive v, Num n) => Parametric (FixedSegment v n) Source # | |
(Metric v, OrderedField n, Real n) => Parametric (Trail v n) Source # | |
(Metric v, OrderedField n, Real n) => Parametric (SegTree v n) Source # | |
(Additive v, Num n) => Parametric (Segment Closed v n) Source # |
|
(Metric v, OrderedField n, Real n) => Parametric (Trail' l v n) Source # | |
class DomainBounds p where Source #
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.
domainLower :: p -> N p Source #
domainLower
defaults to being constantly 0 (for vector spaces with
numeric scalars).
domainLower :: Num (N p) => p -> N p Source #
domainLower
defaults to being constantly 0 (for vector spaces with
numeric scalars).
domainUpper :: p -> N p Source #
domainUpper
defaults to being constantly 1 (for vector spaces
with numeric scalars).
domainUpper :: Num n => p -> n Source #
domainUpper
defaults to being constantly 1 (for vector spaces
with numeric scalars).
Num n => DomainBounds (BernsteinPoly n) Source # | |
DomainBounds a => DomainBounds (Located a) Source # | |
DomainBounds t => DomainBounds (Tangent t) Source # | |
DomainBounds t => DomainBounds (GetSegment t) Source # | |
Num n => DomainBounds (FixedSegment v n) Source # | |
Num n => DomainBounds (Trail v n) Source # | |
Num n => DomainBounds (SegTree v n) Source # | |
Num n => DomainBounds (Segment Closed v n) Source # | |
Num n => DomainBounds (Trail' l v n) Source # | |
domainBounds :: DomainBounds p => p -> (N p, N p) Source #
Return the lower and upper bounds of a parametric domain together as a pair.
class (Parametric p, DomainBounds p) => EndValues p where Source #
Type class for querying the values of a parametric object at the ends of its domain.
atStart :: p -> Codomain p (N p) Source #
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) Source #
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.
class DomainBounds p => Sectionable p where Source #
Type class for parametric objects which can be split into subobjects.
Minimal definition: Either splitAtParam
or section
,
plus reverseDomain
.
splitAtParam :: p -> N p -> (p, p) Source #
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 Source #
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 Source #
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 Source #
Flip the parameterization on the domain.
Fractional n => Sectionable (BernsteinPoly n) Source # | |
(InSpace v n a, Fractional n, Parametric a, Sectionable a, (~) (* -> *) (Codomain a) v) => Sectionable (Located a) Source # | |
(Additive v, Fractional n) => Sectionable (FixedSegment v n) Source # | |
(Metric v, OrderedField n, Real n) => Sectionable (Trail v n) Source # | Note that there is no |
(Metric v, OrderedField n, Real n) => Sectionable (SegTree v n) Source # | |
(Additive v, Fractional n) => Sectionable (Segment Closed v n) Source # | |
(Metric v, OrderedField n, Real n) => Sectionable (Trail' Line v n) Source # | |
class Parametric p => HasArcLength p where Source #
Type class for parametric things with a notion of arc length.
arcLengthBounded :: N p -> p -> Interval (N p) Source #
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 Source #
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 Source #
arcLength eps s
approximates the arc length of x
up to the
accuracy eps
(plus or minus).
stdArcLength :: p -> N p Source #
Approximate the arc length up to a standard accuracy of
stdTolerance
(1e-6
).
stdArcLength :: Fractional (N p) => p -> N p Source #
Approximate the arc length up to a standard accuracy of
stdTolerance
(1e-6
).
arcLengthToParam :: N p -> p -> N p -> N p Source #
converts the absolute arc length
arcLengthToParam
eps s ll
, 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 Source #
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 Source #
A simple interface to convert arc length to a parameter,
guaranteed to be accurate within stdTolerance
, or 1e-6
.
(InSpace v n a, Fractional n, HasArcLength a, (~) (* -> *) (Codomain a) v) => HasArcLength (Located a) Source # | |
(Metric v, OrderedField n) => HasArcLength (FixedSegment v n) Source # | |
(Metric v, OrderedField n, Real n) => HasArcLength (Trail v n) Source # | |
(Metric v, OrderedField n, Real n) => HasArcLength (SegTree v n) Source # | |
(Metric v, OrderedField n) => HasArcLength (Segment Closed v n) Source # | |
(Metric v, OrderedField n, Real n) => HasArcLength (Trail' l v n) Source # | |