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

Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone

Diagrams.Located

Description

"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.

Synopsis

Documentation

data Located a Source

"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.

Instances

(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 Located a is the envelope of the a, translated to the location.

Traced a => Traced (Located a)

The trace of a Located a is the trace of the a, translated to the location.

Qualifiable a => Qualifiable (Located a) 
Transformable a => Transformable (Located a)

Applying a transformation t to a Located a results in the transformation being applied to the location, and the linear portion of t being applied to the value of type a (i.e. it is not translated).

VectorSpace (V a) => HasOrigin (Located a)

Located a is an instance of HasOrigin whether a is or not. In particular, translating a Located a simply translates the associated point (and does not affect the value of type 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)

Located things are trail-like as long as the underlying type is. The location is taken to be the location of the input located trail.

(VectorSpace v, InnerSpace v, ~ * s (Scalar v), Ord s, Fractional s, Floating s, Show s, Show v) => Deformable (Located (Trail v)) 

at :: a -> Point (V a) -> Located aSource

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 -> aSource

Project the value of type a out of a Located a, discarding the location.

loc :: Located a -> Point (V a)Source

Project out the location of a Located value.

mapLoc :: V a ~ V b => (a -> b) -> Located a -> Located bSource

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.)

located :: V a ~ V a' => Lens (Located a) (Located a') a a'Source

A lens giving access to the object within a Located wrapper.