Copyright | (c) 2011-15 diagrams-lib team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | diagrams-discuss@googlegroups.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Affine transformations, parameterized by any vector space. For transformations on particular vector spaces, see e.g. Diagrams.TwoD.Transform.
Synopsis
- data Transformation (v :: Type -> Type) n
- inv :: forall (v :: Type -> Type) n. (Functor v, Num n) => Transformation v n -> Transformation v n
- transl :: Transformation v n -> v n
- apply :: Transformation v n -> v n -> v n
- papply :: forall (v :: Type -> Type) n. (Additive v, Num n) => Transformation v n -> Point v n -> Point v n
- class Transformable t where
- transform :: Transformation (V t) (N t) -> t -> t
- translation :: v n -> Transformation v n
- translate :: Transformable t => Vn t -> t -> t
- moveTo :: forall (v :: Type -> Type) n t. (InSpace v n t, HasOrigin t) => Point v n -> t -> t
- place :: forall (v :: Type -> Type) n t. (InSpace v n t, HasOrigin t) => t -> Point v n -> t
- scaling :: forall (v :: Type -> Type) n. (Additive v, Fractional n) => n -> Transformation v n
- scale :: forall (v :: Type -> Type) n a. (InSpace v n a, Eq n, Fractional n, Transformable a) => n -> a -> a
- conjugate :: (Additive v, Num n) => Transformation v n -> Transformation v n -> Transformation v n
- underT :: (InSpace v n a, SameSpace a b, Transformable a, Transformable b) => (a -> b) -> Transformation v n -> a -> b
- transformed :: (InSpace v n a, SameSpace a b, Transformable a, Transformable b) => Transformation v n -> Iso a b a b
- translated :: (InSpace v n a, SameSpace a b, Transformable a, Transformable b) => v n -> Iso a b a b
- movedTo :: (InSpace v n a, SameSpace a b, HasOrigin a, HasOrigin b) => Point v n -> Iso a b a b
- movedFrom :: (InSpace v n a, SameSpace a b, HasOrigin a, HasOrigin b) => Point v n -> Iso a b a b
- class HasOrigin t where
- moveOriginTo :: Point (V t) (N t) -> t -> t
- moveOriginBy :: (V t ~ v, N t ~ n, HasOrigin t) => v n -> t -> t
Transformations
data Transformation (v :: Type -> Type) 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
inv :: forall (v :: Type -> Type) n. (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 :: forall (v :: Type -> Type) n. (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.
transform :: Transformation (V t) (N t) -> t -> t #
Apply a transformation to an object.
Instances
Some specific transformations
translation :: v n -> Transformation v n #
Create a translation.
translate :: Transformable t => Vn t -> t -> t #
Translate by a vector.
moveTo :: forall (v :: Type -> Type) n t. (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 :: forall (v :: Type -> Type) n t. (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 :: forall (v :: Type -> Type) n. (Additive v, Fractional n) => n -> Transformation v n #
Create a uniform scaling transformation.
scale :: forall (v :: Type -> Type) n a. (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 Source #
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 Source #
Carry out some transformation "under" another one: f
first applies `underT`
tt
, then f
, then the inverse of t
. For
example,
is the transformation which scales by a factor of 2 along the
diagonal line y = x.scaleX
2 `underT`
rotation
(-1/8 @@ Turn)
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 Source #
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 Source #
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 Source #
movedFrom :: (InSpace v n a, SameSpace a b, HasOrigin a, HasOrigin b) => Point v n -> Iso a b a b Source #
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 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, Trail
s) are
transformable but are translationally invariant, i.e. have no
origin.
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
moveOriginBy :: (V t ~ v, N t ~ n, HasOrigin t) => v n -> t -> t #
Move the local origin by a relative vector.