diagrams-core-0.5.0.1: Core libraries for diagrams EDSL

Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone

Graphics.Rendering.Diagrams.Transform

Contents

Description

Graphics.Rendering.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 Source

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

Constructors

(u :-* v) :-: (v :-* u) 

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 :-: vSource

Create an invertible linear map from two functions which are assumed to be linear inverses.

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

Invert a linear map.

lapp :: (VectorSpace v, Scalar u ~ Scalar v, HasLinearMap u) => (u :-: v) -> u -> vSource

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.

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.

Newtype (QDiagram b v m) (UDTree (UpAnnots v m) (DownAnnots v) (Prim b v)) 

inv :: HasLinearMap v => Transformation v -> Transformation vSource

Invert a transformation.

transp :: Transformation v -> v :-: vSource

Get the transpose of a transformation (ignoring the translation component).

transl :: Transformation v -> vSource

Get the translational component of a transformation.

apply :: HasLinearMap v => Transformation v -> v -> vSource

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 vSource

Apply a transformation to a point.

fromLinear :: AdditiveGroup v => (v :-: v) -> (v :-: v) -> Transformation vSource

Create a general affine transformation from an invertible linear transformation and its transpose. The translational component is assumed to be zero.

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 whereSource

Type class for things t which can be transformed.

Methods

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

Apply a transformation to an object.

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 

Fields

unTransInv :: 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 vSource

Create a translation.

translate :: (Transformable t, HasLinearMap (V t)) => V t -> t -> tSource

Translate by a vector.

scaling :: (HasLinearMap v, Fractional (Scalar v)) => Scalar v -> Transformation vSource

Create a uniform scaling transformation.

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

Scale uniformly in every dimension by the given scalar.