-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Linear Algebra -- -- Types and combinators for linear algebra on free vector spaces @package linear @version 1.10.1.2 -- | Orphans module Linear.Instances instance Traversable1 Complex instance Foldable1 Complex instance Traversable Complex instance Foldable Complex instance MonadFix Complex instance MonadZip Complex instance Monad Complex instance Bind Complex instance Applicative Complex instance Apply Complex instance Functor Complex instance (Hashable k, Eq k) => Bind (HashMap k) instance (Hashable k, Eq k) => Apply (HashMap k) -- | Operations on free vector spaces. module Linear.Vector -- | A vector is an additive group with additional structure. class Functor f => Additive f where zero = to1 gzero (^+^) = liftU2 (+) x ^-^ y = x ^+^ negated y lerp alpha u v = alpha *^ u ^+^ (1 - alpha) *^ v liftU2 = liftA2 liftI2 = liftA2 zero :: (Additive f, Num a) => f a (^+^) :: (Additive f, Num a) => f a -> f a -> f a (^-^) :: (Additive f, Num a) => f a -> f a -> f a lerp :: (Additive f, Num a) => a -> f a -> f a -> f a liftU2 :: Additive f => (a -> a -> a) -> f a -> f a -> f a liftI2 :: Additive f => (a -> b -> c) -> f a -> f b -> f c -- | Basis element newtype E t E :: (forall x. Lens' (t x) x) -> E t el :: E t -> forall x. Lens' (t x) x -- | Compute the negation of a vector -- --
--   >>> negated (V2 2 4)
--   V2 (-2) (-4)
--   
negated :: (Functor f, Num a) => f a -> f a -- | Compute the right scalar product -- --
--   >>> V2 3 4 ^* 2
--   V2 6 8
--   
(^*) :: (Functor f, Num a) => f a -> a -> f a -- | Compute the left scalar product -- --
--   >>> 2 *^ V2 3 4
--   V2 6 8
--   
(*^) :: (Functor f, Num a) => a -> f a -> f a -- | Compute division by a scalar on the right. (^/) :: (Functor f, Fractional a) => f a -> a -> f a -- | Sum over multiple vectors -- --
--   >>> sumV [V2 1 1, V2 3 4]
--   V2 4 5
--   
sumV :: (Foldable f, Additive v, Num a) => f (v a) -> v a -- | Produce a default basis for a vector space. If the dimensionality of -- the vector space is not statically known, see basisFor. basis :: (Applicative t, Traversable t, Num a) => [t a] -- | Produce a default basis for a vector space from which the argument is -- drawn. basisFor :: (Traversable t, Num a) => t b -> [t a] -- | Produce a diagonal matrix from a vector. kronecker :: (Traversable t, Num a) => t a -> t (t a) -- | Outer (tensor) product of two vectors outer :: (Functor f, Functor g, Num a) => f a -> g a -> f (g a) -- | Create a unit vector. -- --
--   >>> unit _x :: V2 Int
--   V2 1 0
--   
unit :: (Applicative t, Num a) => ASetter' (t a) a -> t a instance Applicative SetOne instance Functor SetOne instance Additive Identity instance Additive Complex instance Additive ((->) b) instance (Eq k, Hashable k) => Additive (HashMap k) instance Ord k => Additive (Map k) instance Additive IntMap instance Additive [] instance Additive Maybe instance Additive Vector instance Additive ZipList instance GAdditive Par1 instance GAdditive f => GAdditive (M1 i c f) instance Additive f => GAdditive (Rec1 f) instance (GAdditive f, GAdditive g) => GAdditive (f :*: g) instance GAdditive U1 -- | Testing for values "near" zero module Linear.Epsilon -- | Provides a fairly subjective test to see if a quantity is near zero. -- --
--   >>> nearZero (1e-11 :: Double)
--   False
--   
-- --
--   >>> nearZero (1e-17 :: Double)
--   True
--   
-- --
--   >>> nearZero (1e-5 :: Float)
--   False
--   
-- --
--   >>> nearZero (1e-7 :: Float)
--   True
--   
class Num a => Epsilon a nearZero :: Epsilon a => a -> Bool instance Epsilon CDouble instance Epsilon CFloat instance Epsilon Double instance Epsilon Float -- | Free metric spaces module Linear.Metric -- | Free and sparse inner product/metric spaces. class Additive f => Metric f where dot x y = sum $ liftI2 (*) x y quadrance v = dot v v qd f g = quadrance (f ^-^ g) distance f g = norm (f ^-^ g) norm v = sqrt (quadrance v) signorm v = fmap (/ m) v where m = norm v dot :: (Metric f, Num a) => f a -> f a -> a quadrance :: (Metric f, Num a) => f a -> a qd :: (Metric f, Num a) => f a -> f a -> a distance :: (Metric f, Floating a) => f a -> f a -> a norm :: (Metric f, Floating a) => f a -> a signorm :: (Metric f, Floating a) => f a -> f a -- | Normalize a Metric functor to have unit norm. This -- function does not change the functor if its norm is 0 or 1. normalize :: (Floating a, Metric f, Epsilon a) => f a -> f a instance Metric Vector instance (Hashable k, Eq k) => Metric (HashMap k) instance Ord k => Metric (Map k) instance Metric IntMap instance Metric Identity -- | 0-D Vectors module Linear.V0 -- | A 0-dimensional vector -- --
--   >>> pure 1 :: V0 Int
--   V0
--   
-- --
--   >>> V0 + V0
--   V0
--   
data V0 a V0 :: V0 a instance Typeable V0 instance Eq (V0 a) instance Ord (V0 a) instance Show (V0 a) instance Read (V0 a) instance Ix (V0 a) instance Enum (V0 a) instance Data a => Data (V0 a) instance Generic (V0 a) instance Generic1 V0 instance Datatype D1V0 instance Constructor C1_0V0 instance MonadFix V0 instance MonadZip V0 instance Vector Vector (V0 a) instance MVector MVector (V0 a) instance Unbox (V0 a) instance Each (V0 a) (V0 b) a b instance Ixed (V0 a) instance Representable V0 instance TraversableWithIndex (E V0) V0 instance FoldableWithIndex (E V0) V0 instance FunctorWithIndex (E V0) V0 instance Storable a => Storable (V0 a) instance Epsilon a => Epsilon (V0 a) instance Hashable (V0 a) instance Distributive V0 instance Metric V0 instance Fractional (V0 a) instance Num (V0 a) instance Monad V0 instance Bind V0 instance Additive V0 instance Applicative V0 instance Apply V0 instance Traversable V0 instance Foldable V0 instance Functor V0 -- | 1-D Vectors module Linear.V1 -- | A 1-dimensional vector -- --
--   >>> pure 1 :: V1 Int
--   V1 1
--   
-- --
--   >>> V1 2 + V1 3
--   V1 5
--   
-- --
--   >>> V1 2 * V1 3
--   V1 6
--   
-- --
--   >>> sum (V1 2)
--   2
--   
newtype V1 a V1 :: a -> V1 a -- | A space that has at least 1 basis vector _x. class R1 t _x :: R1 t => Lens' (t a) a ex :: R1 t => E t instance Typeable V1 instance Eq a => Eq (V1 a) instance Ord a => Ord (V1 a) instance Show a => Show (V1 a) instance Read a => Read (V1 a) instance Data a => Data (V1 a) instance Functor V1 instance Foldable V1 instance Traversable V1 instance Epsilon a => Epsilon (V1 a) instance Storable a => Storable (V1 a) instance Generic (V1 a) instance Generic1 V1 instance Datatype D1V1 instance Constructor C1_0V1 instance MonadFix V1 instance MonadZip V1 instance Unbox a => Vector Vector (V1 a) instance Unbox a => MVector MVector (V1 a) instance Unbox a => Unbox (V1 a) instance Each (V1 a) (V1 b) a b instance Ixed (V1 a) instance TraversableWithIndex (E V1) V1 instance FoldableWithIndex (E V1) V1 instance FunctorWithIndex (E V1) V1 instance Representable V1 instance Ix a => Ix (V1 a) instance Distributive V1 instance R1 Identity instance R1 V1 instance Metric V1 instance Hashable a => Hashable (V1 a) instance Fractional a => Fractional (V1 a) instance Num a => Num (V1 a) instance Monad V1 instance Bind V1 instance Additive V1 instance Applicative V1 instance Apply V1 instance Traversable1 V1 instance Foldable1 V1 -- | 2-D Vectors module Linear.V2 -- | A 2-dimensional vector -- --
--   >>> pure 1 :: V2 Int
--   V2 1 1
--   
-- --
--   >>> V2 1 2 + V2 3 4
--   V2 4 6
--   
-- --
--   >>> V2 1 2 * V2 3 4
--   V2 3 8
--   
-- --
--   >>> sum (V2 1 2)
--   3
--   
data V2 a V2 :: !a -> !a -> V2 a -- | A space that has at least 1 basis vector _x. class R1 t _x :: R1 t => Lens' (t a) a -- | A space that distinguishes 2 orthogonal basis vectors _x and -- _y, but may have more. class R1 t => R2 t where _y = _xy . _y _y :: (R2 t, Functor f) => (a -> f a) -> t a -> f (t a) _xy :: (R2 t, Functor f) => (V2 a -> f (V2 a)) -> t a -> f (t a) ex :: R1 t => E t ey :: R2 t => E t -- | the counter-clockwise perpendicular vector -- --
--   >>> perp $ V2 10 20
--   V2 (-20) 10
--   
perp :: Num a => V2 a -> V2 a angle :: Floating a => a -> V2 a instance Typeable V2 instance Eq a => Eq (V2 a) instance Ord a => Ord (V2 a) instance Show a => Show (V2 a) instance Read a => Read (V2 a) instance Data a => Data (V2 a) instance Generic (V2 a) instance Generic1 V2 instance Datatype D1V2 instance Constructor C1_0V2 instance MonadFix V2 instance MonadZip V2 instance Unbox a => Vector Vector (V2 a) instance Unbox a => MVector MVector (V2 a) instance Unbox a => Unbox (V2 a) instance Each (V2 a) (V2 b) a b instance Ixed (V2 a) instance TraversableWithIndex (E V2) V2 instance FoldableWithIndex (E V2) V2 instance FunctorWithIndex (E V2) V2 instance Representable V2 instance Ix a => Ix (V2 a) instance Storable a => Storable (V2 a) instance Epsilon a => Epsilon (V2 a) instance Distributive V2 instance R2 V2 instance R1 V2 instance Metric V2 instance Fractional a => Fractional (V2 a) instance Num a => Num (V2 a) instance Monad V2 instance Bind V2 instance Additive V2 instance Hashable a => Hashable (V2 a) instance Applicative V2 instance Apply V2 instance Traversable1 V2 instance Foldable1 V2 instance Traversable V2 instance Foldable V2 instance Functor V2 -- | 3-D Vectors module Linear.V3 -- | A 3-dimensional vector data V3 a V3 :: !a -> !a -> !a -> V3 a -- | cross product cross :: Num a => V3 a -> V3 a -> V3 a -- | scalar triple product triple :: Num a => V3 a -> V3 a -> V3 a -> a -- | A space that has at least 1 basis vector _x. class R1 t _x :: R1 t => Lens' (t a) a -- | A space that distinguishes 2 orthogonal basis vectors _x and -- _y, but may have more. class R1 t => R2 t where _y = _xy . _y _y :: (R2 t, Functor f) => (a -> f a) -> t a -> f (t a) _xy :: (R2 t, Functor f) => (V2 a -> f (V2 a)) -> t a -> f (t a) -- | A space that distinguishes 3 orthogonal basis vectors: _x, -- _y, and _z. (It may have more) class R2 t => R3 t _z :: (R3 t, Functor f) => (a -> f a) -> t a -> f (t a) _xyz :: (R3 t, Functor f) => (V3 a -> f (V3 a)) -> t a -> f (t a) ex :: R1 t => E t ey :: R2 t => E t ez :: R3 t => E t instance Typeable V3 instance Eq a => Eq (V3 a) instance Ord a => Ord (V3 a) instance Show a => Show (V3 a) instance Read a => Read (V3 a) instance Data a => Data (V3 a) instance Generic (V3 a) instance Generic1 V3 instance Datatype D1V3 instance Constructor C1_0V3 instance MonadFix V3 instance MonadZip V3 instance Unbox a => Vector Vector (V3 a) instance Unbox a => MVector MVector (V3 a) instance Unbox a => Unbox (V3 a) instance Each (V3 a) (V3 b) a b instance Ixed (V3 a) instance TraversableWithIndex (E V3) V3 instance FoldableWithIndex (E V3) V3 instance FunctorWithIndex (E V3) V3 instance Representable V3 instance Ix a => Ix (V3 a) instance Epsilon a => Epsilon (V3 a) instance Storable a => Storable (V3 a) instance R3 V3 instance R2 V3 instance R1 V3 instance Distributive V3 instance Metric V3 instance Hashable a => Hashable (V3 a) instance Fractional a => Fractional (V3 a) instance Num a => Num (V3 a) instance Monad V3 instance Bind V3 instance Additive V3 instance Applicative V3 instance Apply V3 instance Traversable1 V3 instance Foldable1 V3 instance Traversable V3 instance Foldable V3 instance Functor V3 -- | 4-D Vectors module Linear.V4 -- | A 4-dimensional vector. data V4 a V4 :: !a -> !a -> !a -> !a -> V4 a -- | Convert a 3-dimensional affine vector into a 4-dimensional homogeneous -- vector. vector :: Num a => V3 a -> V4 a -- | Convert a 3-dimensional affine point into a 4-dimensional homogeneous -- vector. point :: Num a => V3 a -> V4 a -- | Convert 4-dimensional projective coordinates to a 3-dimensional point. -- This operation may be denoted, euclidean [x:y:z:w] = (x/w, y/w, -- z/w) where the projective, homogenous, coordinate -- [x:y:z:w] is one of many associated with a single point -- (x/w, y/w, z/w). normalizePoint :: Fractional a => V4 a -> V3 a -- | A space that has at least 1 basis vector _x. class R1 t _x :: R1 t => Lens' (t a) a -- | A space that distinguishes 2 orthogonal basis vectors _x and -- _y, but may have more. class R1 t => R2 t where _y = _xy . _y _y :: (R2 t, Functor f) => (a -> f a) -> t a -> f (t a) _xy :: (R2 t, Functor f) => (V2 a -> f (V2 a)) -> t a -> f (t a) -- | A space that distinguishes 3 orthogonal basis vectors: _x, -- _y, and _z. (It may have more) class R2 t => R3 t _z :: (R3 t, Functor f) => (a -> f a) -> t a -> f (t a) _xyz :: (R3 t, Functor f) => (V3 a -> f (V3 a)) -> t a -> f (t a) -- | A space that distinguishes orthogonal basis vectors _x, -- _y, _z, _w. (It may have more.) class R3 t => R4 t _w :: (R4 t, Functor f) => (a -> f a) -> t a -> f (t a) _xyzw :: (R4 t, Functor f) => (V4 a -> f (V4 a)) -> t a -> f (t a) ex :: R1 t => E t ey :: R2 t => E t ez :: R3 t => E t ew :: R4 t => E t instance Typeable V4 instance Eq a => Eq (V4 a) instance Ord a => Ord (V4 a) instance Show a => Show (V4 a) instance Read a => Read (V4 a) instance Data a => Data (V4 a) instance Generic (V4 a) instance Generic1 V4 instance Datatype D1V4 instance Constructor C1_0V4 instance MonadFix V4 instance MonadZip V4 instance Unbox a => Vector Vector (V4 a) instance Unbox a => MVector MVector (V4 a) instance Unbox a => Unbox (V4 a) instance Each (V4 a) (V4 b) a b instance Ixed (V4 a) instance TraversableWithIndex (E V4) V4 instance FoldableWithIndex (E V4) V4 instance FunctorWithIndex (E V4) V4 instance Representable V4 instance Ix a => Ix (V4 a) instance Epsilon a => Epsilon (V4 a) instance Storable a => Storable (V4 a) instance R4 V4 instance R3 V4 instance R2 V4 instance R1 V4 instance Hashable a => Hashable (V4 a) instance Distributive V4 instance Metric V4 instance Fractional a => Fractional (V4 a) instance Num a => Num (V4 a) instance Monad V4 instance Bind V4 instance Additive V4 instance Apply V4 instance Applicative V4 instance Traversable1 V4 instance Foldable1 V4 instance Traversable V4 instance Foldable V4 instance Functor V4 -- | Plücker coordinates for lines in 3d homogeneous space. module Linear.Plucker -- | Plücker coordinates for lines in a 3-dimensional space. data Plucker a Plucker :: !a -> !a -> !a -> !a -> !a -> !a -> Plucker a -- | Valid Plücker coordinates p will have squaredError -- p == 0 -- -- That said, floating point makes a mockery of this claim, so you may -- want to use nearZero. squaredError :: (Eq a, Num a) => Plucker a -> a -- | Checks if the line is near-isotropic (isotropic vectors in this -- quadratic space represent lines in real 3d space). isotropic :: Epsilon a => Plucker a -> Bool -- | This isn't th actual metric because this bilinear form gives rise to -- an isotropic quadratic space (><) :: Num a => Plucker a -> Plucker a -> a -- | Given a pair of points represented by homogeneous coordinates generate -- Plücker coordinates for the line through them, directed from the -- second towards the first. plucker :: Num a => V4 a -> V4 a -> Plucker a -- | Given a pair of 3D points, generate Plücker coordinates for the line -- through them, directed from the second towards the first. plucker3D :: Num a => V3 a -> V3 a -> Plucker a -- | Checks if two lines are parallel. parallel :: Epsilon a => Plucker a -> Plucker a -> Bool -- | Checks if two lines intersect (or nearly intersect). intersects :: (Epsilon a, Ord a) => Plucker a -> Plucker a -> Bool -- | Describe how two lines pass each other. data LinePass -- | The lines are coplanar (parallel or intersecting). Coplanar :: LinePass -- | The lines pass each other clockwise (right-handed screw) Clockwise :: LinePass -- | The lines pass each other counterclockwise (left-handed screw). Counterclockwise :: LinePass -- | Check how two lines pass each other. passes l1 l2 describes -- l2 when looking down l1. passes :: (Epsilon a, Num a, Ord a) => Plucker a -> Plucker a -> LinePass -- | The minimum squared distance of a line from the origin. quadranceToOrigin :: Fractional a => Plucker a -> a -- | The point where a line is closest to the origin. closestToOrigin :: Fractional a => Plucker a -> V3 a -- | Not all 6-dimensional points correspond to a line in 3D. This -- predicate tests that a Plücker coordinate lies on the Grassmann -- manifold, and does indeed represent a 3D line. isLine :: Epsilon a => Plucker a -> Bool -- | When lines are represented as Plücker coordinates, we have the ability -- to check for both directed and undirected equality. Undirected -- equality between Lines (or a Line and a Ray) -- checks that the two lines coincide in 3D space. Directed equality, -- between two Rays, checks that two lines coincide in 3D, and -- have the same direction. To accomodate these two notions of equality, -- we use an Eq instance on the Coincides data type. -- -- For example, to check the directed equality between two lines, -- p1 and p2, we write, Ray p1 == Ray p2. data Coincides a Line :: Plucker a -> Coincides a Ray :: Plucker a -> Coincides a -- | These elements form a basis for the Plücker space, or the Grassmanian -- manifold Gr(2,V4). -- --
--   p01 :: Lens' (Plucker a) a
--   p02 :: Lens' (Plucker a) a
--   p03 :: Lens' (Plucker a) a
--   p23 :: Lens' (Plucker a) a
--   p31 :: Lens' (Plucker a) a
--   p12 :: Lens' (Plucker a) a
--   
p01 :: Lens' (Plucker a) a -- | These elements form a basis for the Plücker space, or the Grassmanian -- manifold Gr(2,V4). -- --
--   p01 :: Lens' (Plucker a) a
--   p02 :: Lens' (Plucker a) a
--   p03 :: Lens' (Plucker a) a
--   p23 :: Lens' (Plucker a) a
--   p31 :: Lens' (Plucker a) a
--   p12 :: Lens' (Plucker a) a
--   
p02 :: Lens' (Plucker a) a -- | These elements form a basis for the Plücker space, or the Grassmanian -- manifold Gr(2,V4). -- --
--   p01 :: Lens' (Plucker a) a
--   p02 :: Lens' (Plucker a) a
--   p03 :: Lens' (Plucker a) a
--   p23 :: Lens' (Plucker a) a
--   p31 :: Lens' (Plucker a) a
--   p12 :: Lens' (Plucker a) a
--   
p03 :: Lens' (Plucker a) a -- | These elements form an alternate basis for the Plücker space, or the -- Grassmanian manifold Gr(2,V4). -- --
--   p10 :: Num a => Lens' (Plucker a) a
--   p20 :: Num a => Lens' (Plucker a) a
--   p30 :: Num a => Lens' (Plucker a) a
--   p32 :: Num a => Lens' (Plucker a) a
--   p13 :: Num a => Lens' (Plucker a) a
--   p21 :: Num a => Lens' (Plucker a) a
--   
p10 :: (Functor f, Num a) => (a -> f a) -> Plucker a -> f (Plucker a) -- | These elements form a basis for the Plücker space, or the Grassmanian -- manifold Gr(2,V4). -- --
--   p01 :: Lens' (Plucker a) a
--   p02 :: Lens' (Plucker a) a
--   p03 :: Lens' (Plucker a) a
--   p23 :: Lens' (Plucker a) a
--   p31 :: Lens' (Plucker a) a
--   p12 :: Lens' (Plucker a) a
--   
p12 :: Lens' (Plucker a) a -- | These elements form an alternate basis for the Plücker space, or the -- Grassmanian manifold Gr(2,V4). -- --
--   p10 :: Num a => Lens' (Plucker a) a
--   p20 :: Num a => Lens' (Plucker a) a
--   p30 :: Num a => Lens' (Plucker a) a
--   p32 :: Num a => Lens' (Plucker a) a
--   p13 :: Num a => Lens' (Plucker a) a
--   p21 :: Num a => Lens' (Plucker a) a
--   
p13 :: (Functor f, Num a) => (a -> f a) -> Plucker a -> f (Plucker a) -- | These elements form an alternate basis for the Plücker space, or the -- Grassmanian manifold Gr(2,V4). -- --
--   p10 :: Num a => Lens' (Plucker a) a
--   p20 :: Num a => Lens' (Plucker a) a
--   p30 :: Num a => Lens' (Plucker a) a
--   p32 :: Num a => Lens' (Plucker a) a
--   p13 :: Num a => Lens' (Plucker a) a
--   p21 :: Num a => Lens' (Plucker a) a
--   
p20 :: (Functor f, Num a) => (a -> f a) -> Plucker a -> f (Plucker a) -- | These elements form an alternate basis for the Plücker space, or the -- Grassmanian manifold Gr(2,V4). -- --
--   p10 :: Num a => Lens' (Plucker a) a
--   p20 :: Num a => Lens' (Plucker a) a
--   p30 :: Num a => Lens' (Plucker a) a
--   p32 :: Num a => Lens' (Plucker a) a
--   p13 :: Num a => Lens' (Plucker a) a
--   p21 :: Num a => Lens' (Plucker a) a
--   
p21 :: (Functor f, Num a) => (a -> f a) -> Plucker a -> f (Plucker a) -- | These elements form a basis for the Plücker space, or the Grassmanian -- manifold Gr(2,V4). -- --
--   p01 :: Lens' (Plucker a) a
--   p02 :: Lens' (Plucker a) a
--   p03 :: Lens' (Plucker a) a
--   p23 :: Lens' (Plucker a) a
--   p31 :: Lens' (Plucker a) a
--   p12 :: Lens' (Plucker a) a
--   
p23 :: Lens' (Plucker a) a -- | These elements form an alternate basis for the Plücker space, or the -- Grassmanian manifold Gr(2,V4). -- --
--   p10 :: Num a => Lens' (Plucker a) a
--   p20 :: Num a => Lens' (Plucker a) a
--   p30 :: Num a => Lens' (Plucker a) a
--   p32 :: Num a => Lens' (Plucker a) a
--   p13 :: Num a => Lens' (Plucker a) a
--   p21 :: Num a => Lens' (Plucker a) a
--   
p30 :: (Functor f, Num a) => (a -> f a) -> Plucker a -> f (Plucker a) -- | These elements form a basis for the Plücker space, or the Grassmanian -- manifold Gr(2,V4). -- --
--   p01 :: Lens' (Plucker a) a
--   p02 :: Lens' (Plucker a) a
--   p03 :: Lens' (Plucker a) a
--   p23 :: Lens' (Plucker a) a
--   p31 :: Lens' (Plucker a) a
--   p12 :: Lens' (Plucker a) a
--   
p31 :: Lens' (Plucker a) a -- | These elements form an alternate basis for the Plücker space, or the -- Grassmanian manifold Gr(2,V4). -- --
--   p10 :: Num a => Lens' (Plucker a) a
--   p20 :: Num a => Lens' (Plucker a) a
--   p30 :: Num a => Lens' (Plucker a) a
--   p32 :: Num a => Lens' (Plucker a) a
--   p13 :: Num a => Lens' (Plucker a) a
--   p21 :: Num a => Lens' (Plucker a) a
--   
p32 :: (Functor f, Num a) => (a -> f a) -> Plucker a -> f (Plucker a) e01 :: E Plucker e02 :: E Plucker e03 :: E Plucker e12 :: E Plucker e31 :: E Plucker e23 :: E Plucker instance Eq a => Eq (Plucker a) instance Ord a => Ord (Plucker a) instance Show a => Show (Plucker a) instance Read a => Read (Plucker a) instance Generic (Plucker a) instance Generic1 Plucker instance Eq LinePass instance Show LinePass instance Generic LinePass instance Datatype D1Plucker instance Constructor C1_0Plucker instance Datatype D1LinePass instance Constructor C1_0LinePass instance Constructor C1_1LinePass instance Constructor C1_2LinePass instance MonadFix Plucker instance MonadZip Plucker instance Unbox a => Vector Vector (Plucker a) instance Unbox a => MVector MVector (Plucker a) instance Unbox a => Unbox (Plucker a) instance Eq (Coincides a) instance Each (Plucker a) (Plucker b) a b instance Ixed (Plucker a) instance TraversableWithIndex (E Plucker) Plucker instance FoldableWithIndex (E Plucker) Plucker instance FunctorWithIndex (E Plucker) Plucker instance Epsilon a => Epsilon (Plucker a) instance Metric Plucker instance Storable a => Storable (Plucker a) instance Hashable a => Hashable (Plucker a) instance Fractional a => Fractional (Plucker a) instance Num a => Num (Plucker a) instance Ix a => Ix (Plucker a) instance Traversable1 Plucker instance Foldable1 Plucker instance Traversable Plucker instance Foldable Plucker instance Representable Plucker instance Distributive Plucker instance Monad Plucker instance Bind Plucker instance Additive Plucker instance Applicative Plucker instance Apply Plucker instance Functor Plucker -- | n-D Vectors module Linear.V data V n a int :: Int -> TypeQ dim :: Dim n => V n a -> Int class Dim n reflectDim :: Dim n => p n -> Int reifyDim :: Int -> (forall (n :: *). Dim n => Proxy n -> r) -> r reifyVector :: Vector a -> (forall (n :: *). Dim n => V n a -> r) -> r fromVector :: Dim n => Vector a -> Maybe (V n a) instance Eq a => Eq (V n a) instance Ord a => Ord (V n a) instance Show a => Show (V n a) instance Read a => Read (V n a) instance Generic (V n a) instance Generic1 (V n) instance Datatype D1V instance Constructor C1_0V instance Selector S1_0_0V instance Each (V n a) (V n b) a b instance Dim n => MonadFix (V n) instance Dim n => MonadZip (V n) instance Ixed (V n a) instance Dim n => Representable (V n) instance Dim n => Metric (V n) instance (Dim n, Epsilon a) => Epsilon (V n a) instance (Dim n, Storable a) => Storable (V n a) instance Dim n => Distributive (V n) instance (Dim n, Fractional a) => Fractional (V n a) instance (Dim n, Num a) => Num (V n a) instance Dim n => Additive (V n) instance Dim n => Monad (V n) instance Bind (V n) instance Dim n => Applicative (V n) instance Apply (V n) instance Traversable (V n) instance Foldable (V n) instance Functor (V n) instance Dim n => Dim (V n a) instance Reifies s Int => Dim (ReifiedDim s) instance KnownNat n => Dim n -- | Involutive rings module Linear.Conjugate -- | An involutive ring class Num a => Conjugate a where conjugate = id conjugate :: Conjugate a => a -> a -- | Requires and provides a default definition such that -- --
--   conjugate = id
--   
class Conjugate a => TrivialConjugate a instance TrivialConjugate CDouble instance TrivialConjugate CFloat instance TrivialConjugate Float instance TrivialConjugate Double instance TrivialConjugate Word8 instance TrivialConjugate Word16 instance TrivialConjugate Word32 instance TrivialConjugate Word64 instance TrivialConjugate Word instance TrivialConjugate Int8 instance TrivialConjugate Int16 instance TrivialConjugate Int32 instance TrivialConjugate Int64 instance TrivialConjugate Int instance TrivialConjugate Integer instance (Conjugate a, RealFloat a) => Conjugate (Complex a) instance Conjugate CDouble instance Conjugate CFloat instance Conjugate Float instance Conjugate Double instance Conjugate Word8 instance Conjugate Word16 instance Conjugate Word32 instance Conjugate Word64 instance Conjugate Word instance Conjugate Int8 instance Conjugate Int16 instance Conjugate Int32 instance Conjugate Int64 instance Conjugate Int instance Conjugate Integer -- | Quaternions module Linear.Quaternion -- | Quaternions data Quaternion a Quaternion :: !a -> {-# UNPACK #-} !(V3 a) -> Quaternion a -- | A vector space that includes the basis elements _e and -- _i class Complicated t _e, _i :: Complicated t => Lens' (t a) a -- | A vector space that includes the basis elements _e, _i, -- _j and _k class Complicated t => Hamiltonian t _j, _k :: Hamiltonian t => Lens' (t a) a _ijk :: Hamiltonian t => Lens' (t a) (V3 a) ee :: Complicated t => E t ei :: Complicated t => E t ej :: Hamiltonian t => E t ek :: Hamiltonian t => E t -- | Spherical linear interpolation between two quaternions. slerp :: RealFloat a => Quaternion a -> Quaternion a -> a -> Quaternion a -- | asin with a specified branch cut. asinq :: RealFloat a => Quaternion a -> Quaternion a -> Quaternion a -- | acos with a specified branch cut. acosq :: RealFloat a => Quaternion a -> Quaternion a -> Quaternion a -- | atan with a specified branch cut. atanq :: RealFloat a => Quaternion a -> Quaternion a -> Quaternion a -- | asinh with a specified branch cut. asinhq :: RealFloat a => Quaternion a -> Quaternion a -> Quaternion a -- | acosh with a specified branch cut. acoshq :: RealFloat a => Quaternion a -> Quaternion a -> Quaternion a -- | atanh with a specified branch cut. atanhq :: RealFloat a => Quaternion a -> Quaternion a -> Quaternion a -- | norm of the imaginary component absi :: Floating a => Quaternion a -> a -- | raise a Quaternion to a scalar power pow :: RealFloat a => Quaternion a -> a -> Quaternion a -- | Apply a rotation to a vector. rotate :: (Conjugate a, RealFloat a) => Quaternion a -> V3 a -> V3 a -- | axisAngle axis theta builds a Quaternion -- representing a rotation of theta radians about axis. axisAngle :: (Epsilon a, Floating a) => V3 a -> a -> Quaternion a instance Typeable Quaternion instance Eq a => Eq (Quaternion a) instance Ord a => Ord (Quaternion a) instance Read a => Read (Quaternion a) instance Show a => Show (Quaternion a) instance Data a => Data (Quaternion a) instance Generic (Quaternion a) instance Generic1 Quaternion instance Datatype D1Quaternion instance Constructor C1_0Quaternion instance MonadFix Quaternion instance MonadZip Quaternion instance Unbox a => Vector Vector (Quaternion a) instance Unbox a => MVector MVector (Quaternion a) instance Unbox a => Unbox (Quaternion a) instance (RealFloat a, Epsilon a) => Epsilon (Quaternion a) instance RealFloat a => Floating (Quaternion a) instance (Conjugate a, RealFloat a) => Conjugate (Quaternion a) instance Distributive Quaternion instance Hamiltonian Quaternion instance Complicated Quaternion instance Complicated Complex instance Metric Quaternion instance RealFloat a => Fractional (Quaternion a) instance Hashable a => Hashable (Quaternion a) instance RealFloat a => Num (Quaternion a) instance Storable a => Storable (Quaternion a) instance Traversable Quaternion instance Foldable Quaternion instance Each (Quaternion a) (Quaternion b) a b instance Ixed (Quaternion a) instance TraversableWithIndex (E Quaternion) Quaternion instance FoldableWithIndex (E Quaternion) Quaternion instance FunctorWithIndex (E Quaternion) Quaternion instance Representable Quaternion instance Ix a => Ix (Quaternion a) instance Monad Quaternion instance Bind Quaternion instance Additive Quaternion instance Applicative Quaternion instance Apply Quaternion instance Functor Quaternion -- | Simple matrix operation for low-dimensional primitives. module Linear.Trace class Functor m => Trace m where trace = sum . diagonal diagonal = join trace :: (Trace m, Num a) => m (m a) -> a diagonal :: Trace m => m (m a) -> m a instance (Distributive g, Trace g, Trace f) => Trace (Compose g f) instance (Trace f, Trace g) => Trace (Product f g) instance Trace Complex instance Trace Quaternion instance Trace Plucker instance Trace V4 instance Trace V3 instance Trace V2 instance Trace V0 instance Dim n => Trace (V n) instance (Eq k, Hashable k) => Trace (HashMap k) instance Ord k => Trace (Map k) instance Trace IntMap -- | Simple matrix operation for low-dimensional primitives. module Linear.Matrix -- | Matrix product. This can compute any combination of sparse and dense -- multiplication. -- --
--   >>> V2 (V3 1 2 3) (V3 4 5 6) !*! V3 (V2 1 2) (V2 3 4) (V2 4 5)
--   V2 (V2 19 25) (V2 43 58)
--   
-- --
--   >>> V2 (fromList [(1,2)]) (fromList [(2,3)]) !*! fromList [(1,V3 0 0 1), (2, V3 0 0 5)]
--   V2 (V3 0 0 2) (V3 0 0 15)
--   
(!*!) :: (Functor m, Foldable t, Additive t, Additive n, Num a) => m (t a) -> t (n a) -> m (n a) -- | Entry-wise matrix addition. -- --
--   >>> V2 (V3 1 2 3) (V3 4 5 6) !+! V2 (V3 7 8 9) (V3 1 2 3)
--   V2 (V3 8 10 12) (V3 5 7 9)
--   
(!+!) :: (Additive m, Additive n, Num a) => m (n a) -> m (n a) -> m (n a) -- | Entry-wise matrix subtraction. -- --
--   >>> V2 (V3 1 2 3) (V3 4 5 6) !-! V2 (V3 7 8 9) (V3 1 2 3)
--   V2 (V3 (-6) (-6) (-6)) (V3 3 3 3)
--   
(!-!) :: (Additive m, Additive n, Num a) => m (n a) -> m (n a) -> m (n a) -- | Matrix * column vector -- --
--   >>> V2 (V3 1 2 3) (V3 4 5 6) !* V3 7 8 9
--   V2 50 122
--   
(!*) :: (Functor m, Foldable r, Additive r, Num a) => m (r a) -> r a -> m a -- | Row vector * matrix -- --
--   >>> V2 1 2 *! V2 (V3 3 4 5) (V3 6 7 8)
--   V3 15 18 21
--   
(*!) :: (Num a, Foldable t, Additive f, Additive t) => t a -> t (f a) -> f a -- | Matrix-scalar product -- --
--   >>> V2 (V2 1 2) (V2 3 4) !!* 5
--   V2 (V2 5 10) (V2 15 20)
--   
(!!*) :: (Functor m, Functor r, Num a) => m (r a) -> a -> m (r a) -- | Scalar-matrix product -- --
--   >>> 5 *!! V2 (V2 1 2) (V2 3 4)
--   V2 (V2 5 10) (V2 15 20)
--   
(*!!) :: (Functor m, Functor r, Num a) => a -> m (r a) -> m (r a) -- | This is a generalization of inside to work over any -- corepresentable Functor. -- --
--   column :: Representable f => Lens s t a b -> Lens (f s) (f t) (f a) (f b)
--   
-- -- In practice it is used to access a column of a matrix. -- --
--   >>> V2 (V3 1 2 3) (V3 4 5 6) ^._x
--   V3 1 2 3
--   
-- --
--   >>> V2 (V3 1 2 3) (V3 4 5 6) ^.column _x
--   V2 1 4
--   
column :: Representable f => LensLike (Context a b) s t a b -> Lens (f s) (f t) (f a) (f b) -- | Hermitian conjugate or conjugate transpose -- --
--   >>> adjoint (V2 (V2 (1 :+ 2) (3 :+ 4)) (V2 (5 :+ 6) (7 :+ 8)))
--   V2 (V2 (1.0 :+ (-2.0)) (5.0 :+ (-6.0))) (V2 (3.0 :+ (-4.0)) (7.0 :+ (-8.0)))
--   
adjoint :: (Functor m, Distributive n, Conjugate a) => m (n a) -> n (m a) -- | A 2x2 matrix with row-major representation type M22 a = V2 (V2 a) -- | A 3x3 matrix with row-major representation type M33 a = V3 (V3 a) -- | A 4x4 matrix with row-major representation type M44 a = V4 (V4 a) -- | A 4x3 matrix with row-major representation type M43 a = V4 (V3 a) -- | Convert a 3x3 matrix to a 4x4 matrix extending it with 0's in the new -- row and column. m33_to_m44 :: Num a => M33 a -> M44 a -- | Convert from a 4x3 matrix to a 4x4 matrix, extending it with the [ -- 0 0 0 1 ] column vector m43_to_m44 :: Num a => M43 a -> M44 a -- | 2x2 matrix determinant. -- --
--   >>> det22 (V2 (V2 a b) (V2 c d))
--   a * d - b * c
--   
det22 :: Num a => M22 a -> a -- | 3x3 matrix determinant. -- --
--   >>> det33 (V3 (V3 a b c) (V3 d e f) (V3 g h i))
--   a * (e * i - f * h) - d * (b * i - c * h) + g * (b * f - c * e)
--   
det33 :: Num a => M33 a -> a -- | 2x2 matrix inverse. -- --
--   >>> inv22 $ V2 (V2 1 2) (V2 3 4)
--   Just (V2 (V2 (-2.0) 1.0) (V2 1.5 (-0.5)))
--   
inv22 :: (Epsilon a, Floating a) => M22 a -> Maybe (M22 a) -- | 3x3 matrix inverse. -- --
--   >>> inv33 $ V3 (V3 1 2 4) (V3 4 2 2) (V3 1 1 1)
--   Just (V3 (V3 0.0 0.5 (-1.0)) (V3 (-0.5) (-0.75) 3.5) (V3 0.5 0.25 (-1.5)))
--   
inv33 :: (Epsilon a, Floating a) => M33 a -> Maybe (M33 a) -- | 2x2 identity matrix. -- --
--   >>> eye2
--   V2 (V2 1 0) (V2 0 1)
--   
eye2 :: Num a => M22 a -- | 3x3 identity matrix. -- --
--   >>> eye3
--   V3 (V3 1 0 0) (V3 0 1 0) (V3 0 0 1)
--   
eye3 :: Num a => M33 a -- | 4x4 identity matrix. -- --
--   >>> eye4
--   V4 (V4 1 0 0 0) (V4 0 1 0 0) (V4 0 0 1 0) (V4 0 0 0 1)
--   
eye4 :: Num a => M44 a class Functor m => Trace m where trace = sum . diagonal diagonal = join trace :: (Trace m, Num a) => m (m a) -> a diagonal :: Trace m => m (m a) -> m a -- | Extract the translation vector (first three entries of the last -- column) from a 3x4 or 4x4 matrix. translation :: (Representable t, R3 t, R4 v) => Lens' (t (v a)) (V3 a) -- | Build a rotation matrix from a unit Quaternion. fromQuaternion :: Num a => Quaternion a -> M33 a -- | Build a transformation matrix from a rotation expressed as a -- Quaternion and a translation vector. mkTransformation :: Num a => Quaternion a -> V3 a -> M44 a -- | Build a transformation matrix from a rotation matrix and a translation -- vector. mkTransformationMat :: Num a => M33 a -> V3 a -> M44 a -- | Operations on affine spaces. module Linear.Affine -- | 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@
--   
class Additive (Diff p) => Affine p where type family Diff p :: * -> * p .-^ v = p .+^ negated v (.-.) :: (Affine p, Num a) => p a -> p a -> Diff p a (.+^) :: (Affine p, Num a) => p a -> Diff p a -> p a (.-^) :: (Affine p, Num a) => p a -> Diff p a -> p a -- | Compute the quadrance of the difference (the square of the distance) qdA :: (Affine p, Foldable (Diff p), Num a) => p a -> p a -> a -- | Distance between two points in an affine space distanceA :: (Floating a, Foldable (Diff p), Affine p) => p a -> p a -> a -- | A handy wrapper to help distinguish points from vectors at the type -- level newtype Point f a P :: (f a) -> Point f a lensP :: Lens' (Point g a) (g a) -- | Vector spaces have origins. origin :: (Additive f, Num a) => Point f a instance Eq (f a) => Eq (Point f a) instance Ord (f a) => Ord (Point f a) instance Show (f a) => Show (Point f a) instance Read (f a) => Read (Point f a) instance Monad f => Monad (Point f) instance Functor f => Functor (Point f) instance Applicative f => Applicative (Point f) instance Foldable f => Foldable (Point f) instance Traversable f => Traversable (Point f) instance Apply f => Apply (Point f) instance Additive f => Additive (Point f) instance Metric f => Metric (Point f) instance Fractional (f a) => Fractional (Point f a) instance Num (f a) => Num (Point f a) instance Ix (f a) => Ix (Point f a) instance Storable (f a) => Storable (Point f a) instance Epsilon (f a) => Epsilon (Point f a) instance Generic (Point f a) instance Generic1 (Point f) instance Datatype D1Point instance Constructor C1_0Point instance Additive f => Affine (Point f) instance R4 f => R4 (Point f) instance R3 f => R3 (Point f) instance R2 f => R2 (Point f) instance R1 f => R1 (Point f) instance Representable f => Representable (Point f) instance Distributive f => Distributive (Point f) instance Bind f => Bind (Point f) instance Dim n => Affine (V n) instance (Eq k, Hashable k) => Affine (HashMap k) instance Ord k => Affine (Map k) instance Affine ((->) b) instance Affine Quaternion instance Affine Plucker instance Affine V4 instance Affine V3 instance Affine V2 instance Affine V1 instance Affine V0 instance Affine Vector instance Affine Identity instance Affine IntMap instance Affine Maybe instance Affine ZipList instance Affine Complex instance Affine [] -- | Serialization of statically-sized types with the Data.Binary -- library. module Linear.Binary -- | Serialize a linear type. putLinear :: (Binary a, Foldable t) => t a -> Put -- | Deserialize a linear type. getLinear :: (Binary a, Applicative t, Traversable t) => Get (t a) module Linear.Algebra -- | An associative unital algebra over a ring class Num r => Algebra r m mult :: Algebra r m => (m -> m -> r) -> m -> r unital :: Algebra r m => r -> m -> r -- | A coassociative counital coalgebra over a ring class Num r => Coalgebra r m comult :: Coalgebra r m => (m -> r) -> m -> m -> r counital :: Coalgebra r m => (m -> r) -> r multRep :: (Representable f, Algebra r (Rep f)) => f (f r) -> f r unitalRep :: (Representable f, Algebra r (Rep f)) => r -> f r comultRep :: (Representable f, Coalgebra r (Rep f)) => f r -> f (f r) counitalRep :: (Representable f, Coalgebra r (Rep f)) => f r -> r instance (Coalgebra r m, Coalgebra r n) => Coalgebra r (m, n) instance (Num r, TrivialConjugate r) => Coalgebra r (E Quaternion) instance Num r => Coalgebra r (E Complex) instance Num r => Coalgebra r (E V4) instance Num r => Coalgebra r (E V3) instance Num r => Coalgebra r (E V2) instance Num r => Coalgebra r (E V1) instance Num r => Coalgebra r (E V0) instance Num r => Coalgebra r () instance Num r => Coalgebra r Void instance (Num r, TrivialConjugate r) => Algebra r (E Quaternion) instance Num r => Algebra r (E Complex) instance (Algebra r a, Algebra r b) => Algebra r (a, b) instance Num r => Algebra r () instance Num r => Algebra r (E V1) instance Num r => Algebra r (E V0) instance Num r => Algebra r Void module Linear.Covector -- | Linear functionals from elements of an (infinite) free module to a -- scalar newtype Covector r a Covector :: ((a -> r) -> r) -> Covector r a runCovector :: Covector r a -> (a -> r) -> r ($*) :: Representable f => Covector r (Rep f) -> f r -> r instance Coalgebra r m => Num (Covector r m) instance Num r => MonadPlus (Covector r) instance Num r => Alternative (Covector r) instance Num r => Plus (Covector r) instance Num r => Alt (Covector r) instance Monad (Covector r) instance Bind (Covector r) instance Applicative (Covector r) instance Apply (Covector r) instance Functor (Covector r) -- | This module simply re-exports everything from the various modules that -- make up the linear package. module Linear