License | BSD-style (see the file LICENSE) |
---|---|
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | provisional |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell98 |
Operations on affine spaces.
Synopsis
- class Additive (Diff p) => Affine p where
- qdA :: (Affine p, Foldable (Diff p), Num a) => p a -> p a -> a
- distanceA :: (Floating a, Foldable (Diff p), Affine p) => p a -> p a -> a
- newtype Point f a = P (f a)
- lensP :: Lens' (Point g a) (g a)
- _Point :: Iso' (Point f a) (f a)
- (.#) :: Coercible b a => (b -> c) -> (a -> b) -> a -> c
- (#.) :: Coercible c b => (b -> c) -> (a -> b) -> a -> c
- unP :: Point f a -> f a
- origin :: (Additive f, Num a) => Point f a
- relative :: (Additive f, Num a) => Point f a -> Iso' (Point f a) (f a)
Documentation
class Additive (Diff p) => Affine p where Source #
An affine space is roughly a vector space in which we have forgotten or at least pretend to have forgotten the origin.
a .+^ (b .-. a) = b@ (a .+^ u) .+^ v = a .+^ (u ^+^ v)@ (a .-. b) ^+^ v = (a .+^ v) .-. q@
(.-.) :: Num a => p a -> p a -> Diff p a infixl 6 Source #
Get the difference between two points as a vector offset.
(.+^) :: Num a => p a -> Diff p a -> p a infixl 6 Source #
Add a vector offset to a point.
(.-^) :: Num a => p a -> Diff p a -> p a infixl 6 Source #
Subtract a vector offset from a point.
Instances
Affine [] Source # | |
Affine Maybe Source # | |
Affine Complex Source # | |
Affine ZipList Source # | |
Affine Identity Source # | |
Affine IntMap Source # | |
Affine Vector Source # | |
Affine V1 Source # | |
Affine V2 Source # | |
Affine V3 Source # | |
Affine V4 Source # | |
Affine V0 Source # | |
Affine Quaternion Source # | |
Defined in Linear.Affine (.-.) :: Num a => Quaternion a -> Quaternion a -> Diff Quaternion a Source # (.+^) :: Num a => Quaternion a -> Diff Quaternion a -> Quaternion a Source # (.-^) :: Num a => Quaternion a -> Diff Quaternion a -> Quaternion a Source # | |
Affine Plucker Source # | |
Ord k => Affine (Map k) Source # | |
(Eq k, Hashable k) => Affine (HashMap k) Source # | |
Additive f => Affine (Point f) Source # | |
Dim n => Affine (V n) Source # | |
Affine ((->) b :: * -> *) Source # | |
qdA :: (Affine p, Foldable (Diff p), Num a) => p a -> p a -> a Source #
Compute the quadrance of the difference (the square of the distance)
distanceA :: (Floating a, Foldable (Diff p), Affine p) => p a -> p a -> a Source #
Distance between two points in an affine space
A handy wrapper to help distinguish points from vectors at the type level
P (f a) |