| Copyright | (c) Justus Sagemüller 2015 | 
|---|---|
| License | GPL v3 | 
| Maintainer | (@) sagemueller $ geo.uni-koeln.de | 
| Stability | experimental | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Data.Function.Affine
Contents
Description
- data Affine s d c where
- evalAffine :: forall s x y. (Manifold x, Atlas x, HasTrie (ChartIndex x), Manifold y, s ~ Scalar (Needle x), s ~ Scalar (Needle y)) => Affine s x y -> x -> (y, LinearMap s (Needle x) (Needle y))
- fromOffsetSlope :: forall s x y. (LinearSpace x, Atlas x, HasTrie (ChartIndex x), Manifold y, s ~ Scalar x, s ~ Scalar (Needle y)) => y -> LinearMap s x (Needle y) -> Affine s x y
- lensEmbedding :: forall k s x c. (Num' s, LinearSpace x, LinearSpace c, Object k x, Object k c, Scalar x ~ s, Scalar c ~ s, EnhancedCat k (LinearMap s)) => Lens' x c -> Embedding k c x
- correspondingDirections :: forall s x c t. (WithField s AffineManifold c, WithField s AffineManifold x, SemiInner (Needle c), SemiInner (Needle x), RealFrac' s, Traversable t) => (Interior c, Interior x) -> t (Needle c, Needle x) -> Maybe (Embedding (Affine s) c x)
Documentation
data Affine s d c where Source #
Instances
evalAffine :: forall s x y. (Manifold x, Atlas x, HasTrie (ChartIndex x), Manifold y, s ~ Scalar (Needle x), s ~ Scalar (Needle y)) => Affine s x y -> x -> (y, LinearMap s (Needle x) (Needle y)) Source #
fromOffsetSlope :: forall s x y. (LinearSpace x, Atlas x, HasTrie (ChartIndex x), Manifold y, s ~ Scalar x, s ~ Scalar (Needle y)) => y -> LinearMap s x (Needle y) -> Affine s x y Source #
Misc
lensEmbedding :: forall k s x c. (Num' s, LinearSpace x, LinearSpace c, Object k x, Object k c, Scalar x ~ s, Scalar c ~ s, EnhancedCat k (LinearMap s)) => Lens' x c -> Embedding k c x Source #
correspondingDirections :: forall s x c t. (WithField s AffineManifold c, WithField s AffineManifold x, SemiInner (Needle c), SemiInner (Needle x), RealFrac' s, Traversable t) => (Interior c, Interior x) -> t (Needle c, Needle x) -> Maybe (Embedding (Affine s) c x) Source #