linear-1.20.9: Linear Algebra

Copyright(C) 2012-2015 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell98

Linear.Vector

Description

Operations on free vector spaces.

Synopsis

Documentation

class Functor f => Additive f where Source #

A vector is an additive group with additional structure.

Minimal complete definition

Nothing

Methods

zero :: Num a => f a Source #

The zero vector

zero :: (GAdditive (Rep1 f), Generic1 f, Num a) => f a Source #

The zero vector

(^+^) :: Num a => f a -> f a -> f a infixl 6 Source #

Compute the sum of two vectors

>>> V2 1 2 ^+^ V2 3 4
V2 4 6

(^-^) :: Num a => f a -> f a -> f a infixl 6 Source #

Compute the difference between two vectors

>>> V2 4 5 ^-^ V2 3 1
V2 1 4

lerp :: Num a => a -> f a -> f a -> f a Source #

Linearly interpolate between two vectors.

liftU2 :: (a -> a -> a) -> f a -> f a -> f a Source #

Apply a function to merge the 'non-zero' components of two vectors, unioning the rest of the values.

  • For a dense vector this is equivalent to liftA2.
  • For a sparse vector this is equivalent to unionWith.

liftU2 :: Applicative f => (a -> a -> a) -> f a -> f a -> f a Source #

Apply a function to merge the 'non-zero' components of two vectors, unioning the rest of the values.

  • For a dense vector this is equivalent to liftA2.
  • For a sparse vector this is equivalent to unionWith.

liftI2 :: (a -> b -> c) -> f a -> f b -> f c Source #

Apply a function to the components of two vectors.

liftI2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c Source #

Apply a function to the components of two vectors.

Instances
Additive [] Source # 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => [a] Source #

(^+^) :: Num a => [a] -> [a] -> [a] Source #

(^-^) :: Num a => [a] -> [a] -> [a] Source #

lerp :: Num a => a -> [a] -> [a] -> [a] Source #

liftU2 :: (a -> a -> a) -> [a] -> [a] -> [a] Source #

liftI2 :: (a -> b -> c) -> [a] -> [b] -> [c] Source #

Additive Maybe Source # 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => Maybe a Source #

(^+^) :: Num a => Maybe a -> Maybe a -> Maybe a Source #

(^-^) :: Num a => Maybe a -> Maybe a -> Maybe a Source #

lerp :: Num a => a -> Maybe a -> Maybe a -> Maybe a Source #

liftU2 :: (a -> a -> a) -> Maybe a -> Maybe a -> Maybe a Source #

liftI2 :: (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c Source #

Additive Complex Source # 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => Complex a Source #

(^+^) :: Num a => Complex a -> Complex a -> Complex a Source #

(^-^) :: Num a => Complex a -> Complex a -> Complex a Source #

lerp :: Num a => a -> Complex a -> Complex a -> Complex a Source #

liftU2 :: (a -> a -> a) -> Complex a -> Complex a -> Complex a Source #

liftI2 :: (a -> b -> c) -> Complex a -> Complex b -> Complex c Source #

Additive ZipList Source # 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => ZipList a Source #

(^+^) :: Num a => ZipList a -> ZipList a -> ZipList a Source #

(^-^) :: Num a => ZipList a -> ZipList a -> ZipList a Source #

lerp :: Num a => a -> ZipList a -> ZipList a -> ZipList a Source #

liftU2 :: (a -> a -> a) -> ZipList a -> ZipList a -> ZipList a Source #

liftI2 :: (a -> b -> c) -> ZipList a -> ZipList b -> ZipList c Source #

Additive Identity Source # 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => Identity a Source #

(^+^) :: Num a => Identity a -> Identity a -> Identity a Source #

(^-^) :: Num a => Identity a -> Identity a -> Identity a Source #

lerp :: Num a => a -> Identity a -> Identity a -> Identity a Source #

liftU2 :: (a -> a -> a) -> Identity a -> Identity a -> Identity a Source #

liftI2 :: (a -> b -> c) -> Identity a -> Identity b -> Identity c Source #

Additive IntMap Source # 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => IntMap a Source #

(^+^) :: Num a => IntMap a -> IntMap a -> IntMap a Source #

(^-^) :: Num a => IntMap a -> IntMap a -> IntMap a Source #

lerp :: Num a => a -> IntMap a -> IntMap a -> IntMap a Source #

liftU2 :: (a -> a -> a) -> IntMap a -> IntMap a -> IntMap a Source #

liftI2 :: (a -> b -> c) -> IntMap a -> IntMap b -> IntMap c Source #

Additive Vector Source # 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => Vector a Source #

(^+^) :: Num a => Vector a -> Vector a -> Vector a Source #

(^-^) :: Num a => Vector a -> Vector a -> Vector a Source #

lerp :: Num a => a -> Vector a -> Vector a -> Vector a Source #

liftU2 :: (a -> a -> a) -> Vector a -> Vector a -> Vector a Source #

liftI2 :: (a -> b -> c) -> Vector a -> Vector b -> Vector c Source #

Additive V1 Source # 
Instance details

Defined in Linear.V1

Methods

zero :: Num a => V1 a Source #

(^+^) :: Num a => V1 a -> V1 a -> V1 a Source #

(^-^) :: Num a => V1 a -> V1 a -> V1 a Source #

lerp :: Num a => a -> V1 a -> V1 a -> V1 a Source #

liftU2 :: (a -> a -> a) -> V1 a -> V1 a -> V1 a Source #

liftI2 :: (a -> b -> c) -> V1 a -> V1 b -> V1 c Source #

Additive V2 Source # 
Instance details

Defined in Linear.V2

Methods

zero :: Num a => V2 a Source #

(^+^) :: Num a => V2 a -> V2 a -> V2 a Source #

(^-^) :: Num a => V2 a -> V2 a -> V2 a Source #

lerp :: Num a => a -> V2 a -> V2 a -> V2 a Source #

liftU2 :: (a -> a -> a) -> V2 a -> V2 a -> V2 a Source #

liftI2 :: (a -> b -> c) -> V2 a -> V2 b -> V2 c Source #

Additive V3 Source # 
Instance details

Defined in Linear.V3

Methods

zero :: Num a => V3 a Source #

(^+^) :: Num a => V3 a -> V3 a -> V3 a Source #

(^-^) :: Num a => V3 a -> V3 a -> V3 a Source #

lerp :: Num a => a -> V3 a -> V3 a -> V3 a Source #

liftU2 :: (a -> a -> a) -> V3 a -> V3 a -> V3 a Source #

liftI2 :: (a -> b -> c) -> V3 a -> V3 b -> V3 c Source #

Additive V4 Source # 
Instance details

Defined in Linear.V4

Methods

zero :: Num a => V4 a Source #

(^+^) :: Num a => V4 a -> V4 a -> V4 a Source #

(^-^) :: Num a => V4 a -> V4 a -> V4 a Source #

lerp :: Num a => a -> V4 a -> V4 a -> V4 a Source #

liftU2 :: (a -> a -> a) -> V4 a -> V4 a -> V4 a Source #

liftI2 :: (a -> b -> c) -> V4 a -> V4 b -> V4 c Source #

Additive V0 Source # 
Instance details

Defined in Linear.V0

Methods

zero :: Num a => V0 a Source #

(^+^) :: Num a => V0 a -> V0 a -> V0 a Source #

(^-^) :: Num a => V0 a -> V0 a -> V0 a Source #

lerp :: Num a => a -> V0 a -> V0 a -> V0 a Source #

liftU2 :: (a -> a -> a) -> V0 a -> V0 a -> V0 a Source #

liftI2 :: (a -> b -> c) -> V0 a -> V0 b -> V0 c Source #

Additive Quaternion Source # 
Instance details

Defined in Linear.Quaternion

Methods

zero :: Num a => Quaternion a Source #

(^+^) :: Num a => Quaternion a -> Quaternion a -> Quaternion a Source #

(^-^) :: Num a => Quaternion a -> Quaternion a -> Quaternion a Source #

lerp :: Num a => a -> Quaternion a -> Quaternion a -> Quaternion a Source #

liftU2 :: (a -> a -> a) -> Quaternion a -> Quaternion a -> Quaternion a Source #

liftI2 :: (a -> b -> c) -> Quaternion a -> Quaternion b -> Quaternion c Source #

Additive Plucker Source # 
Instance details

Defined in Linear.Plucker

Methods

zero :: Num a => Plucker a Source #

(^+^) :: Num a => Plucker a -> Plucker a -> Plucker a Source #

(^-^) :: Num a => Plucker a -> Plucker a -> Plucker a Source #

lerp :: Num a => a -> Plucker a -> Plucker a -> Plucker a Source #

liftU2 :: (a -> a -> a) -> Plucker a -> Plucker a -> Plucker a Source #

liftI2 :: (a -> b -> c) -> Plucker a -> Plucker b -> Plucker c Source #

Ord k => Additive (Map k) Source # 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => Map k a Source #

(^+^) :: Num a => Map k a -> Map k a -> Map k a Source #

(^-^) :: Num a => Map k a -> Map k a -> Map k a Source #

lerp :: Num a => a -> Map k a -> Map k a -> Map k a Source #

liftU2 :: (a -> a -> a) -> Map k a -> Map k a -> Map k a Source #

liftI2 :: (a -> b -> c) -> Map k a -> Map k b -> Map k c Source #

(Eq k, Hashable k) => Additive (HashMap k) Source # 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => HashMap k a Source #

(^+^) :: Num a => HashMap k a -> HashMap k a -> HashMap k a Source #

(^-^) :: Num a => HashMap k a -> HashMap k a -> HashMap k a Source #

lerp :: Num a => a -> HashMap k a -> HashMap k a -> HashMap k a Source #

liftU2 :: (a -> a -> a) -> HashMap k a -> HashMap k a -> HashMap k a Source #

liftI2 :: (a -> b -> c) -> HashMap k a -> HashMap k b -> HashMap k c Source #

Additive f => Additive (Point f) Source # 
Instance details

Defined in Linear.Affine

Methods

zero :: Num a => Point f a Source #

(^+^) :: Num a => Point f a -> Point f a -> Point f a Source #

(^-^) :: Num a => Point f a -> Point f a -> Point f a Source #

lerp :: Num a => a -> Point f a -> Point f a -> Point f a Source #

liftU2 :: (a -> a -> a) -> Point f a -> Point f a -> Point f a Source #

liftI2 :: (a -> b -> c) -> Point f a -> Point f b -> Point f c Source #

Dim n => Additive (V n) Source # 
Instance details

Defined in Linear.V

Methods

zero :: Num a => V n a Source #

(^+^) :: Num a => V n a -> V n a -> V n a Source #

(^-^) :: Num a => V n a -> V n a -> V n a Source #

lerp :: Num a => a -> V n a -> V n a -> V n a Source #

liftU2 :: (a -> a -> a) -> V n a -> V n a -> V n a Source #

liftI2 :: (a -> b -> c) -> V n a -> V n b -> V n c Source #

Additive ((->) b :: Type -> Type) Source # 
Instance details

Defined in Linear.Vector

Methods

zero :: Num a => b -> a Source #

(^+^) :: Num a => (b -> a) -> (b -> a) -> b -> a Source #

(^-^) :: Num a => (b -> a) -> (b -> a) -> b -> a Source #

lerp :: Num a => a -> (b -> a) -> (b -> a) -> b -> a Source #

liftU2 :: (a -> a -> a) -> (b -> a) -> (b -> a) -> b -> a Source #

liftI2 :: (a -> b0 -> c) -> (b -> a) -> (b -> b0) -> b -> c Source #

newtype E t Source #

Basis element

Constructors

E 

Fields

Instances
(Num r, TrivialConjugate r) => Coalgebra r (E Quaternion) Source # 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E Quaternion -> r) -> E Quaternion -> E Quaternion -> r Source #

counital :: (E Quaternion -> r) -> r Source #

Num r => Coalgebra r (E Complex) Source # 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E Complex -> r) -> E Complex -> E Complex -> r Source #

counital :: (E Complex -> r) -> r Source #

Num r => Coalgebra r (E V4) Source # 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V4 -> r) -> E V4 -> E V4 -> r Source #

counital :: (E V4 -> r) -> r Source #

Num r => Coalgebra r (E V3) Source # 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V3 -> r) -> E V3 -> E V3 -> r Source #

counital :: (E V3 -> r) -> r Source #

Num r => Coalgebra r (E V2) Source # 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V2 -> r) -> E V2 -> E V2 -> r Source #

counital :: (E V2 -> r) -> r Source #

Num r => Coalgebra r (E V1) Source # 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V1 -> r) -> E V1 -> E V1 -> r Source #

counital :: (E V1 -> r) -> r Source #

Num r => Coalgebra r (E V0) Source # 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V0 -> r) -> E V0 -> E V0 -> r Source #

counital :: (E V0 -> r) -> r Source #

(Num r, TrivialConjugate r) => Algebra r (E Quaternion) Source # 
Instance details

Defined in Linear.Algebra

Methods

mult :: (E Quaternion -> E Quaternion -> r) -> E Quaternion -> r Source #

unital :: r -> E Quaternion -> r Source #

Num r => Algebra r (E Complex) Source # 
Instance details

Defined in Linear.Algebra

Methods

mult :: (E Complex -> E Complex -> r) -> E Complex -> r Source #

unital :: r -> E Complex -> r Source #

Num r => Algebra r (E V1) Source # 
Instance details

Defined in Linear.Algebra

Methods

mult :: (E V1 -> E V1 -> r) -> E V1 -> r Source #

unital :: r -> E V1 -> r Source #

Num r => Algebra r (E V0) Source # 
Instance details

Defined in Linear.Algebra

Methods

mult :: (E V0 -> E V0 -> r) -> E V0 -> r Source #

unital :: r -> E V0 -> r Source #

FunctorWithIndex (E V1) V1 Source # 
Instance details

Defined in Linear.V1

Methods

imap :: (E V1 -> a -> b) -> V1 a -> V1 b #

imapped :: IndexedSetter (E V1) (V1 a) (V1 b) a b #

FunctorWithIndex (E V2) V2 Source # 
Instance details

Defined in Linear.V2

Methods

imap :: (E V2 -> a -> b) -> V2 a -> V2 b #

imapped :: IndexedSetter (E V2) (V2 a) (V2 b) a b #

FunctorWithIndex (E V3) V3 Source # 
Instance details

Defined in Linear.V3

Methods

imap :: (E V3 -> a -> b) -> V3 a -> V3 b #

imapped :: IndexedSetter (E V3) (V3 a) (V3 b) a b #

FunctorWithIndex (E V4) V4 Source # 
Instance details

Defined in Linear.V4

Methods

imap :: (E V4 -> a -> b) -> V4 a -> V4 b #

imapped :: IndexedSetter (E V4) (V4 a) (V4 b) a b #

FunctorWithIndex (E V0) V0 Source # 
Instance details

Defined in Linear.V0

Methods

imap :: (E V0 -> a -> b) -> V0 a -> V0 b #

imapped :: IndexedSetter (E V0) (V0 a) (V0 b) a b #

FunctorWithIndex (E Quaternion) Quaternion Source # 
Instance details

Defined in Linear.Quaternion

Methods

imap :: (E Quaternion -> a -> b) -> Quaternion a -> Quaternion b #

imapped :: IndexedSetter (E Quaternion) (Quaternion a) (Quaternion b) a b #

FunctorWithIndex (E Plucker) Plucker Source # 
Instance details

Defined in Linear.Plucker

Methods

imap :: (E Plucker -> a -> b) -> Plucker a -> Plucker b #

imapped :: IndexedSetter (E Plucker) (Plucker a) (Plucker b) a b #

FoldableWithIndex (E V1) V1 Source # 
Instance details

Defined in Linear.V1

Methods

ifoldMap :: Monoid m => (E V1 -> a -> m) -> V1 a -> m #

ifolded :: IndexedFold (E V1) (V1 a) a #

ifoldr :: (E V1 -> a -> b -> b) -> b -> V1 a -> b #

ifoldl :: (E V1 -> b -> a -> b) -> b -> V1 a -> b #

ifoldr' :: (E V1 -> a -> b -> b) -> b -> V1 a -> b #

ifoldl' :: (E V1 -> b -> a -> b) -> b -> V1 a -> b #

FoldableWithIndex (E V2) V2 Source # 
Instance details

Defined in Linear.V2

Methods

ifoldMap :: Monoid m => (E V2 -> a -> m) -> V2 a -> m #

ifolded :: IndexedFold (E V2) (V2 a) a #

ifoldr :: (E V2 -> a -> b -> b) -> b -> V2 a -> b #

ifoldl :: (E V2 -> b -> a -> b) -> b -> V2 a -> b #

ifoldr' :: (E V2 -> a -> b -> b) -> b -> V2 a -> b #

ifoldl' :: (E V2 -> b -> a -> b) -> b -> V2 a -> b #

FoldableWithIndex (E V3) V3 Source # 
Instance details

Defined in Linear.V3

Methods

ifoldMap :: Monoid m => (E V3 -> a -> m) -> V3 a -> m #

ifolded :: IndexedFold (E V3) (V3 a) a #

ifoldr :: (E V3 -> a -> b -> b) -> b -> V3 a -> b #

ifoldl :: (E V3 -> b -> a -> b) -> b -> V3 a -> b #

ifoldr' :: (E V3 -> a -> b -> b) -> b -> V3 a -> b #

ifoldl' :: (E V3 -> b -> a -> b) -> b -> V3 a -> b #

FoldableWithIndex (E V4) V4 Source # 
Instance details

Defined in Linear.V4

Methods

ifoldMap :: Monoid m => (E V4 -> a -> m) -> V4 a -> m #

ifolded :: IndexedFold (E V4) (V4 a) a #

ifoldr :: (E V4 -> a -> b -> b) -> b -> V4 a -> b #

ifoldl :: (E V4 -> b -> a -> b) -> b -> V4 a -> b #

ifoldr' :: (E V4 -> a -> b -> b) -> b -> V4 a -> b #

ifoldl' :: (E V4 -> b -> a -> b) -> b -> V4 a -> b #

FoldableWithIndex (E V0) V0 Source # 
Instance details

Defined in Linear.V0

Methods

ifoldMap :: Monoid m => (E V0 -> a -> m) -> V0 a -> m #

ifolded :: IndexedFold (E V0) (V0 a) a #

ifoldr :: (E V0 -> a -> b -> b) -> b -> V0 a -> b #

ifoldl :: (E V0 -> b -> a -> b) -> b -> V0 a -> b #

ifoldr' :: (E V0 -> a -> b -> b) -> b -> V0 a -> b #

ifoldl' :: (E V0 -> b -> a -> b) -> b -> V0 a -> b #

FoldableWithIndex (E Quaternion) Quaternion Source # 
Instance details

Defined in Linear.Quaternion

Methods

ifoldMap :: Monoid m => (E Quaternion -> a -> m) -> Quaternion a -> m #

ifolded :: IndexedFold (E Quaternion) (Quaternion a) a #

ifoldr :: (E Quaternion -> a -> b -> b) -> b -> Quaternion a -> b #

ifoldl :: (E Quaternion -> b -> a -> b) -> b -> Quaternion a -> b #

ifoldr' :: (E Quaternion -> a -> b -> b) -> b -> Quaternion a -> b #

ifoldl' :: (E Quaternion -> b -> a -> b) -> b -> Quaternion a -> b #

FoldableWithIndex (E Plucker) Plucker Source # 
Instance details

Defined in Linear.Plucker

Methods

ifoldMap :: Monoid m => (E Plucker -> a -> m) -> Plucker a -> m #

ifolded :: IndexedFold (E Plucker) (Plucker a) a #

ifoldr :: (E Plucker -> a -> b -> b) -> b -> Plucker a -> b #

ifoldl :: (E Plucker -> b -> a -> b) -> b -> Plucker a -> b #

ifoldr' :: (E Plucker -> a -> b -> b) -> b -> Plucker a -> b #

ifoldl' :: (E Plucker -> b -> a -> b) -> b -> Plucker a -> b #

TraversableWithIndex (E V1) V1 Source # 
Instance details

Defined in Linear.V1

Methods

itraverse :: Applicative f => (E V1 -> a -> f b) -> V1 a -> f (V1 b) #

itraversed :: IndexedTraversal (E V1) (V1 a) (V1 b) a b #

TraversableWithIndex (E V2) V2 Source # 
Instance details

Defined in Linear.V2

Methods

itraverse :: Applicative f => (E V2 -> a -> f b) -> V2 a -> f (V2 b) #

itraversed :: IndexedTraversal (E V2) (V2 a) (V2 b) a b #

TraversableWithIndex (E V3) V3 Source # 
Instance details

Defined in Linear.V3

Methods

itraverse :: Applicative f => (E V3 -> a -> f b) -> V3 a -> f (V3 b) #

itraversed :: IndexedTraversal (E V3) (V3 a) (V3 b) a b #

TraversableWithIndex (E V4) V4 Source # 
Instance details

Defined in Linear.V4

Methods

itraverse :: Applicative f => (E V4 -> a -> f b) -> V4 a -> f (V4 b) #

itraversed :: IndexedTraversal (E V4) (V4 a) (V4 b) a b #

TraversableWithIndex (E V0) V0 Source # 
Instance details

Defined in Linear.V0

Methods

itraverse :: Applicative f => (E V0 -> a -> f b) -> V0 a -> f (V0 b) #

itraversed :: IndexedTraversal (E V0) (V0 a) (V0 b) a b #

TraversableWithIndex (E Quaternion) Quaternion Source # 
Instance details

Defined in Linear.Quaternion

TraversableWithIndex (E Plucker) Plucker Source # 
Instance details

Defined in Linear.Plucker

Methods

itraverse :: Applicative f => (E Plucker -> a -> f b) -> Plucker a -> f (Plucker b) #

itraversed :: IndexedTraversal (E Plucker) (Plucker a) (Plucker b) a b #

negated :: (Functor f, Num a) => f a -> f a Source #

Compute the negation of a vector

>>> negated (V2 2 4)
V2 (-2) (-4)

(^*) :: (Functor f, Num a) => f a -> a -> f a infixl 7 Source #

Compute the right scalar product

>>> V2 3 4 ^* 2
V2 6 8

(*^) :: (Functor f, Num a) => a -> f a -> f a infixl 7 Source #

Compute the left scalar product

>>> 2 *^ V2 3 4
V2 6 8

(^/) :: (Functor f, Fractional a) => f a -> a -> f a infixl 7 Source #

Compute division by a scalar on the right.

sumV :: (Foldable f, Additive v, Num a) => f (v a) -> v a Source #

Sum over multiple vectors

>>> sumV [V2 1 1, V2 3 4]
V2 4 5

basis :: (Additive t, Traversable t, Num a) => [t a] Source #

Produce a default basis for a vector space. If the dimensionality of the vector space is not statically known, see basisFor.

basisFor :: (Traversable t, Num a) => t b -> [t a] Source #

Produce a default basis for a vector space from which the argument is drawn.

scaled :: (Traversable t, Num a) => t a -> t (t a) Source #

Produce a diagonal (scale) matrix from a vector.

>>> scaled (V2 2 3)
V2 (V2 2 0) (V2 0 3)

outer :: (Functor f, Functor g, Num a) => f a -> g a -> f (g a) Source #

Outer (tensor) product of two vectors

unit :: (Additive t, Num a) => ASetter' (t a) a -> t a Source #

Create a unit vector.

>>> unit _x :: V2 Int
V2 1 0