linear-1.4: Linear Algebra

Portabilitynon-portable
Stabilityexperimental
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellTrustworthy

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

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 aSource

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

Scalar-matrix product

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

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 M33 a = V3 (V3 a)Source

A 3x3 matrix with row-major representation

type M44 a = V4 (V4 a)Source

A 4x4 matrix with row-major representation

type M43 a = V4 (V3 a)Source

A 4x3 matrix with row-major representation

m33_to_m44 :: Num a => M33 a -> M44 aSource

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 aSource

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

det22 :: Num a => M22 a -> aSource

2x2 matrix determinant.

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

det33 :: Num a => M33 a -> aSource

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)

inv22 :: (Epsilon a, Floating a) => M22 a -> Maybe (M22 a)Source

2x2 matrix inverse.

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

inv33 :: (Epsilon a, Floating a) => M33 a -> Maybe (M33 a)Source

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

eye2 :: Num a => M22 aSource

2x2 identity matrix.

>>> eye2
V2 (V2 1 0) (V2 0 1)

eye3 :: Num a => M33 aSource

3x3 identity matrix.

>>> eye3
V3 (V3 1 0 0) (V3 0 1 0) (V3 0 0 1)

eye4 :: Num a => M44 aSource

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)

class Functor m => Trace m whereSource

Methods

trace :: Num a => m (m a) -> aSource

Compute the trace of a matrix

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

diagonal :: m (m a) -> m aSource

Compute the diagonal of a matrix

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

Instances

translation :: (Functor f, R4 v, R3 t) => (V3 a -> f (V3 a)) -> t (v a) -> f (t (v a))Source

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

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

fromQuaternion :: Num a => Quaternion a -> M33 aSource

Build a rotation matrix from a unit Quaternion.

mkTransformation :: Num a => Quaternion a -> V3 a -> M44 aSource

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

mkTransformationMat :: Num a => M33 a -> V3 a -> M44 aSource

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