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

Copyright(c) Artem Chirkin
LicenseBSD3
Maintainerchirkin@arch.ethz.ch
Safe HaskellNone
LanguageHaskell2010

Numeric.Matrix

Description

 

Synopsis

Documentation

class MatrixCalculus t n m where Source #

Minimal complete definition

transpose

Methods

transpose :: (MatrixCalculus t m n, PrimBytes (Matrix t m n)) => Matrix t n m -> Matrix t m n Source #

Transpose Mat

class SquareMatrixCalculus t n where Source #

Minimal complete definition

eye, diag, det, 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

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

Determinant of Mat

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

Sum of diagonal elements

class MatrixInverse t n where Source #

Minimal complete definition

inverse

Methods

inverse :: DataFrame t '[n, n] -> DataFrame t '[n, n] Source #

Matrix inverse

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 :: Vector t 3 -> Vector t 3 -> Vector t 3 -> Matrix t 4 4 Source #

Create a transform matrix using up direction, camera position and a point to look at. Just the same as GluLookAt.

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

A perspective symmetric projection matrix. Right-handed coordinate system. (x - right, y - top) http://en.wikibooks.org/wiki/GLSL_Programming/Vertex_Transformations

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

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.

type Matrix t n m = DataFrame t '[n, m] Source #

Alias for DataFrames of rank 2

mat22 :: (PrimBytes (Vector t 2), PrimBytes (Matrix t 2 2)) => Vector t 2 -> Vector t 2 -> Matrix t 2 2 Source #

Compose a 2x2D matrix

mat33 :: (PrimBytes t, PrimBytes (Vector t 3), PrimBytes (Matrix t 3 3)) => Vector t 3 -> Vector t 3 -> Vector t 3 -> Matrix t 3 3 Source #

Compose a 3x3D matrix

mat44 :: forall t. (PrimBytes t, PrimBytes (Vector t (4 :: Nat)), PrimBytes (Matrix t (4 :: Nat) (4 :: Nat))) => Vector t (4 :: Nat) -> Vector t (4 :: Nat) -> Vector t (4 :: Nat) -> Vector t (4 :: Nat) -> Matrix t (4 :: Nat) (4 :: Nat) Source #

Compose a 4x4D matrix

(%*) :: (ConcatList as bs (as ++ bs), Contraction t as bs asbs, KnownDim m, PrimBytes (DataFrame t (as +: m)), PrimBytes (DataFrame t (m :+ bs)), PrimBytes (DataFrame t (as ++ bs))) => DataFrame t (as +: m) -> DataFrame t (m :+ bs) -> DataFrame t (as ++ bs) infixl 7 Source #

Tensor contraction. In particular: 1. matrix-matrix product 2. matrix-vector or vector-matrix product 3. dot product of two vectors.