| Copyright | (c) 2011 diagrams-core team (see LICENSE) | 
|---|---|
| License | BSD-style (see LICENSE) | 
| Maintainer | diagrams-discuss@googlegroups.com | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Diagrams.Core.Transform
Contents
Description
Diagrams defines the core library of primitives forming the basis of an embedded domain-specific language for describing and rendering diagrams.
The Transform module defines generic transformations
 parameterized by any vector space.
- data u :-: v = (u :-* v) :-: (v :-* u)
- (<->) :: (HasLinearMap u, HasLinearMap v) => (u -> v) -> (v -> u) -> u :-: v
- linv :: (u :-: v) -> v :-: u
- lapp :: (VectorSpace v, Scalar u ~ Scalar v, HasLinearMap u) => (u :-: v) -> u -> v
- data Transformation v = Transformation (v :-: v) (v :-: v) v
- inv :: HasLinearMap v => Transformation v -> Transformation v
- transp :: Transformation v -> v :-: v
- transl :: Transformation v -> v
- apply :: HasLinearMap v => Transformation v -> v -> v
- papply :: HasLinearMap v => Transformation v -> Point v -> Point v
- fromLinear :: AdditiveGroup v => (v :-: v) -> (v :-: v) -> Transformation v
- basis :: forall v. HasLinearMap v => [v]
- onBasis :: forall v. HasLinearMap v => Transformation v -> ([v], v)
- matrixRep :: HasLinearMap v => Transformation v -> [[Scalar v]]
- determinant :: (HasLinearMap v, Num (Scalar v)) => Transformation v -> Scalar v
- class (HasBasis v, HasTrie (Basis v), VectorSpace v) => HasLinearMap v
- class HasLinearMap (V t) => Transformable t where- transform :: Transformation (V t) -> t -> t
 
- newtype TransInv t = TransInv t
- translation :: HasLinearMap v => v -> Transformation v
- translate :: (Transformable t, HasLinearMap (V t)) => V t -> t -> t
- scaling :: (HasLinearMap v, Fractional (Scalar v)) => Scalar v -> Transformation v
- scale :: (Transformable t, Fractional (Scalar (V t)), Eq (Scalar (V t))) => Scalar (V t) -> t -> t
Transformations
Invertible linear transformations
(v1 :-: v2) is a linear map paired with its inverse.
Instances
| HasLinearMap v => Monoid ((:-:) v v) | Invertible linear maps from a vector space to itself form a monoid under composition. | 
| HasLinearMap v => Semigroup ((:-:) v v) | 
(<->) :: (HasLinearMap u, HasLinearMap v) => (u -> v) -> (v -> u) -> u :-: v Source
Create an invertible linear map from two functions which are assumed to be linear inverses.
lapp :: (VectorSpace v, Scalar u ~ Scalar v, HasLinearMap u) => (u :-: v) -> u -> v Source
Apply a linear map to a vector.
General transformations
data Transformation v Source
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. 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-invertable transformations, see
   Diagrams.Deform (in diagrams-lib).
Constructors
| Transformation (v :-: v) (v :-: v) v | 
Instances
| HasLinearMap v => Monoid (Transformation v) | |
| HasLinearMap v => Semigroup (Transformation v) | Transformations are closed under composition;  | 
| HasLinearMap v => HasOrigin (Transformation v) | |
| HasLinearMap v => Transformable (Transformation v) | |
| (HasLinearMap v, (~) * v (V a), Transformable a) => Action (Transformation v) a | Transformations can act on transformable things. | 
| type V (Transformation v) = v | 
inv :: HasLinearMap v => Transformation v -> Transformation v Source
Invert a transformation.
transp :: Transformation v -> v :-: v Source
Get the transpose of a transformation (ignoring the translation component).
transl :: Transformation v -> v Source
Get the translational component of a transformation.
apply :: HasLinearMap v => Transformation v -> v -> v Source
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 :: HasLinearMap v => Transformation v -> Point v -> Point v Source
Apply a transformation to a point.
fromLinear :: AdditiveGroup v => (v :-: v) -> (v :-: v) -> Transformation v Source
Create a general affine transformation from an invertible linear transformation and its transpose. The translational component is assumed to be zero.
basis :: forall v. HasLinearMap v => [v] Source
Get the matrix equivalent of the basis of the vector space v as a list of columns.
onBasis :: forall v. HasLinearMap v => Transformation v -> ([v], v) Source
Get the matrix equivalent of the linear transform, (as a list of columns) and the translation vector. This is mostly useful for implementing backends.
matrixRep :: HasLinearMap v => Transformation v -> [[Scalar v]] Source
Convert a `Transformation v` to a matrix representation as a list of column vectors which are also lists.
determinant :: (HasLinearMap v, Num (Scalar v)) => Transformation v -> Scalar v Source
The determinant of a Transformation.
The Transformable class
class (HasBasis v, HasTrie (Basis v), VectorSpace v) => HasLinearMap v Source
HasLinearMap is a poor man's class constraint synonym, just to
   help shorten some of the ridiculously long constraint sets.
Instances
| (HasBasis v, HasTrie (Basis v), VectorSpace v) => HasLinearMap v | 
class HasLinearMap (V t) => Transformable t where Source
Type class for things t which can be transformed.
Instances
Translational invariance
TransInv is a wrapper which makes a transformable type
   translationally invariant; the translational component of
   transformations will no longer affect things wrapped in
   TransInv.
Constructors
| TransInv t | 
Instances
| Eq t => Eq (TransInv t) | |
| Ord t => Ord (TransInv t) | |
| Show t => Show (TransInv t) | |
| Monoid t => Monoid (TransInv t) | |
| Semigroup t => Semigroup (TransInv t) | |
| Wrapped (TransInv t) | |
| VectorSpace (V t) => HasOrigin (TransInv t) | |
| Transformable t => Transformable (TransInv t) | |
| Qualifiable a => Qualifiable (TransInv a) | |
| Traced t => Traced (TransInv t) | |
| Enveloped t => Enveloped (TransInv t) | |
| Rewrapped (TransInv t) (TransInv t') | |
| type Unwrapped (TransInv t) = t | |
| type V (TransInv t) = V t | 
Vector space independent transformations
Most transformations are specific to a particular vector space, but a few can be defined generically over any vector space.
translation :: HasLinearMap v => v -> Transformation v Source
Create a translation.
translate :: (Transformable t, HasLinearMap (V t)) => V t -> t -> t Source
Translate by a vector.
scaling :: (HasLinearMap v, Fractional (Scalar v)) => Scalar v -> Transformation v Source
Create a uniform scaling transformation.