easytensor-2.1.1.1: Pure, type-indexed haskell vector, matrix, and tensor library.
Safe HaskellNone
LanguageHaskell2010

Numeric.Matrix

Synopsis

Documentation

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

Methods

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

Transpose Mat

Instances

Instances details
MatrixTranspose (t :: Type) (xn :: XNat) (xm :: XNat) Source # 
Instance details

Defined in Numeric.Matrix.Internal

Methods

transpose :: Matrix t xn xm -> Matrix t xm xn Source #

(KnownDim n, KnownDim m, PrimArray t (Matrix t n m), PrimArray t (Matrix t m n)) => MatrixTranspose (t :: Type) (n :: Nat) (m :: Nat) Source # 
Instance details

Defined in Numeric.Matrix.Internal

Methods

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

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

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

Instances

Instances details
(KnownDim n, PrimArray t (Matrix t n n), Num t) => SquareMatrix t n Source # 
Instance details

Defined in Numeric.Matrix.Internal

Methods

eye :: Matrix t n n Source #

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

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

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

Methods

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

Determinant of Mat

Instances

Instances details
KnownDim n => MatrixDeterminant Double n Source # 
Instance details

Defined in Numeric.Matrix.Internal.Double

Methods

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

KnownDim n => MatrixDeterminant Float n Source # 
Instance details

Defined in Numeric.Matrix.Internal.Float

Methods

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

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

Methods

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

Matrix inverse

Instances

Instances details
KnownDim n => MatrixInverse Double n Source # 
Instance details

Defined in Numeric.Matrix.Internal.Double

Methods

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

KnownDim n => MatrixInverse Float n Source # 
Instance details

Defined in Numeric.Matrix.Internal.Float

Methods

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

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.

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.

rotateEuler Source #

Arguments

:: t

pitch (axis X'')

-> t

yaw (axis Y')

-> t

roll (axis Z)

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

https://en.wikipedia.org/wiki/Euler_angles#Conventions_2

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.

Instances

Instances details
HomTransform4 Double Source # 
Instance details

Defined in Numeric.Matrix.Internal.Double

HomTransform4 Float Source # 
Instance details

Defined in Numeric.Matrix.Internal.Float

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.