Copyright | (c) Artem Chirkin |
---|---|
License | BSD3 |
Maintainer | chirkin@arch.ethz.ch |
Safe Haskell | None |
Language | Haskell2010 |
- class MatrixCalculus t n m where
- class SquareMatrixCalculus t n where
- class MatrixInverse t n where
- class HomTransform4 t where
- type Matrix t n m = DataFrame t '[n, m]
- 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 (Vector t 2), PrimBytes (Matrix t 2 2)) => Vector t 2 -> Vector t 2 -> Matrix t 2 2
- 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
- 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)
- (%*) :: (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)
Documentation
class MatrixCalculus t n m where Source #
class SquareMatrixCalculus t n where Source #
class MatrixInverse t n where Source #
class HomTransform4 t where Source #
Operations on 4x4 transformation matrices and vectors in homogeneous coordinates. All angles are specified in radians.
translate4, translate3, rotateX, rotateY, rotateZ, rotate, rotateEuler, lookAt, perspective, orthogonal, toHomPoint, toHomVector, fromHom
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.
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.