| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Data.Semimodule.Matrix
Synopsis
- type M22 a = V2 (V2 a)
- type M23 a = V2 (V3 a)
- type M24 a = V2 (V4 a)
- type M32 a = V3 (V2 a)
- type M33 a = V3 (V3 a)
- type M34 a = V3 (V4 a)
- type M42 a = V4 (V2 a)
- type M43 a = V4 (V3 a)
- type M44 a = V4 (V4 a)
- lensRep :: Eq (Rep f) => Representable f => Rep f -> forall g. Functor g => (a -> g a) -> f a -> g (f a)
- grateRep :: Representable f => forall g. Functor g => (Rep f -> g a -> b) -> g (f a) -> f b
- tran :: Semiring a => Basis b f => Basis c g => Foldable g => f (g a) -> Tran a b c
- row :: Representable f => Rep f -> f a -> a
- rows :: Free f => Free g => g a -> f (g a)
- col :: Functor f => Representable g => Rep g -> f (g a) -> f a
- cols :: Free f => Free g => f a -> f (g a)
- (.#) :: (Semiring a, Free f, Free g, Foldable g) => f (g a) -> g a -> f a
- (.*) :: Semimodule r a => a -> r -> a
- (#.) :: (Semiring a, Free f, Foldable f, Free g) => f a -> f (g a) -> g a
- (*.) :: Semimodule r a => r -> a -> a
- (.#.) :: (Semiring a, Free f, Free g, Free h, Foldable g) => f (g a) -> g (h a) -> f (h a)
- (.*.) :: Free f => Foldable f => Semiring a => f a -> f a -> a
- outer :: Semiring a => Functor f => Functor g => f a -> g a -> f (g a)
- scale :: (Additive - Monoid) a => Free f => f a -> f (f a)
- dirac :: Eq i => Semiring a => i -> i -> a
- identity :: Semiring a => Free f => f (f a)
- transpose :: Free f => Free g => f (g a) -> g (f a)
- trace :: Semiring a => Free f => Foldable f => f (f a) -> a
- diagonal :: Representable f => f (f a) -> f a
- bdet2 :: Semiring a => Basis I2 f => Basis I2 g => f (g a) -> (a, a)
- det2 :: Ring a => Basis I2 f => Basis I2 g => f (g a) -> a
- inv2 :: Field a => Basis I2 f => Basis I2 g => f (g a) -> g (f a)
- bdet3 :: Semiring a => Basis I3 f => Basis I3 g => f (g a) -> (a, a)
- det3 :: Ring a => Basis I3 f => Basis I3 g => f (g a) -> a
- inv3 :: forall a f g. Field a => Basis I3 f => Basis I3 g => f (g a) -> g (f a)
- bdet4 :: Semiring a => Basis I4 f => Basis I4 g => f (g a) -> (a, a)
- det4 :: Ring a => Basis I4 f => Basis I4 g => f (g a) -> a
- inv4 :: forall a f g. Field a => Basis I4 f => Basis I4 g => f (g a) -> g (f a)
- m22 :: Basis I2 f => Basis I2 g => a -> a -> a -> a -> f (g a)
- m23 :: Basis I2 f => Basis I3 g => a -> a -> a -> a -> a -> a -> f (g a)
- m24 :: Basis I2 f => Basis I4 g => a -> a -> a -> a -> a -> a -> a -> a -> f (g a)
- m32 :: Basis I3 f => Basis I2 g => a -> a -> a -> a -> a -> a -> f (g a)
- m33 :: Basis I3 f => Basis I3 g => a -> a -> a -> a -> a -> a -> a -> a -> a -> f (g a)
- m34 :: Basis I3 f => Basis I4 g => a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> f (g a)
- m42 :: Basis I4 f => Basis I2 g => a -> a -> a -> a -> a -> a -> a -> a -> f (g a)
- m43 :: Basis I4 f => Basis I3 g => a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> f (g a)
- m44 :: Basis I4 f => Basis I4 g => a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> f (g a)
Documentation
lensRep :: Eq (Rep f) => Representable f => Rep f -> forall g. Functor g => (a -> g a) -> f a -> g (f a) Source #
grateRep :: Representable f => forall g. Functor g => (Rep f -> g a -> b) -> g (f a) -> f b Source #
row :: Representable f => Rep f -> f a -> a Source #
Retrieve a row of a row-major matrix or element of a row vector.
>>>row I21 (V2 1 2)1
rows :: Free f => Free g => g a -> f (g a) Source #
Obtain a matrix by stacking rows.
>>>rows (V2 1 2) :: M22 IntV2 (V2 1 2) (V2 1 2)
col :: Functor f => Representable g => Rep g -> f (g a) -> f a Source #
Retrieve a column of a row-major matrix.
>>>row I22 . col I31 $ V2 (V3 1 2 3) (V3 4 5 6)4
cols :: Free f => Free g => f a -> f (g a) Source #
Obtain a matrix by stacking columns.
>>>cols (V2 1 2) :: M22 IntV2 (V2 1 1) (V2 2 2)
(.*) :: Semimodule r a => a -> r -> a infixl 7 Source #
Right-multiply by a scalar.
(#.) :: (Semiring a, Free f, Foldable 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 8V3 15 18 21
>>>V2 1 2 #. m23 3 4 5 6 7 8 #. m32 1 0 0 0 0 0V2 15 0
(*.) :: Semimodule r a => r -> a -> a infixl 7 Source #
Left-multiply by a scalar.
(.#.) :: (Semiring a, Free f, Free g, Free h, Foldable g) => 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 IntV2 (V2 7 10) (V2 15 22)
>>>m23 1 2 3 4 5 6 .#. m32 1 2 3 4 4 5 :: M22 IntV2 (V2 19 25) (V2 43 58)
(.*.) :: Free f => Foldable f => Semiring a => f a -> f a -> a infix 6 Source #
Dot product.
>>>V3 1 2 3 .*. V3 1 2 314
outer :: Semiring a => Functor f => Functor g => f a -> g a -> f (g a) Source #
Outer product of two vectors.
>>>V2 1 1 `outer` V2 1 1V2 (V2 1 1) (V2 1 1)
scale :: (Additive - 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 :: Semiring a => Free f => f (f a) Source #
Identity matrix.
>>>identity :: M44 IntV4 (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 :: Free f => Free 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)
>>>transpose $ m23 1 2 3 4 5 6 :: M32 IntV3 (V2 1 4) (V2 2 5) (V2 3 6)
trace :: Semiring a => Free f => Foldable f => f (f a) -> a Source #
Compute the trace of a matrix.
>>>trace (V2 (V2 a b) (V2 c d))a <> d
diagonal :: Representable f => f (f a) -> f a Source #
Obtain the diagonal of a matrix as a vector.
>>>diagonal (V2 (V2 a b) (V2 c d))V2 a d
bdet2 :: Semiring a => Basis I2 f => Basis I2 g => f (g a) -> (a, a) Source #
2x2 matrix bdeterminant over a commutative semiring.
>>>bdet2 $ m22 1 2 3 4(4,6)
inv2 :: Field a => Basis I2 f => Basis I2 g => f (g a) -> g (f a) Source #
2x2 matrix inverse over a field.
>>>inv2 $ m22 1 2 3 4 :: M22 DoubleV2 (V2 (-2.0) 1.0) (V2 1.5 (-0.5))
bdet3 :: Semiring a => Basis I3 f => Basis I3 g => f (g a) -> (a, a) Source #
3x3 matrix bdeterminant over a commutative semiring.
>>>bdet3 (V3 (V3 1 2 3) (V3 4 5 6) (V3 7 8 9))(225, 225)
inv3 :: forall a f g. Field a => Basis I3 f => Basis I3 g => f (g a) -> g (f a) Source #
3x3 matrix inverse.
>>>inv3 $ m33 1 2 4 4 2 2 1 1 1 :: M33 DoubleV3 (V3 0.0 0.5 (-1.0)) (V3 (-0.5) (-0.75) 3.5) (V3 0.5 0.25 (-1.5))
bdet4 :: Semiring a => Basis I4 f => Basis I4 g => f (g a) -> (a, a) Source #
4x4 matrix bdeterminant 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)
inv4 :: forall a f g. Field a => Basis I4 f => Basis I4 g => f (g a) -> g (f a) Source #
4x4 matrix inverse.
>>>row I41 $ inv4 (m44 1 0 3 2 2 0 2 1 0 0 0 1 0 3 4 0 :: M44 Rational)V4 (6 % (-12)) ((-9) % (-12)) ((-3) % (-12)) (0 % (-12))
m24 :: Basis I2 f => Basis I4 g => a -> a -> a -> a -> a -> a -> a -> a -> f (g a) Source #
Construct a 2x4 matrix.
Arguments are in row-major order.
m32 :: Basis I3 f => Basis I2 g => a -> a -> a -> a -> a -> a -> f (g a) Source #
Construct a 3x2 matrix.
Arguments are in row-major order.
m33 :: Basis I3 f => Basis I3 g => a -> a -> a -> a -> a -> a -> a -> a -> a -> f (g a) Source #
Construct a 3x3 matrix.
Arguments are in row-major order.
m34 :: Basis I3 f => Basis I4 g => a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> f (g a) Source #
Construct a 3x4 matrix.
Arguments are in row-major order.
m42 :: Basis I4 f => Basis I2 g => a -> a -> a -> a -> a -> a -> a -> a -> f (g a) Source #
Construct a 4x2 matrix.
Arguments are in row-major order.