easytensor-1.0.0.0: Pure, type-indexed haskell vector, matrix, and tensor library.

Safe HaskellNone
LanguageHaskell2010

Numeric.Matrix.Class

Synopsis

Documentation

class MatrixTranspose t (n :: k) (m :: k) where Source #

Minimal complete definition

transpose

Methods

transpose :: Matrix t n m -> Matrix t m n Source #

Transpose Mat

class SquareMatrix t (n :: Nat) where Source #

Minimal complete definition

eye, diag, trace

Methods

eye :: Matrix t n n Source #

Mat with 1 on diagonal and 0 elsewhere

diag :: Scalar t -> Matrix t n n Source #

Put the same value on the Mat diagonal, 0 otherwise

trace :: Matrix t n n -> Scalar t Source #

Sum of diagonal elements

class MatrixDeterminant t (n :: Nat) where Source #

Minimal complete definition

det

Methods

det :: Matrix t n n -> Scalar t Source #

Determinant of Mat

class MatrixInverse t (n :: Nat) where Source #

Minimal complete definition

inverse

Methods

inverse :: Matrix t n n -> Matrix t n n Source #

Matrix inverse

class MatrixLU t (n :: Nat) where Source #

Minimal complete definition

lu

Methods

lu :: Matrix t n n -> LUFact t n Source #

Compute LU factorization with Partial Pivoting

data LUFact t n Source #

Result of LU factorization with Partial Pivoting PA = LU .

Constructors

LUFact 

Fields

Instances

(Eq (Matrix * k t n n), Eq t) => Eq (LUFact k t n) Source # 

Methods

(==) :: LUFact k t n -> LUFact k t n -> Bool #

(/=) :: LUFact k t n -> LUFact k t n -> Bool #

(Show (Matrix * k t n n), Show t) => Show (LUFact k t n) Source # 

Methods

showsPrec :: Int -> LUFact k t n -> ShowS #

show :: LUFact k t n -> String #

showList :: [LUFact k t n] -> ShowS #

type Matrix (t :: l) (n :: k) (m :: k) = DataFrame t '[n, m] Source #

Alias for DataFrames of rank 2

class HomTransform4 t where Source #

Operations on 4x4 transformation matrices and vectors in homogeneous coordinates. All angles are specified in radians.

Methods

translate4 :: Vector t 4 -> Matrix t 4 4 Source #

Create a translation matrix from a vector

translate3 :: Vector t 3 -> Matrix t 4 4 Source #

Create a translation matrix from a vector

rotateX :: t -> Matrix t 4 4 Source #

Rotation matrix for a rotation around the X axis, angle is given in radians.

rotateY :: t -> Matrix t 4 4 Source #

Rotation matrix for a rotation around the Y axis, angle is given in radians.

rotateZ :: t -> Matrix t 4 4 Source #

Rotation matrix for a rotation around the Z axis, angle is given in radians.

rotate :: Vector t 3 -> t -> Matrix t 4 4 Source #

Rotation matrix for a rotation around an arbitrary normalized vector

rotateEuler :: t -> t -> t -> Matrix t 4 4 Source #

Rotation matrix from the Euler angles yaw pitch and roll

lookAt Source #

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.

perspective Source #

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

orthogonal Source #

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.