| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Numeric.Matrix
Synopsis
- class MatrixTranspose t (n :: k) (m :: k) where
- class SquareMatrix t (n :: Nat) where
- class MatrixDeterminant t (n :: Nat) where
- class MatrixInverse t (n :: Nat) where
- class MatrixLU t (n :: Nat) where
- data LUFact t n = LUFact {}
- type Matrix (t :: l) (n :: k) (m :: k) = DataFrame t '[n, m]
- class HomTransform4 t where- translate4 :: Vector t 4 -> Matrix t 4 4
- translate3 :: Vector t 3 -> Matrix t 4 4
- rotateX :: t -> Matrix t 4 4
- rotateY :: t -> Matrix t 4 4
- rotateZ :: t -> Matrix t 4 4
- rotate :: Vector t 3 -> t -> Matrix t 4 4
- rotateEuler :: t -> t -> t -> Matrix t 4 4
- lookAt :: Vector t 3 -> Vector t 3 -> Vector t 3 -> Matrix t 4 4
- perspective :: t -> t -> t -> t -> Matrix t 4 4
- orthogonal :: t -> t -> t -> t -> Matrix t 4 4
- toHomPoint :: Vector t 3 -> Vector t 4
- toHomVector :: Vector t 3 -> Vector t 4
- fromHom :: Vector t 4 -> Vector t 3
 
- type Mat22f = Matrix Float 2 2
- type Mat23f = Matrix Float 2 3
- type Mat24f = Matrix Float 2 4
- type Mat32f = Matrix Float 3 2
- type Mat33f = Matrix Float 3 3
- type Mat34f = Matrix Float 3 4
- type Mat42f = Matrix Float 4 2
- type Mat43f = Matrix Float 4 3
- type Mat44f = Matrix Float 4 4
- type Mat22d = Matrix Double 2 2
- type Mat23d = Matrix Double 2 3
- type Mat24d = Matrix Double 2 4
- type Mat32d = Matrix Double 3 2
- type Mat33d = Matrix Double 3 3
- type Mat34d = Matrix Double 3 4
- type Mat42d = Matrix Double 4 2
- type Mat43d = Matrix Double 4 3
- type Mat44d = Matrix Double 4 4
- mat22 :: PrimBytes (t :: Type) => Vector t 2 -> Vector t 2 -> Matrix t 2 2
- mat33 :: PrimBytes (t :: Type) => Vector t 3 -> Vector t 3 -> Vector t 3 -> Matrix t 3 3
- mat44 :: PrimBytes (t :: Type) => Vector t 4 -> Vector t 4 -> Vector t 4 -> Vector t 4 -> Matrix t 4 4
- (%*) :: (Contraction t as bs asbs, KnownDim m, PrimArray t (DataFrame t (as +: m)), PrimArray t (DataFrame t (m :+ bs)), PrimArray t (DataFrame t asbs)) => DataFrame t (as +: m) -> DataFrame t (m :+ bs) -> DataFrame t asbs
- pivotMat :: forall (t :: Type) (n :: Nat). (KnownDim n, PrimArray t (Matrix t n n), Ord t, Num t) => Matrix t n n -> (Matrix t n n, Matrix t n n, Scalar t)
- luSolve :: forall (t :: Type) (n :: Nat). (KnownDim n, Fractional t, PrimArray t (Matrix t n n), PrimArray t (Vector t n)) => LUFact t n -> Vector t n -> Vector t n
Documentation
class MatrixTranspose t (n :: k) (m :: k) where Source #
class SquareMatrix t (n :: Nat) where Source #
class MatrixDeterminant t (n :: Nat) where Source #
Instances
| (KnownDim n, Ord t, Fractional t, PrimBytes t, PrimArray t (Matrix t n n)) => MatrixDeterminant t n Source # | |
class MatrixInverse t (n :: Nat) where Source #
Result of LU factorization with Partial Pivoting
    PA = LU .
Constructors
| LUFact | |
class HomTransform4 t where Source #
Operations on 4x4 transformation matrices and vectors in homogeneous coordinates. All angles are specified in radians.
Note: since version 2 of easytensor, DataFrames and matrices are row-major.
         A good SIMD implementation may drastically improve performance
         of 4D vector-matrix products of the form v %* m, but not so much
         for products of the form m %* v (due to memory layout).
         Thus, all operations here assume the former form to benefit more from
         SIMD in future.
Methods
translate4 :: Vector t 4 -> Matrix t 4 4 Source #
Create a translation matrix from a vector. The 4th coordinate is ignored.
If p ! 3 == 1 and v ! 3 == 0, then
p %* translate4 v == p + v
translate3 :: Vector t 3 -> Matrix t 4 4 Source #
Create a translation matrix from a vector.
If p ! 3 == 1, then
p %* translate3 v == p + toHomVector v
rotateX :: t -> Matrix t 4 4 Source #
Rotation matrix for a rotation around the X axis, angle is given in radians.
   e.g. p %* rotateX (pi/2) rotates point p around Ox by 90 degrees.
rotateY :: t -> Matrix t 4 4 Source #
Rotation matrix for a rotation around the Y axis, angle is given in radians.
   e.g. p %* rotateY (pi/2) rotates point p around Oy by 90 degrees.
rotateZ :: t -> Matrix t 4 4 Source #
Rotation matrix for a rotation around the Z axis, angle is given in radians.
   e.g. p %* rotateZ (pi/2) rotates point p around Oz by 90 degrees.
rotate :: Vector t 3 -> t -> Matrix t 4 4 Source #
Rotation matrix for a rotation around an arbitrary normalized vector
   e.g. p %* rotate (pi/2) v rotates point p around v by 90 degrees.
Arguments
| :: t | pitch (axis  | 
| -> t | yaw (axis  | 
| -> t | roll (axis  | 
| -> Matrix t 4 4 | 
Rotation matrix from the Euler angles roll (axis Z), yaw (axis Y'), and pitch (axis X'').
   This order is known as Tait-Bryan angles (Z-Y'-X'' intrinsic rotations), or nautical angles, or Cardan angles.
rotateEuler pitch yaw roll == rotateZ roll %* rotateY yaw %* rotateX pitch
Arguments
| :: Vector t 3 | The up direction, not necessary unit length or perpendicular to the view vector | 
| -> Vector t 3 | The viewers position | 
| -> Vector t 3 | The point to look at | 
| -> Matrix t 4 4 | 
Create a transform matrix using up direction, camera position and a point to look at. Just the same as GluLookAt.
Arguments
| :: t | Near plane clipping distance (always positive) | 
| -> t | Far plane clipping distance (always positive) | 
| -> t | Field of view of the y axis, in radians | 
| -> t | Aspect ratio, i.e. screen's width/height | 
| -> Matrix t 4 4 | 
A perspective symmetric projection matrix. Right-handed coordinate system. (x - right, y - top)
   http://en.wikibooks.org/wiki/GLSL_Programming/Vertex_Transformations
Arguments
| :: t | Near plane clipping distance | 
| -> t | Far plane clipping distance | 
| -> t | width | 
| -> t | height | 
| -> Matrix t 4 4 | 
An orthogonal symmetric projection matrix. Right-handed coordinate system. (x - right, y - top)
   http://en.wikibooks.org/wiki/GLSL_Programming/Vertex_Transformations
toHomPoint :: Vector t 3 -> Vector t 4 Source #
Add one more dimension and set it to 1.
toHomVector :: Vector t 3 -> Vector t 4 Source #
Add one more dimension and set it to 0.
fromHom :: Vector t 4 -> Vector t 3 Source #
Transform a homogenous vector or point into a normal 3D vector. If the last coordinate is not zero, divide the rest by it.
Instances
mat22 :: PrimBytes (t :: Type) => Vector t 2 -> Vector t 2 -> Matrix t 2 2 Source #
Compose a 2x2D matrix
mat33 :: PrimBytes (t :: Type) => Vector t 3 -> Vector t 3 -> Vector t 3 -> Matrix t 3 3 Source #
Compose a 3x3D matrix
mat44 :: PrimBytes (t :: Type) => Vector t 4 -> Vector t 4 -> Vector t 4 -> Vector t 4 -> Matrix t 4 4 Source #
Compose a 4x4D matrix
(%*) :: (Contraction t as bs asbs, KnownDim m, PrimArray t (DataFrame t (as +: m)), PrimArray t (DataFrame t (m :+ bs)), PrimArray t (DataFrame t asbs)) => DataFrame t (as +: m) -> DataFrame t (m :+ bs) -> DataFrame t asbs infixl 7 Source #
Tensor contraction. In particular: 1. matrix-matrix product 2. matrix-vector or vector-matrix product 3. dot product of two vectors.
pivotMat :: forall (t :: Type) (n :: Nat). (KnownDim n, PrimArray t (Matrix t n n), Ord t, Num t) => Matrix t n n -> (Matrix t n n, Matrix t n n, Scalar t) Source #
Permute rows that the largest magnitude elements in columns are on diagonals.
Invariants of result matrix: * forall j >= i: |M[i,i]| >= M[j,i] * if M[i,i] == 0 then forall j >= i: |M[i+1,i+1]| >= M[j,i+1]