Copyright | (c) 2013 diagrams-lib team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | diagrams-discuss@googlegroups.com |
Safe Haskell | None |
Language | Haskell2010 |
"Located" things, i.e. things with a concrete location:
intuitively, Located a ~ (a, Point)
. Wrapping a translationally
invariant thing (e.g. a Segment
or Trail
) in Located
pins
it down to a particular location and makes it no longer
translationally invariant.
Documentation
"Located" things, i.e. things with a concrete location:
intuitively, Located a ~ (Point, a)
. Wrapping a translationally
invariant thing (e.g. a Segment
or Trail
) in Located
pins
it down to a particular location and makes it no longer
translationally invariant.
Located
is intentionally abstract. To construct Located
values, use at
. To destruct, use viewLoc
, unLoc
, or loc
.
To map, use mapLoc
.
Much of the utility of having a concrete type for the Located
concept lies in the type class instances we can give it. The
HasOrigin
, Transformable
, Enveloped
, Traced
, and
TrailLike
instances are particularly useful; see the documented
instances below for more information.
(Eq (V a), Eq a) => Eq (Located a) | |
(Ord (V a), Ord a) => Ord (Located a) | |
(Show (V a), Show a) => Show (Located a) | |
Enveloped a => Juxtaposable (Located a) | |
Enveloped a => Enveloped (Located a) | The envelope of a |
Traced a => Traced (Located a) | The trace of a |
Qualifiable a => Qualifiable (Located a) | |
Transformable a => Transformable (Located a) | Applying a transformation |
VectorSpace (V a) => HasOrigin (Located a) |
|
((~) * (Codomain a) (V a), AdditiveGroup (V a), Fractional (Scalar (V a)), HasArcLength a) => HasArcLength (Located a) | |
((~) * (Codomain a) (V a), Fractional (Scalar (V a)), AdditiveGroup (V a), Sectionable a, Parametric a) => Sectionable (Located a) | |
((~) * (Codomain a) (V a), AdditiveGroup (V a), EndValues a) => EndValues (Located a) | |
(DomainBounds t, EndValues (Tangent t)) => EndValues (Tangent (Located t)) | |
DomainBounds a => DomainBounds (Located a) | |
((~) * (Codomain a) (V a), AdditiveGroup (V a), Parametric a) => Parametric (Located a) | |
Parametric (Tangent t) => Parametric (Tangent (Located t)) | |
TrailLike t => TrailLike (Located t) |
|
(VectorSpace v, InnerSpace v, (~) * s (Scalar v), Ord s, Fractional s, Floating s, Show s, Show v) => Deformable (Located (Trail v)) | |
type V (Located a) = V a | |
type Codomain (Located a) = Point (Codomain a) | |
type Codomain (Tangent (Located t)) = Codomain (Tangent t) |
at :: a -> Point (V a) -> Located a infix 5 Source
Construct a Located a
from a value of type a
and a location.
at
is intended to be used infix, like x `at` origin
.
viewLoc :: Located a -> (Point (V a), a) Source
Deconstruct a Located a
into a location and a value of type
a
. viewLoc
can be especially useful in conjunction with the
ViewPatterns
extension.
unLoc :: Located a -> a Source
Project the value
of type a
out of
a Located a
,
discarding the
location.
mapLoc :: (V a ~ V b) => (a -> b) -> Located a -> Located b Source
Located
is not a Functor
, since changing the type could
change the type of the associated vector space, in which case the
associated location would no longer have the right type. mapLoc
has an extra constraint specifying that the vector space must
stay the same.
(Technically, one can say that for every vector space v
,
Located
is a little-f (endo)functor on the category of types
with associated vector space v
; but that is not covered by the
standard Functor
class.)