rings-0.0.2.4: Groups, rings, semirings, and dioids.

Safe HaskellSafe
LanguageHaskell2010

Data.Semiring.Matrix

Description

API essentially follows that of linear & hmatrix.

Synopsis

Documentation

type M22 a = V2 (V2 a) Source #

A 2x2 matrix.

type M23 a = V2 (V3 a) Source #

A 2x3 matrix.

type M24 a = V2 (V4 a) Source #

A 2x4 matrix.

type M32 a = V3 (V2 a) Source #

A 3x2 matrix.

type M33 a = V3 (V3 a) Source #

A 3x3 matrix.

type M34 a = V3 (V4 a) Source #

A 3x4 matrix.

type M42 a = V4 (V2 a) Source #

A 4x2 matrix.

type M43 a = V4 (V3 a) Source #

A 4x3 matrix.

type M44 a = V4 (V4 a) Source #

A 4x4 matrix.

m22 :: a -> a -> a -> a -> M22 a Source #

Construct a 2x2 matrix.

Arguments are in row-major order.

m23 :: a -> a -> a -> a -> a -> a -> M23 a Source #

Construct a 2x3 matrix.

Arguments are in row-major order.

m24 :: a -> a -> a -> a -> a -> a -> a -> a -> M24 a Source #

Construct a 2x4 matrix.

Arguments are in row-major order.

m32 :: a -> a -> a -> a -> a -> a -> M32 a Source #

Construct a 3x2 matrix.

Arguments are in row-major order.

m33 :: a -> a -> a -> a -> a -> a -> a -> a -> a -> M33 a Source #

Construct a 3x3 matrix.

Arguments are in row-major order.

m34 :: a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> M34 a Source #

Construct a 3x4 matrix.

Arguments are in row-major order.

m42 :: a -> a -> a -> a -> a -> a -> a -> a -> M42 a Source #

Construct a 4x2 matrix.

Arguments are in row-major order.

m43 :: a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> M43 a Source #

Construct a 4x3 matrix.

Arguments are in row-major order.

m44 :: a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> M44 a Source #

Construct a 4x4 matrix.

Arguments are in row-major order.

row :: Representable f => Rep f -> f c -> c Source #

Index into a row of a matrix or vector.

>>> row I21 (V2 1 2)
1

col :: Functor f => Representable g => Rep g -> f (g a) -> f a Source #

Index into a column of a matrix.

>>> row I22 . col I31 $ V2 (V3 1 2 3) (V3 4 5 6)
4

(.>) :: Semiring a => Functor f => Functor g => a -> f (g a) -> f (g a) infixr 7 Source #

Scalar-matrix product.

The > arrow points towards the return type.

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

(<.) :: Semiring a => Functor f => Functor g => f (g a) -> a -> f (g a) infixl 7 Source #

Matrix-scalar product.

The < arrow points towards the return type.

>>> m22 1 2 3 4 <. 5
V2 (V2 5 10) (V2 15 20)
>>> m22 1 2 3 4 <. 5 <. 2
V2 (V2 10 20) (V2 30 40)

(#>) :: (Semiring a, Free f, Free g) => f (g a) -> g a -> f a infixr 7 Source #

Multiply a matrix on the right by a column vector.

>>> m23 1 2 3 4 5 6 #> V3 7 8 9
V2 50 122
>>> m22 1 0 0 0 #> m23 1 2 3 4 5 6 #> V3 7 8 9
V2 50 0

(<#) :: (Semiring a, Free f, Free g) => f a -> f (g a) -> g a infixl 7 Source #

Multiply a matrix on the left by a row vector.

>>> V2 1 2 <# m23 3 4 5 6 7 8
V3 15 18 21
>>> V2 1 2 <# m23 3 4 5 6 7 8 <# m32 1 0 0 0 0 0
V2 15 0

(<#>) :: (Semiring a, Free f, Free g, Free h) => f (g a) -> g (h a) -> f (h a) infixr 7 Source #

Multiply two matrices.

>>> m22 1 2 3 4 <#> m22 1 2 3 4 :: M22 Int
V2 (V2 7 10) (V2 15 22)
>>> m23 1 2 3 4 5 6 <#> m32 1 2 3 4 4 5 :: M22 Int
V2 (V2 19 25) (V2 43 58)

scale :: Monoid a => Free f => f a -> f (f a) Source #

Obtain a diagonal matrix from a vector.

>>> scale (V2 2 3)
V2 (V2 2 0) (V2 0 3)

identity :: Unital a => Free f => f (f a) Source #

Identity matrix.

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

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

Transpose a matrix.

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

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

trace :: Semigroup a => Free f => f (f a) -> a Source #

Compute the trace of a matrix.

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

diag :: Representable f => f (f a) -> f a Source #

Compute the diagonal of a matrix.

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

bdet2 :: Semiring a => M22 a -> (a, a) Source #

2x2 matrix bideterminant over a commutative semiring.

>>> bdet2 $ m22 1 2 3 4
(4,6)

det2 :: Ring a => M22 a -> a Source #

2x2 matrix determinant over a commutative ring.

det2uncurry (<<) . bdet2

det2d :: M22 Double -> Double Source #

2x2 double-precision matrix determinant.

>>> det2d $ m22 1 2 3 4
-2.0

inv2d :: M22 Double -> M22 Double Source #

2x2 double-precision matrix inverse.

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

bdet3 :: Semiring a => M33 a -> (a, a) Source #

3x3 matrix bideterminant over a commutative semiring.

>>> bdet3 (V3 (V3 1 2 3) (V3 4 5 6) (V3 7 8 9))
(225, 225)

det3 :: Ring a => M33 a -> a Source #

3x3 matrix determinant over a commutative ring.

det3uncurry (<<) . bdet3

det3d :: M33 Double -> Double Source #

3x3 double-precision matrix determinant.

This implementation uses a cofactor expansion to avoid loss of precision.

inv3d :: M33 Double -> M33 Double Source #

3x3 double-precision matrix inverse.

>>> inv3d $ m33 1 2 4 4 2 2 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))

bdet4 :: Semiring a => M44 a -> (a, a) Source #

4x4 matrix bideterminant over a commutative semiring.

>>> bdet4 (V4 (V4 1 2 3 4) (V4 5 6 7 8) (V4 9 10 11 12) (V4 13 14 15 16))
(27728,27728)

det4 :: Ring a => M44 a -> a Source #

4x4 matrix determinant over a commutative ring.

det4uncurry (<<) . bdet4

det4d :: M44 Double -> Double Source #

4x4 double-precision matrix determinant.

This implementation uses a cofactor expansion to avoid loss of precision.

inv4d :: M44 Double -> M44 Double Source #

4x4 double-precision matrix inverse.