diagrams-lib-1.3: Embedded domain-specific language for declarative graphics

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

Diagrams.LinearMap

Contents

Description

Linear maps. Unlike Transformations these are not restricted to the same space. In practice these are used for projections in Diagrams.ThreeD.Projection. Unless you want to work with projections you're probably better off using Transform.

Currently only path-like things can be projected. In the future we hope to support projecting diagrams.

Synopsis

Linear maps

newtype LinearMap v u n Source

Type for holding linear maps. Note that these are not affine transforms so attemping apply a translation with LinearMap will likely produce incorrect results.

Constructors

LinearMap 

Fields

lapply :: v n -> u n
 

class LinearMappable a b where Source

Class of things that have vectors that can be mapped over.

Methods

vmap :: (Vn a -> Vn b) -> a -> b Source

Apply a linear map to an object. If the map is not linear, behaviour will likely be wrong.

Instances

(LinearMappable a b, (~) * r (Located b)) => LinearMappable (Located a) r 
(~) * r (FixedSegment u m) => LinearMappable (FixedSegment v n) r 
(Metric v, Metric u, OrderedField n, OrderedField m, (~) * r (Trail u m)) => LinearMappable (Trail v n) r 
(Metric v, Metric u, OrderedField n, OrderedField m, (~) * r (SegTree u m)) => LinearMappable (SegTree v n) r 
(Metric v, Metric u, OrderedField n, OrderedField m, (~) * r (Path u m)) => LinearMappable (Path v n) r 
LinearMappable (Point v n) (Point u m) 
(~) * r (Segment c u m) => LinearMappable (Segment c v n) r 
(~) * r (Offset c u m) => LinearMappable (Offset c v n) r 
(Metric v, Metric u, OrderedField n, OrderedField m, (~) * r (Trail' l u m)) => LinearMappable (Trail' l v n) r 

Applying linear maps

linmap :: (InSpace v n a, Foldable v, LinearMappable a b, N b ~ n) => LinearMap v (V b) n -> a -> b Source

Apply a linear map.

Affine maps

data AffineMap v u n Source

Affine linear maps. Unlike Transformation these do not have to be invertible so we can map between spaces.

Constructors

AffineMap (LinearMap v u n) (u n) 

class (LinearMappable a b, N a ~ N b) => AffineMappable a b where Source

Minimal complete definition

Nothing

Methods

amap :: (Additive (V a), Foldable (V a), Additive (V b), Num (N b)) => AffineMap (V a) (V b) (N b) -> a -> b Source

Affine map over an object. Has a default implimentation of only applying the linear map

Instances

(LinearMappable a b, (~) * (N a) (N b), (~) * r (Located b)) => AffineMappable (Located a) r 
(Additive v, Foldable v, Num n, (~) * r (Point u n)) => AffineMappable (Point v n) r 
(~) * r (FixedSegment u n) => AffineMappable (FixedSegment v n) r 
(Metric v, Metric u, OrderedField n, (~) * r (Trail u n)) => AffineMappable (Trail v n) r 
(Metric v, Metric u, OrderedField n, (~) * r (SegTree u n)) => AffineMappable (SegTree v n) r 
(Metric v, Metric u, OrderedField n, (~) * r (Path u n)) => AffineMappable (Path v n) r 
(~) * r (Segment c u n) => AffineMappable (Segment c v n) r 
(~) * r (Offset c u n) => AffineMappable (Offset c v n) r 
(Metric v, Metric u, OrderedField n, (~) * r (Trail' l u n)) => AffineMappable (Trail' l v n) r 

Constructing affine maps

mkAffineMap :: (v n -> u n) -> u n -> AffineMap v u n Source

Make an affine map from a linear function and a translation.