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

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

Diagrams.Transform

Contents

Description

Affine transformations, parameterized by any vector space. For transformations on particular vector spaces, see e.g. Diagrams.TwoD.Transform.

Synopsis

Transformations

data Transformation v n :: (* -> *) -> * -> *

General (affine) transformations, represented by an invertible linear map, its transpose, and a vector representing a translation component.

By the transpose of a linear map we mean simply the linear map corresponding to the transpose of the map's matrix representation. For example, any scale is its own transpose, since scales are represented by matrices with zeros everywhere except the diagonal. The transpose of a rotation is the same as its inverse.

The reason we need to keep track of transposes is because it turns out that when transforming a shape according to some linear map L, the shape's normal vectors transform according to L's inverse transpose. (For a more detailed explanation and proof, see https://wiki.haskell.org/Diagrams/Dev/Transformations.) This is exactly what we need when transforming bounding functions, which are defined in terms of perpendicular (i.e. normal) hyperplanes.

For more general, non-invertible transformations, see Diagrams.Deform (in diagrams-lib).

Instances

(Additive v, Num n) => Semigroup (Transformation v n)

Transformations are closed under composition; t1 <> t2 is the transformation which performs first t2, then t1.

(Additive v, Num n) => Monoid (Transformation v n) 
(Additive v, Num n) => Transformable (Transformation v n) 
(Additive v, Num n) => HasOrigin (Transformation v n) 
(Transformable a, (~) (* -> *) (V a) v, (~) * (N a) n) => Action (Transformation v n) a

Transformations can act on transformable things.

type V (Transformation v n) = v 
type N (Transformation v n) = n 

inv :: (Functor v, Num n) => Transformation v n -> Transformation v n

Invert a transformation.

transl :: Transformation v n -> v n

Get the translational component of a transformation.

apply :: Transformation v n -> v n -> v n

Apply a transformation to a vector. Note that any translational component of the transformation will not affect the vector, since vectors are invariant under translation.

papply :: (Additive v, Num n) => Transformation v n -> Point v n -> Point v n

Apply a transformation to a point.

The Transformable class

class Transformable t where

Type class for things t which can be transformed.

Methods

transform :: Transformation (V t) (N t) -> t -> t

Apply a transformation to an object.

Instances

Transformable t => Transformable [t] 
(Transformable t, Ord t) => Transformable (Set t) 
(Num (N t), Additive (V t), Transformable t) => Transformable (TransInv t) 
Transformable m => Transformable (Deletable m) 
Transformable (ParallelLight n) 
Fractional n => Transformable (PointLight n) 
Fractional n => Transformable (Frustum n) 
Fractional n => Transformable (Box n) 
Fractional n => Transformable (Ellipsoid n) 
((~) (* -> *) (V t) V2, (~) * (N t) n, RealFloat n, Transformable t) => Transformable (ScaleInv t) 
(Additive (V a), Num (N 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).

OrderedField n => Transformable (Clip n) 
Fractional n => Transformable (LGradient n) 
Fractional n => Transformable (RGradient n) 
Floating n => Transformable (Texture n) 
Floating n => Transformable (FillTexture n) 
Floating n => Transformable (LineTexture n) 
Floating n => Transformable (Text n) 
((~) (* -> *) (V t) v, (~) * (N t) n, (~) (* -> *) (V t) (V s), (~) * (N t) (N s), Functor v, Num n, Transformable t, Transformable s) => Transformable (s -> t) 
(Transformable t, Transformable s, (~) (* -> *) (V t) (V s), (~) * (N t) (N s)) => Transformable (t, s) 
Transformable t => Transformable (Map k t) 
(Metric v, Floating n) => Transformable (Envelope v n) 
(Additive v, Num n) => Transformable (Trace v n) 
(Additive v, Traversable v, Floating n) => Transformable (Attribute v n)

TAttributes are transformed directly, MAttributes have their local scale multiplied by the average scale of the transform. Plain Attributes are unaffected.

(Additive v, Traversable v, Floating n) => Transformable (Style v n) 
(Additive v, Num n) => Transformable (Transformation v n) 
(Additive v, Num n) => Transformable (Point v n) 
((~) (* -> *) (V (v n)) v, (~) * (N (v n)) n, Transformable (v n)) => Transformable (Direction v n) 
Num n => Transformable (Camera l n) 
(Additive v, Num n) => Transformable (FixedSegment v n) 
(HasLinearMap v, Metric v, OrderedField n) => Transformable (Trail v n) 
(Floating n, Ord n, Metric v) => Transformable (SegTree v n) 
(HasLinearMap v, Metric v, OrderedField n) => Transformable (Path v n) 
Fractional n => Transformable (DImage n a) 
(Transformable t, Transformable s, Transformable u, (~) (* -> *) (V s) (V t), (~) * (N s) (N t), (~) (* -> *) (V s) (V u), (~) * (N s) (N u)) => Transformable (t, s, u) 
Transformable (Prim b v n)

The Transformable instance for Prim just pushes calls to transform down through the Prim constructor.

(Additive v, Num n) => Transformable (Query v n m) 
Transformable (Segment c v n) 
Transformable (Offset c v n) 
(HasLinearMap v, Metric v, OrderedField n) => Transformable (Trail' l v n) 
(OrderedField n, Metric v, Semigroup m) => Transformable (QDiagram b v n m)

Diagrams can be transformed by transforming each of their components appropriately.

Transformable (Subdiagram b v n m) 
Transformable (SubMap b v n m) 

Some specific transformations

translation :: v n -> Transformation v n

Create a translation.

translate :: Transformable t => Vn t -> t -> t

Translate by a vector.

moveTo :: (InSpace v n t, HasOrigin t) => Point v n -> t -> t

Translate the object by the translation that sends the origin to the given point. Note that this is dual to moveOriginTo, i.e. we should have

  moveTo (origin .^+ v) === moveOriginTo (origin .^- v)
  

For types which are also Transformable, this is essentially the same as translate, i.e.

  moveTo (origin .^+ v) === translate v
  

place :: (InSpace v n t, HasOrigin t) => t -> Point v n -> t

A flipped variant of moveTo, provided for convenience. Useful when writing a function which takes a point as an argument, such as when using withName and friends.

scaling :: (Additive v, Fractional n) => n -> Transformation v n

Create a uniform scaling transformation.

scale :: (InSpace v n a, Eq n, Fractional n, Transformable a) => n -> a -> a

Scale uniformly in every dimension by the given scalar.

Miscellaneous transformation-related utilities

conjugate :: (Additive v, Num n) => Transformation v n -> Transformation v n -> Transformation v n

Conjugate one transformation by another. conjugate t1 t2 is the transformation which performs first t1, then t2, then the inverse of t1.

underT :: (InSpace v n a, SameSpace a b, Transformable a, Transformable b) => (a -> b) -> Transformation v n -> a -> b

Carry out some transformation "under" another one: f `underT` t first applies t, then f, then the inverse of t. For example, scaleX 2 `underT` rotation (-1/8 @@ Turn) is the transformation which scales by a factor of 2 along the diagonal line y = x.

Note that

(transform t2) underT t1 == transform (conjugate t1 t2)

for all transformations t1 and t2.

See also the isomorphisms like transformed, movedTo, movedFrom, and translated.

transformed :: (InSpace v n a, SameSpace a b, Transformable a, Transformable b) => Transformation v n -> Iso a b a b

Use a Transformation to make an Iso between an object transformed and untransformed. This is useful for carrying out functions under another transform:

under (transformed t) f               == transform (inv t) . f . transform t
under (transformed t1) (transform t2) == transform (conjugate t1 t2)
transformed t ## a                    == transform t a
a ^. transformed t                    == transform (inv t) a

translated :: (InSpace v n a, SameSpace a b, Transformable a, Transformable b) => v n -> Iso a b a b

Use a vector to make an Iso between an object translated and untranslated.

under (translated v) f == translate (-v) . f . translate v
translated v ## a      == translate v a
a ^. translated v      == translate (-v) a
over (translated v) f  == translate v . f . translate (-v)

movedTo :: (InSpace v n a, SameSpace a b, HasOrigin a, HasOrigin b) => Point v n -> Iso a b a b

Use a Point to make an Iso between an object moved to and from that point:

under (movedTo p) f == moveTo (-p) . f . moveTo p
over (movedTo p) f  == moveTo p . f . moveTo (-p)
movedTo p           == from (movedFrom p)
movedTo p ## a      == moveTo p a
a ^. movedTo p      == moveOriginTo p a

movedFrom :: (InSpace v n a, SameSpace a b, HasOrigin a, HasOrigin b) => Point v n -> Iso a b a b

Use a Transformation to make an Iso between an object transformed and untransformed. We have

under (movedFrom p) f == moveTo p . f . moveTo (-p)
movedFrom p           == from (movedTo p)
movedFrom p ## a      == moveOriginTo p a
a ^. movedFrom p      == moveTo p a
over (movedFrom p) f  == moveTo (-p) . f . moveTo p

The HasOrigin class

class HasOrigin t where

Class of types which have an intrinsic notion of a "local origin", i.e. things which are not invariant under translation, and which allow the origin to be moved.

One might wonder why not just use Transformable instead of having a separate class for HasOrigin; indeed, for types which are instances of both we should have the identity

  moveOriginTo (origin .^+ v) === translate (negated v)
  

The reason is that some things (e.g. vectors, Trails) are transformable but are translationally invariant, i.e. have no origin.

Methods

moveOriginTo :: Point (V t) (N t) -> t -> t

Move the local origin to another point.

Note that this function is in some sense dual to translate (for types which are also Transformable); moving the origin itself while leaving the object "fixed" is dual to fixing the origin and translating the diagram.

Instances

HasOrigin t => HasOrigin [t] 
(HasOrigin t, Ord t) => HasOrigin (Set t) 
HasOrigin (TransInv t) 
((~) (* -> *) (V t) v, (~) * (N t) n, Additive v, Num n, HasOrigin t) => HasOrigin (ScaleInv t) 
(Num (N a), Additive (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).

Floating n => HasOrigin (Text n) 
(HasOrigin t, HasOrigin s, SameSpace s t) => HasOrigin (s, t) 
HasOrigin t => HasOrigin (Map k t) 
(Metric v, Fractional n) => HasOrigin (Envelope v n)

The local origin of an envelope is the point with respect to which bounding queries are made, i.e. the point from which the input vectors are taken to originate.

(Additive v, Num n) => HasOrigin (Trace v n) 
(Additive v, Num n) => HasOrigin (Transformation v n) 
HasOrigin t => HasOrigin (Measured n t) 
(Additive v, Num n) => HasOrigin (Point v n) 
(Additive v, Num n) => HasOrigin (FixedSegment v n) 
(Additive v, Num n) => HasOrigin (Path v n) 
(Additive v, Num n) => HasOrigin (BoundingBox v n) 
Fractional n => HasOrigin (DImage n a) 
(Additive v, Num n) => HasOrigin (Query v n m) 
(Metric v, OrderedField n, Semigroup m) => HasOrigin (QDiagram b v n m)

Every diagram has an intrinsic "local origin" which is the basis for all combining operations.

(Metric v, OrderedField n) => HasOrigin (Subdiagram b v n m) 
(OrderedField n, Metric v) => HasOrigin (SubMap b v n m) 

moveOriginBy :: ((~) (* -> *) (V t) v, (~) * (N t) n, HasOrigin t) => v n -> t -> t

Move the local origin by a relative vector.