| Copyright | (c) 2014-2015 diagrams team (see LICENSE) | 
|---|---|
| License | BSD-style (see LICENSE) | 
| Maintainer | diagrams-discuss@googlegroups.com | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Diagrams.LinearMap
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
- newtype LinearMap v u n = LinearMap {- lapply :: v n -> u n
 
- class LinearMappable a b where
- linmap :: (InSpace v n a, LinearMappable a b, N b ~ n) => LinearMap v (V b) n -> a -> b
- data AffineMap v u n = AffineMap (LinearMap v u n) (u n)
- class (LinearMappable a b, N a ~ N b) => AffineMappable a b where
- mkAffineMap :: (v n -> u n) -> u n -> AffineMap v u n
- toAffineMap :: Transformation v n -> AffineMap v v n
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.
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 Source # | |
| (Metric v, Metric u, OrderedField n, OrderedField m, r ~ Path u m) => LinearMappable (Path v n) r Source # | |
| r ~ FixedSegment u m => LinearMappable (FixedSegment v n) r Source # | |
| Defined in Diagrams.LinearMap Methods vmap :: (Vn (FixedSegment v n) -> Vn r) -> FixedSegment v n -> r Source # | |
| (Metric v, Metric u, OrderedField n, OrderedField m, r ~ SegTree u m) => LinearMappable (SegTree v n) r Source # | |
| (Metric v, Metric u, OrderedField n, OrderedField m, r ~ Trail u m) => LinearMappable (Trail v n) r Source # | |
| LinearMappable (Point v n) (Point u m) Source # | |
| r ~ Offset c u m => LinearMappable (Offset c v n) r Source # | |
| r ~ Segment c u m => LinearMappable (Segment c v n) r Source # | |
| (Metric v, Metric u, OrderedField n, OrderedField m, r ~ Trail' l u m) => LinearMappable (Trail' l v n) r Source # | |
Applying linear maps
linmap :: (InSpace v n a, LinearMappable a b, N b ~ n) => LinearMap v (V b) n -> a -> b Source #
Apply a linear map.
Affine maps
Affine linear maps. Unlike Transformation these do not have to be
   invertible so we can map between spaces.
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 Source # | |
| (Metric v, Metric u, OrderedField n, r ~ Path u n) => AffineMappable (Path v n) r Source # | |
| r ~ FixedSegment u n => AffineMappable (FixedSegment v n) r Source # | |
| Defined in Diagrams.LinearMap Methods amap :: AffineMap (V (FixedSegment v n)) (V r) (N r) -> FixedSegment v n -> r Source # | |
| (Metric v, Metric u, OrderedField n, r ~ SegTree u n) => AffineMappable (SegTree v n) r Source # | |
| (Metric v, Metric u, OrderedField n, r ~ Trail u n) => AffineMappable (Trail v n) r Source # | |
| (Additive v, Num n, r ~ Point u n) => AffineMappable (Point v n) r Source # | |
| r ~ Offset c u n => AffineMappable (Offset c v n) r Source # | |
| r ~ Segment c u n => AffineMappable (Segment c v n) r Source # | |
| (Metric v, Metric u, OrderedField n, r ~ Trail' l u n) => AffineMappable (Trail' l v n) r Source # | |
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.
toAffineMap :: Transformation v n -> AffineMap v v n Source #