Copyright | (c) 2011-2015 diagrams-core team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | diagrams-discuss@googlegroups.com |
Safe Haskell | None |
Language | Haskell2010 |
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)
- (<->) :: (u -> v) -> (v -> u) -> u :-: v
- linv :: (u :-: v) -> v :-: u
- lapp :: (u :-: v) -> u -> v
- data Transformation v n = Transformation (v n :-: v n) (v n :-: v n) (v n)
- inv :: (Functor v, Num n) => Transformation v n -> Transformation v n
- transp :: Transformation v n -> v n :-: v n
- transl :: Transformation v n -> v n
- dropTransl :: (Additive v, Num n) => Transformation v n -> Transformation v n
- apply :: Transformation v n -> v n -> v n
- papply :: (Additive v, Num n) => Transformation v n -> Point v n -> Point v n
- fromLinear :: (Additive v, Num n) => (v n :-: v n) -> (v n :-: v n) -> Transformation v n
- fromOrthogonal :: (Additive v, Num n) => (v n :-: v n) -> Transformation v n
- fromSymmetric :: (Additive v, Num n) => (v n :-: v n) -> Transformation v n
- basis :: (Additive t, Traversable t, Num a) => [t a]
- dimension :: forall a v. (V a ~ v, Additive v, Traversable v) => a -> Int
- onBasis :: (Additive v, Traversable v, Num n) => Transformation v n -> ([v n], v n)
- listRep :: Foldable v => v n -> [n]
- matrixRep :: (Additive v, Traversable v, Num n) => Transformation v n -> [[n]]
- matrixHomRep :: (Additive v, Traversable v, Num n) => Transformation v n -> [[n]]
- determinant :: (Additive v, Traversable v, Num n) => Transformation v n -> n
- isReflection :: (Additive v, Traversable v, Num n, Ord n) => Transformation v n -> Bool
- avgScale :: (Additive v, Traversable v, Floating n) => Transformation v n -> n
- eye :: (HasBasis v, Num n) => v (v n)
- class (HasBasis v, Traversable v) => HasLinearMap v
- class (Additive v, Representable v, Rep v ~ E v) => HasBasis v
- class Transformable t where
- transform :: Transformation (V t) (N t) -> t -> t
- newtype TransInv t = TransInv t
- translation :: v n -> Transformation v n
- translate :: (Num (N t), Transformable t) => Vn t -> t -> t
- scaling :: (Additive v, Fractional n) => n -> Transformation v n
- scale :: (InSpace v n a, Eq n, Fractional n, Transformable a) => n -> a -> a
Transformations
Invertible linear transformations
(v1 :-: v2)
is a linear map paired with its inverse.
(u -> v) :-: (v -> u) infixr 7 |
(<->) :: (u -> v) -> (v -> u) -> u :-: v Source
Create an invertible linear map from two functions which are assumed to be linear inverses.
General transformations
data Transformation v n 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. (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
).
Transformation (v n :-: v n) (v n :-: v n) (v n) |
(Additive v, Num n) => Monoid (Transformation v n) Source | |
(Additive v, Num n) => Semigroup (Transformation v n) Source | Transformations are closed under composition; |
(Additive v, Num n) => HasOrigin (Transformation v n) Source | |
(Additive v, Num n) => Transformable (Transformation v n) Source | |
(Transformable a, (~) (* -> *) (V a) v, (~) * (N a) n) => Action (Transformation v n) a Source | Transformations can act on transformable things. |
type N (Transformation v n) = n Source | |
type V (Transformation v n) = v Source |
inv :: (Functor v, Num n) => Transformation v n -> Transformation v n Source
Invert a transformation.
transp :: Transformation v n -> v n :-: v n Source
Get the transpose of a transformation (ignoring the translation component).
transl :: Transformation v n -> v n Source
Get the translational component of a transformation.
dropTransl :: (Additive v, Num n) => Transformation v n -> Transformation v n Source
Drop the translational component of a transformation, leaving only the linear part.
apply :: Transformation v n -> v n -> v n 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 :: (Additive v, Num n) => Transformation v n -> Point v n -> Point v n Source
Apply a transformation to a point.
fromLinear :: (Additive v, Num n) => (v n :-: v n) -> (v n :-: v n) -> Transformation v n Source
Create a general affine transformation from an invertible linear transformation and its transpose. The translational component is assumed to be zero.
fromOrthogonal :: (Additive v, Num n) => (v n :-: v n) -> Transformation v n Source
An orthogonal linear map is one whose inverse is also its transpose.
fromSymmetric :: (Additive v, Num n) => (v n :-: v n) -> Transformation v n Source
A symmetric linear map is one whose transpose is equal to its self.
basis :: (Additive t, Traversable t, Num a) => [t a]
Produce a default basis for a vector space. If the dimensionality
of the vector space is not statically known, see basisFor
.
dimension :: forall a v. (V a ~ v, Additive v, Traversable v) => a -> Int Source
Get the dimension of an object whose vector space is an instance of
HasLinearMap
, e.g. transformations, paths, diagrams, etc.
onBasis :: (Additive v, Traversable v, Num n) => Transformation v n -> ([v n], v n) 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 :: (Additive v, Traversable v, Num n) => Transformation v n -> [[n]] Source
Convert the linear part of a Transformation
to a matrix
representation as a list of column vectors which are also lists.
matrixHomRep :: (Additive v, Traversable v, Num n) => Transformation v n -> [[n]] Source
Convert a `Transformation v` to a homogeneous matrix representation. The final list is the translation. The representation leaves off the last row of the matrix as it is always [0,0, ... 1] and this representation is the defacto standard for backends.
determinant :: (Additive v, Traversable v, Num n) => Transformation v n -> n Source
The determinant of (the linear part of) a Transformation
.
isReflection :: (Additive v, Traversable v, Num n, Ord n) => Transformation v n -> Bool Source
Determine whether a Transformation
includes a reflection
component, that is, whether it reverses orientation.
avgScale :: (Additive v, Traversable v, Floating n) => Transformation v n -> n Source
Compute the "average" amount of scaling performed by a transformation. Satisfies the properties
avgScale (scaling k) == k avgScale (t1 <> t2) == avgScale t1 * avgScale t2
The Transformable class
class (HasBasis v, Traversable v) => HasLinearMap v Source
HasLinearMap
is a poor man's class constraint synonym, just to
help shorten some of the ridiculously long constraint sets.
(HasBasis v, Traversable v) => HasLinearMap v Source |
class (Additive v, Representable v, Rep v ~ E v) => HasBasis v Source
An Additive
vector space whose representation is made up of basis elements.
class Transformable t where Source
Type class for things t
which can be transformed.
transform :: Transformation (V t) (N t) -> t -> t Source
Apply a transformation to an object.
Transformable t => Transformable [t] Source | |
(Transformable t, Ord t) => Transformable (Set t) Source | |
Transformable m => Transformable (Deletable m) Source | |
(Num (N t), Additive (V t), Transformable t) => Transformable (TransInv t) Source | |
((~) (* -> *) (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) Source | |
(Transformable t, Transformable s, (~) (* -> *) (V t) (V s), (~) * (N t) (N s)) => Transformable (t, s) Source | |
Transformable t => Transformable (Map k t) Source | |
(Additive v, Num n) => Transformable (Point v n) Source | |
(Additive v, Num n) => Transformable (Transformation v n) Source | |
(Additive v, Traversable v, Floating n) => Transformable (Style v n) Source | |
(Additive v, Traversable v, Floating n) => Transformable (Attribute v n) Source |
|
(Additive v, Num n) => Transformable (Trace v n) Source | |
(Metric v, Floating n) => Transformable (Envelope v n) Source | |
(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) Source | |
(Additive v, Num n) => Transformable (Query v n m) Source | |
Transformable (Prim b v n) Source | The |
(Metric v, Floating n) => Transformable (SubMap b v n m) Source | |
(Metric v, Floating n) => Transformable (Subdiagram b v n m) Source | |
(OrderedField n, Metric v, Semigroup m) => Transformable (QDiagram b v n m) Source | Diagrams can be transformed by transforming each of their components appropriately. |
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
.
TransInv t |
Eq t => Eq (TransInv t) Source | |
Ord t => Ord (TransInv t) Source | |
Show t => Show (TransInv t) Source | |
Monoid t => Monoid (TransInv t) Source | |
Semigroup t => Semigroup (TransInv t) Source | |
Wrapped (TransInv t) Source | |
HasOrigin (TransInv t) Source | |
(Num (N t), Additive (V t), Transformable t) => Transformable (TransInv t) Source | |
Qualifiable a => Qualifiable (TransInv a) Source | |
Traced t => Traced (TransInv t) Source | |
Enveloped t => Enveloped (TransInv t) Source | |
Rewrapped (TransInv t) (TransInv t') Source | |
type Unwrapped (TransInv t) = t Source | |
type N (TransInv t) = N t Source | |
type V (TransInv t) = V t Source |
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 :: v n -> Transformation v n Source
Create a translation.
scaling :: (Additive v, Fractional n) => n -> Transformation v n Source
Create a uniform scaling transformation.
scale :: (InSpace v n a, Eq n, Fractional n, Transformable a) => n -> a -> a Source
Scale uniformly in every dimension by the given scalar.