diagrams-core-1.2: Core libraries for diagrams EDSL

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

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.

Synopsis

Transformations

Invertible linear transformations

data u :-: v infixr 7 Source

(v1 :-: v2) is a linear map paired with its inverse.

Constructors

(u :-* v) :-: (v :-* u) infixr 7 

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.

linv :: (u :-: v) -> v :-: u Source

Invert a linear map.

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; t1 <> t2 is the transformation which performs first t2, then t1.

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.

dropTransl :: AdditiveGroup v => Transformation v -> Transformation v Source

Drop the translational component of a transformation, leaving only the linear part.

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.

dimension :: forall a. HasLinearMap (V a) => a -> Int Source

Get the dimension of an object whose vector space is an instance of HasLinearMap, e.g. transformations, paths, diagrams, etc.

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.

listRep :: HasLinearMap v => v -> [Scalar v] Source

Convert a vector v to a list of scalars.

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.

matrixHomRep :: HasLinearMap v => Transformation v -> [[Scalar v]] 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 :: (HasLinearMap v, Num (Scalar v)) => Transformation v -> Scalar v Source

The determinant of a Transformation.

avgScale :: (HasLinearMap v, Floating (Scalar v)) => Transformation v -> Scalar v 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, 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

class HasLinearMap (V t) => Transformable t where Source

Type class for things t which can be transformed.

Methods

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

Apply a transformation to an object.

Instances

Transformable Double 
Transformable Rational 
Transformable t => Transformable [t] 
(Transformable t, Ord t) => Transformable (Set t) 
Transformable m => Transformable (Deletable m) 
HasLinearMap v => Transformable (Point v) 
Transformable t => Transformable (TransInv t) 
HasLinearMap v => Transformable (Transformation v) 
HasLinearMap v => Transformable (Style v) 
HasLinearMap v => Transformable (Attribute v) 
HasLinearMap v => Transformable (Trace v) 
(HasLinearMap v, InnerSpace v, Floating (Scalar v)) => Transformable (Envelope v) 
(HasLinearMap v, Floating (Scalar v)) => Transformable (Measure v) 
(HasBasis (V b), HasTrie (Basis (V b)), Transformable a, Transformable b, (~) * (V b) (V a)) => Transformable (a -> b) 
(Transformable a, Transformable b, (~) * (V a) (V b)) => Transformable (a, b) 
Transformable t => Transformable (Map k t) 
HasLinearMap v => Transformable (Query v m) 
HasLinearMap v => Transformable (Prim b v)

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

(Transformable a, Transformable b, Transformable c, (~) * (V a) (V b), (~) * (V a) (V c)) => Transformable (a, b, c) 
(InnerSpace v, Floating (Scalar v), HasLinearMap v) => Transformable (SubMap b v m) 
(HasLinearMap v, InnerSpace v, Floating (Scalar v)) => Transformable (Subdiagram b v m) 
(HasLinearMap v, OrderedField (Scalar v), InnerSpace v, Semigroup m) => Transformable (QDiagram b v m)

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

Translational invariance

newtype TransInv t Source

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 

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.

scale :: (Transformable t, Fractional (Scalar (V t)), Eq (Scalar (V t))) => Scalar (V t) -> t -> t Source

Scale uniformly in every dimension by the given scalar.