Copyright | (C) 2012-2015 Edward Kmett |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Edward Kmett <[email protected]> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Trustworthy |
Language | Haskell98 |
Linear.Matrix
Description
Simple matrix operation for low-dimensional primitives.
- (!*!) :: (Functor m, Foldable t, Additive t, Additive n, Num a) => m (t a) -> t (n a) -> m (n a)
- (!+!) :: (Additive m, Additive n, Num a) => m (n a) -> m (n a) -> m (n a)
- (!-!) :: (Additive m, Additive n, Num a) => m (n a) -> m (n a) -> m (n a)
- (!*) :: (Functor m, Foldable r, Additive r, Num a) => m (r a) -> r a -> m a
- (*!) :: (Num a, Foldable t, Additive f, Additive t) => t a -> t (f a) -> f a
- (!!*) :: (Functor m, Functor r, Num a) => m (r a) -> a -> m (r a)
- (*!!) :: (Functor m, Functor r, Num a) => a -> m (r a) -> m (r a)
- (!!/) :: (Functor m, Functor r, Fractional a) => m (r a) -> a -> m (r a)
- column :: Representable f => LensLike (Context a b) s t a b -> Lens (f s) (f t) (f a) (f b)
- adjoint :: (Functor m, Distributive n, Conjugate a) => m (n a) -> n (m a)
- 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)
- m33_to_m44 :: Num a => M33 a -> M44 a
- m43_to_m44 :: Num a => M43 a -> M44 a
- det22 :: Num a => M22 a -> a
- det33 :: Num a => M33 a -> a
- det44 :: Num a => M44 a -> a
- inv22 :: Floating a => M22 a -> M22 a
- inv33 :: Floating a => M33 a -> M33 a
- inv44 :: Fractional a => M44 a -> M44 a
- identity :: (Num a, Traversable t, Applicative t) => t (t a)
- class Functor m => Trace m where
- translation :: (Representable t, R3 t, R4 v) => Lens' (t (v a)) (V3 a)
- transpose :: (Distributive g, Functor f) => f (g a) -> g (f a)
- fromQuaternion :: Num a => Quaternion a -> M33 a
- mkTransformation :: Num a => Quaternion a -> V3 a -> M44 a
- mkTransformationMat :: Num a => M33 a -> V3 a -> M44 a
- _m22 :: (Representable t, R2 t, R2 v) => Lens' (t (v a)) (M22 a)
- _m23 :: (Representable t, R2 t, R3 v) => Lens' (t (v a)) (M23 a)
- _m24 :: (Representable t, R2 t, R4 v) => Lens' (t (v a)) (M24 a)
- _m32 :: (Representable t, R3 t, R2 v) => Lens' (t (v a)) (M32 a)
- _m33 :: (Representable t, R3 t, R3 v) => Lens' (t (v a)) (M33 a)
- _m34 :: (Representable t, R3 t, R4 v) => Lens' (t (v a)) (M34 a)
- _m42 :: (Representable t, R4 t, R2 v) => Lens' (t (v a)) (M42 a)
- _m43 :: (Representable t, R4 t, R3 v) => Lens' (t (v a)) (M43 a)
- _m44 :: (Representable t, R4 t, R4 v) => Lens' (t (v a)) (M44 a)
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
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)))
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)
inv22 :: Floating 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 :: Floating 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
diagonal :: m (m a) -> m a Source
Compute the diagonal of a matrix
>>>
diagonal (V2 (V2 a b) (V2 c d))
V2 a d
Instances
Trace Complex Source | |
Trace IntMap Source | |
Trace V0 Source | |
Trace V1 Source | |
Trace V2 Source | |
Trace V3 Source | |
Trace V4 Source | |
Trace Plucker Source | |
Trace Quaternion Source | |
Ord k => Trace (Map k) Source | |
(Eq k, Hashable k) => Trace (HashMap k) Source | |
(Distributive g, Trace g, Trace f) => Trace (Compose g f) Source | |
(Trace f, Trace g) => Trace (Product f g) Source | |
Dim * n => Trace (V * n) 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.