diagrams-core-1.4: Core libraries for diagrams EDSL

Copyright(c) 2011-2015 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

Semigroup ((:-:) a a) Source # 

Methods

(<>) :: (a :-: a) -> (a :-: a) -> a :-: a #

sconcat :: NonEmpty (a :-: a) -> a :-: a #

stimes :: Integral b => b -> (a :-: a) -> a :-: a #

Monoid ((:-:) v v) Source #

Invertible linear maps from a vector space to itself form a monoid under composition.

Methods

mempty :: v :-: v #

mappend :: (v :-: v) -> (v :-: v) -> v :-: v #

mconcat :: [v :-: v] -> v :-: 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 :: (u :-: v) -> u -> v Source #

Apply a linear map to a vector.

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).

Constructors

Transformation (v n :-: v n) (v n :-: v n) (v n) 

Instances

(Additive v, Num n) => Semigroup (Transformation v n) Source #

Transformations are closed under composition; t1 <> t2 is the transformation which performs first t2, then t1.

(Additive v, Num n) => Monoid (Transformation v n) Source # 
(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.

Methods

act :: Transformation v n -> a -> a #

type N (Transformation v n) Source # 
type N (Transformation v n) = n
type V (Transformation v n) Source # 
type V (Transformation v n) = v

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. (Additive (V a), Traversable (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 :: (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.

listRep :: Foldable v => v n -> [n] Source #

Convert a vector v to a list of scalars.

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
  

eye :: (HasBasis v, Num n) => v (v n) Source #

Identity matrix.

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.

Instances

class (Additive v, Representable v, Rep v ~ E v) => HasBasis v Source #

An Additive vector space whose representation is made up of basis elements.

Instances

(Additive v, Representable v, (~) * (Rep v) (E v)) => HasBasis v Source # 

class Transformable t where Source #

Type class for things t which can be transformed.

Minimal complete definition

transform

Methods

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

Apply a transformation to an object.

Instances

Transformable t => Transformable [t] Source # 

Methods

transform :: Transformation (V [t]) (N [t]) -> [t] -> [t] Source #

(Transformable t, Ord t) => Transformable (Set t) Source # 

Methods

transform :: Transformation (V (Set t)) (N (Set t)) -> Set t -> 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 # 

Methods

transform :: Transformation (V (s -> t)) (N (s -> t)) -> (s -> t) -> s -> t Source #

(Transformable t, Transformable s, (~) (* -> *) (V t) (V s), (~) * (N t) (N s)) => Transformable (t, s) Source # 

Methods

transform :: Transformation (V (t, s)) (N (t, s)) -> (t, s) -> (t, s) Source #

Transformable t => Transformable (Map k t) Source # 

Methods

transform :: Transformation (V (Map k t)) (N (Map k t)) -> Map k t -> Map k t Source #

(Additive v, Num n) => Transformable (Point v n) Source # 

Methods

transform :: Transformation (V (Point v n)) (N (Point v n)) -> Point v n -> Point v n Source #

(InSpace v n t, Transformable t, HasLinearMap v, Floating n) => Transformable (Measured n t) Source # 

Methods

transform :: Transformation (V (Measured n t)) (N (Measured n t)) -> Measured n t -> Measured n t Source #

(Additive v, Num n) => Transformable (Transformation v n) Source # 
(Additive v, Traversable v, Floating n) => Transformable (Style v n) Source # 

Methods

transform :: Transformation (V (Style v n)) (N (Style v n)) -> Style v n -> Style v n Source #

(Additive v, Traversable v, Floating n) => Transformable (Attribute v n) Source #

TAttributes are transformed directly, MAttributes have their local scale multiplied by the average scale of the transform. Plain Attributes are unaffected.

Methods

transform :: Transformation (V (Attribute v n)) (N (Attribute v n)) -> Attribute v n -> Attribute v n Source #

(Additive v, Num n) => Transformable (Trace v n) Source # 

Methods

transform :: Transformation (V (Trace v n)) (N (Trace v n)) -> Trace v n -> Trace v n Source #

(Metric v, Floating n) => Transformable (Envelope v n) Source # 

Methods

transform :: Transformation (V (Envelope v n)) (N (Envelope v n)) -> Envelope v n -> 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 # 

Methods

transform :: Transformation (V (t, s, u)) (N (t, s, u)) -> (t, s, u) -> (t, s, u) Source #

(Additive v, Num n) => Transformable (Query v n m) Source # 

Methods

transform :: Transformation (V (Query v n m)) (N (Query v n m)) -> Query v n m -> Query v n m Source #

Transformable (Prim b v n) Source #

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

Methods

transform :: Transformation (V (Prim b v n)) (N (Prim b v n)) -> Prim b v n -> Prim b v n Source #

Transformable (SubMap b v n m) Source # 

Methods

transform :: Transformation (V (SubMap b v n m)) (N (SubMap b v n m)) -> SubMap b v n m -> SubMap b v n m Source #

Transformable (Subdiagram b v n m) Source # 

Methods

transform :: Transformation (V (Subdiagram b v n m)) (N (Subdiagram b v n m)) -> Subdiagram b v n m -> 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.

Methods

transform :: Transformation (V (QDiagram b v n m)) (N (QDiagram b v n m)) -> QDiagram b v n m -> QDiagram b v n m Source #

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 

Instances

Eq t => Eq (TransInv t) Source # 

Methods

(==) :: TransInv t -> TransInv t -> Bool #

(/=) :: TransInv t -> TransInv t -> Bool #

Ord t => Ord (TransInv t) Source # 

Methods

compare :: TransInv t -> TransInv t -> Ordering #

(<) :: TransInv t -> TransInv t -> Bool #

(<=) :: TransInv t -> TransInv t -> Bool #

(>) :: TransInv t -> TransInv t -> Bool #

(>=) :: TransInv t -> TransInv t -> Bool #

max :: TransInv t -> TransInv t -> TransInv t #

min :: TransInv t -> TransInv t -> TransInv t #

Show t => Show (TransInv t) Source # 

Methods

showsPrec :: Int -> TransInv t -> ShowS #

show :: TransInv t -> String #

showList :: [TransInv t] -> ShowS #

Semigroup t => Semigroup (TransInv t) Source # 

Methods

(<>) :: TransInv t -> TransInv t -> TransInv t #

sconcat :: NonEmpty (TransInv t) -> TransInv t #

stimes :: Integral b => b -> TransInv t -> TransInv t #

Monoid t => Monoid (TransInv t) Source # 

Methods

mempty :: TransInv t #

mappend :: TransInv t -> TransInv t -> TransInv t #

mconcat :: [TransInv t] -> TransInv t #

Wrapped (TransInv t) Source # 

Associated Types

type Unwrapped (TransInv t) :: * #

HasOrigin (TransInv t) Source # 

Methods

moveOriginTo :: Point (V (TransInv t)) (N (TransInv t)) -> TransInv t -> TransInv t Source #

(Num (N t), Additive (V t), Transformable t) => Transformable (TransInv t) Source # 
Qualifiable a => Qualifiable (TransInv a) Source # 

Methods

(.>>) :: IsName a => a -> TransInv a -> TransInv a Source #

Traced t => Traced (TransInv t) Source # 

Methods

getTrace :: TransInv t -> Trace (V (TransInv t)) (N (TransInv t)) Source #

Enveloped t => Enveloped (TransInv t) Source # 

Methods

getEnvelope :: TransInv t -> Envelope (V (TransInv t)) (N (TransInv t)) Source #

Rewrapped (TransInv t) (TransInv t') Source # 
type Unwrapped (TransInv t) Source # 
type Unwrapped (TransInv t) = t
type N (TransInv t) Source # 
type N (TransInv t) = N t
type V (TransInv t) Source # 
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 :: v n -> Transformation v n Source #

Create a translation.

translate :: Transformable t => Vn t -> t -> t Source #

Translate by a vector.

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.