| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Numeric.Matrix.Class
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
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.
Methods
translate4 :: Vector t 4 -> Matrix t 4 4 Source #
Create a translation matrix from a vector. The 4th coordinate is ignored.
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
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 == rotateX pitch %* rotateY yaw %* rotateZ roll
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.