linear-1.21.5: Linear Algebra
Copyright(C) 2012-2015 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellTrustworthy
LanguageHaskell2010

Linear.Matrix

Description

Simple matrix operation for low-dimensional primitives.

Synopsis

Documentation

(!*!) :: (Functor m, Foldable t, Additive t, Additive n, Num a) => m (t a) -> t (n a) -> m (n a) infixl 7 Source #

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)

(!+!) :: (Additive m, Additive n, Num a) => m (n a) -> m (n a) -> m (n a) infixl 6 Source #

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) infixl 6 Source #

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)

(!*) :: (Functor m, Foldable r, Additive r, Num a) => m (r a) -> r a -> m a infixl 7 Source #

Matrix * column vector

>>> V2 (V3 1 2 3) (V3 4 5 6) !* V3 7 8 9
V2 50 122

(*!) :: (Num a, Foldable t, Additive f, Additive t) => t a -> t (f a) -> f a infixl 7 Source #

Row vector * matrix

>>> V2 1 2 *! V2 (V3 3 4 5) (V3 6 7 8)
V3 15 18 21

(!!*) :: (Functor m, Functor r, Num a) => m (r a) -> a -> m (r a) infixl 7 Source #

Matrix-scalar product

>>> V2 (V2 1 2) (V2 3 4) !!* 5
V2 (V2 5 10) (V2 15 20)

(*!!) :: (Functor m, Functor r, Num a) => a -> m (r a) -> m (r a) infixl 7 Source #

Scalar-matrix product

>>> 5 *!! V2 (V2 1 2) (V2 3 4)
V2 (V2 5 10) (V2 15 20)

(!!/) :: (Functor m, Functor r, Fractional a) => m (r a) -> a -> m (r a) infixl 7 Source #

Matrix-scalar division

column :: Representable f => LensLike (Context a b) s t a b -> Lens (f s) (f t) (f a) (f b) Source #

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

adjoint :: (Functor m, Distributive n, Conjugate a) => m (n a) -> n (m a) Source #

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)))

type M22 a = V2 (V2 a) Source #

A 2x2 matrix with row-major representation

type M23 a = V2 (V3 a) Source #

A 2x3 matrix with row-major representation

type M24 a = V2 (V4 a) Source #

A 2x4 matrix with row-major representation

type M32 a = V3 (V2 a) Source #

A 3x2 matrix with row-major representation

type M33 a = V3 (V3 a) Source #

A 3x3 matrix with row-major representation

type M34 a = V3 (V4 a) Source #

A 3x4 matrix with row-major representation

type M42 a = V4 (V2 a) Source #

A 4x2 matrix with row-major representation

type M43 a = V4 (V3 a) Source #

A 4x3 matrix with row-major representation

type M44 a = V4 (V4 a) Source #

A 4x4 matrix with row-major representation

m33_to_m44 :: Num a => M33 a -> M44 a Source #

Convert a 3x3 matrix to a 4x4 matrix extending it with 0's in the new row and column.

m43_to_m44 :: Num a => M43 a -> M44 a Source #

Convert from a 4x3 matrix to a 4x4 matrix, extending it with the [ 0 0 0 1 ] column vector

det22 :: Num a => M22 a -> a Source #

2x2 matrix determinant.

>>> det22 (V2 (V2 a b) (V2 c d))
a * d - b * c

det33 :: Num a => M33 a -> a Source #

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)

det44 :: Num a => M44 a -> a Source #

4x4 matrix determinant.

inv22 :: Fractional a => M22 a -> M22 a Source #

2x2 matrix inverse.

>>> inv22 $ V2 (V2 1 2) (V2 3 4)
V2 (V2 (-2.0) 1.0) (V2 1.5 (-0.5))

inv33 :: Fractional a => M33 a -> M33 a Source #

3x3 matrix inverse.

>>> inv33 $ V3 (V3 1 2 4) (V3 4 2 2) (V3 1 1 1)
V3 (V3 0.0 0.5 (-1.0)) (V3 (-0.5) (-0.75) 3.5) (V3 0.5 0.25 (-1.5))

inv44 :: Fractional a => M44 a -> M44 a Source #

4x4 matrix inverse.

identity :: (Num a, Traversable t, Applicative t) => t (t a) Source #

The identity matrix for any dimension vector.

>>> identity :: M44 Int
V4 (V4 1 0 0 0) (V4 0 1 0 0) (V4 0 0 1 0) (V4 0 0 0 1)
>>> identity :: V3 (V3 Int)
V3 (V3 1 0 0) (V3 0 1 0) (V3 0 0 1)

class Functor m => Trace m where Source #

Minimal complete definition

Nothing

Methods

trace :: Num a => m (m a) -> a Source #

Compute the trace of a matrix

>>> trace (V2 (V2 a b) (V2 c d))
a + d

default trace :: (Foldable m, Num a) => m (m a) -> a Source #

diagonal :: m (m a) -> m a Source #

Compute the diagonal of a matrix

>>> diagonal (V2 (V2 a b) (V2 c d))
V2 a d

default diagonal :: Monad m => m (m a) -> m a Source #

Instances

Instances details
Trace Complex Source # 
Instance details

Defined in Linear.Trace

Methods

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

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

Trace IntMap Source # 
Instance details

Defined in Linear.Trace

Methods

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

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

Trace V1 Source # 
Instance details

Defined in Linear.Trace

Methods

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

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

Trace V2 Source # 
Instance details

Defined in Linear.Trace

Methods

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

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

Trace V3 Source # 
Instance details

Defined in Linear.Trace

Methods

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

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

Trace V4 Source # 
Instance details

Defined in Linear.Trace

Methods

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

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

Trace V0 Source # 
Instance details

Defined in Linear.Trace

Methods

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

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

Trace Quaternion Source # 
Instance details

Defined in Linear.Trace

Trace Plucker Source # 
Instance details

Defined in Linear.Trace

Methods

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

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

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

Defined in Linear.Trace

Methods

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

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

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

Defined in Linear.Trace

Methods

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

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

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

Defined in Linear.Trace

Methods

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

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

(Trace f, Trace g) => Trace (Product f g) Source # 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => Product f g (Product f g a) -> a Source #

diagonal :: Product f g (Product f g a) -> Product f g a Source #

(Distributive g, Trace g, Trace f) => Trace (Compose g f) Source # 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => Compose g f (Compose g f a) -> a Source #

diagonal :: Compose g f (Compose g f a) -> Compose g f a Source #

translation :: (Representable t, R3 t, R4 v) => Lens' (t (v a)) (V3 a) Source #

Extract the translation vector (first three entries of the last column) from a 3x4 or 4x4 matrix.

transpose :: (Distributive g, Functor f) => f (g a) -> g (f a) Source #

transpose is just an alias for distribute

transpose (V3 (V2 1 2) (V2 3 4) (V2 5 6))

V2 (V3 1 3 5) (V3 2 4 6)

fromQuaternion :: Num a => Quaternion a -> M33 a Source #

Build a rotation matrix from a unit Quaternion.

mkTransformation :: Num a => Quaternion a -> V3 a -> M44 a Source #

Build a transformation matrix from a rotation expressed as a Quaternion and a translation vector.

mkTransformationMat :: Num a => M33 a -> V3 a -> M44 a Source #

Build a transformation matrix from a rotation matrix and a translation vector.

_m22 :: (Representable t, R2 t, R2 v) => Lens' (t (v a)) (M22 a) Source #

Extract a 2x2 matrix from a matrix of higher dimensions by dropping excess rows and columns.

_m23 :: (Representable t, R2 t, R3 v) => Lens' (t (v a)) (M23 a) Source #

Extract a 2x3 matrix from a matrix of higher dimensions by dropping excess rows and columns.

_m24 :: (Representable t, R2 t, R4 v) => Lens' (t (v a)) (M24 a) Source #

Extract a 2x4 matrix from a matrix of higher dimensions by dropping excess rows and columns.

_m32 :: (Representable t, R3 t, R2 v) => Lens' (t (v a)) (M32 a) Source #

Extract a 3x2 matrix from a matrix of higher dimensions by dropping excess rows and columns.

_m33 :: (Representable t, R3 t, R3 v) => Lens' (t (v a)) (M33 a) Source #

Extract a 3x3 matrix from a matrix of higher dimensions by dropping excess rows and columns.

_m34 :: (Representable t, R3 t, R4 v) => Lens' (t (v a)) (M34 a) Source #

Extract a 3x4 matrix from a matrix of higher dimensions by dropping excess rows and columns.

_m42 :: (Representable t, R4 t, R2 v) => Lens' (t (v a)) (M42 a) Source #

Extract a 4x2 matrix from a matrix of higher dimensions by dropping excess rows and columns.

_m43 :: (Representable t, R4 t, R3 v) => Lens' (t (v a)) (M43 a) Source #

Extract a 4x3 matrix from a matrix of higher dimensions by dropping excess rows and columns.

_m44 :: (Representable t, R4 t, R4 v) => Lens' (t (v a)) (M44 a) Source #

Extract a 4x4 matrix from a matrix of higher dimensions by dropping excess rows and columns.

lu :: (Num a, Fractional a, Foldable m, Traversable m, Applicative m, Additive m, Ixed (m a), Ixed (m (m a)), i ~ Index (m a), i ~ Index (m (m a)), Eq i, Integral i, a ~ IxValue (m a), m a ~ IxValue (m (m a)), Num (m a)) => m (m a) -> (m (m a), m (m a)) Source #

Compute the (L, U) decomposition of a square matrix using Crout's algorithm. The Index of the vectors must be Integral.

luFinite :: (Num a, Fractional a, Functor m, Finite m, n ~ Size m, KnownNat n, Num (m a)) => m (m a) -> (m (m a), m (m a)) Source #

Compute the (L, U) decomposition of a square matrix using Crout's algorithm, using the vector's Finite instance to provide an index.

forwardSub :: (Num a, Fractional a, Foldable m, Additive m, Ixed (m a), Ixed (m (m a)), i ~ Index (m a), i ~ Index (m (m a)), Eq i, Ord i, Integral i, a ~ IxValue (m a), m a ~ IxValue (m (m a))) => m (m a) -> m a -> m a Source #

Solve a linear system with a lower-triangular matrix of coefficients with forwards substitution.

forwardSubFinite :: (Num a, Fractional a, Foldable m, n ~ Size m, KnownNat n, Additive m, Finite m) => m (m a) -> m a -> m a Source #

Solve a linear system with a lower-triangular matrix of coefficients with forwards substitution, using the vector's Finite instance to provide an index.

backwardSub :: (Num a, Fractional a, Foldable m, Additive m, Ixed (m a), Ixed (m (m a)), i ~ Index (m a), i ~ Index (m (m a)), Eq i, Ord i, Integral i, a ~ IxValue (m a), m a ~ IxValue (m (m a))) => m (m a) -> m a -> m a Source #

Solve a linear system with an upper-triangular matrix of coefficients with backwards substitution.

backwardSubFinite :: (Num a, Fractional a, Foldable m, n ~ Size m, KnownNat n, Additive m, Finite m) => m (m a) -> m a -> m a Source #

Solve a linear system with an upper-triangular matrix of coefficients with backwards substitution, using the vector's Finite instance to provide an index.

luSolve :: (Num a, Fractional a, Foldable m, Traversable m, Applicative m, Additive m, Ixed (m a), Ixed (m (m a)), i ~ Index (m a), i ~ Index (m (m a)), Eq i, Integral i, a ~ IxValue (m a), m a ~ IxValue (m (m a)), Num (m a)) => m (m a) -> m a -> m a Source #

Solve a linear system with LU decomposition.

luSolveFinite :: (Num a, Fractional a, Functor m, Finite m, n ~ Size m, KnownNat n, Num (m a)) => m (m a) -> m a -> m a Source #

Solve a linear system with LU decomposition, using the vector's Finite instance to provide an index.

luInv :: (Num a, Fractional a, Foldable m, Traversable m, Applicative m, Additive m, Distributive m, Ixed (m a), Ixed (m (m a)), i ~ Index (m a), i ~ Index (m (m a)), Eq i, Integral i, a ~ IxValue (m a), m a ~ IxValue (m (m a)), Num (m a)) => m (m a) -> m (m a) Source #

Invert a matrix with LU decomposition.

luInvFinite :: (Num a, Fractional a, Functor m, Finite m, n ~ Size m, KnownNat n, Num (m a)) => m (m a) -> m (m a) Source #

Invert a matrix with LU decomposition, using the vector's Finite instance to provide an index.

luDet :: (Num a, Fractional a, Foldable m, Traversable m, Applicative m, Additive m, Trace m, Ixed (m a), Ixed (m (m a)), i ~ Index (m a), i ~ Index (m (m a)), Eq i, Integral i, a ~ IxValue (m a), m a ~ IxValue (m (m a)), Num (m a)) => m (m a) -> a Source #

Compute the determinant of a matrix using LU decomposition.

luDetFinite :: (Num a, Fractional a, Functor m, Finite m, n ~ Size m, KnownNat n, Num (m a)) => m (m a) -> a Source #

Compute the determinant of a matrix using LU decomposition, using the vector's Finite instance to provide an index.