Vec-1.0.1: Fixed-length lists and low-dimensional linear algebra.

Safe HaskellNone

Data.Vec.LinAlg

Synopsis

Documentation

dot :: (Num a, Num v, Fold v a) => v -> v -> aSource

dot / inner / scalar product

normSq :: (Num a, Num v, Fold v a) => v -> aSource

vector norm, squared

norm :: (Num v, Floating a, Fold v a) => v -> aSource

vector / L2 / Euclidean norm

normalize :: (Floating a, Num v, Fold v a, Map a a v v) => v -> vSource

normalize v is a unit vector in the direction of v. v is assumed non-null.

cross :: Num a => Vec3 a -> Vec3 a -> Vec3 aSource

3d cross product.

homPoint :: (Snoc v a v', Num a) => v -> v'Source

lift a point into homogenous coordinates

homVec :: (Snoc v a v', Num a) => v -> v'Source

point-at-infinity in homogenous coordinates

project :: (Reverse' () t1 v', Fractional t1, Vec a t t1, Reverse' () v (t :. t1)) => v -> v'Source

project a vector from homogenous coordinates. Last vector element is assumed non-zero.

multvm :: (Transpose m mt, Map v a mt v', Fold v a, Num a, Num v) => v -> m -> v'Source

row vector * matrix

multmv :: (Map v a m v', Num v, Fold v a, Num a) => m -> v -> v'Source

matrix * column vector

multmm :: (Map v v' m1 m3, Map v a b v', Transpose m2 b, Fold v a, Num v, Num a) => m1 -> m2 -> m3Source

matrix * matrix

translate :: (Transpose m mt, Reverse' () mt (v' :. t), Reverse' (v' :. ()) t v'1, Transpose v'1 m, Num v', Num a, Snoc v a v') => v -> m -> mSource

apply a translation to a projective transformation matrix

column :: (Transpose m mt, Access n v mt) => n -> m -> vSource

get the n-th column as a vector. n is a type-level natural.

row :: Access n a v => n -> v -> aSource

get the n-th row as a vector. n is a type-level natural.

class Transpose a b | a -> b, b -> a whereSource

matrix transposition

Methods

transpose :: a -> bSource

Instances

Transpose () () 
(Vec (Succ n) s (:. s ra), Vec (Succ m) (:. s ra) (:. (:. s ra) a), Vec (Succ m) s (:. s rb), Vec (Succ n) (:. s rb) (:. (:. s rb) b), Transpose' (:. (:. s ra) a) (:. (:. s rb) b)) => Transpose (:. (:. s ra) a) (:. (:. s rb) b) 

scale :: (GetDiagonal' N0 () m r, Num r, Vec n a r, Vec n r m, SetDiagonal' N0 r m) => r -> m -> mSource

scale v m multiplies the diagonal of matrix m by the vector s, component-wise. So scale 5 m multiplies the diagonal by 5, whereas scale 2:.1 m only scales the x component.

diagonal :: (Vec n a v, Vec n v m, SetDiagonal v m, Num m) => v -> mSource

diagonal v is a square matrix with the vector v as the diagonal, and 0 elsewhere.

identity :: (Vec n a v, Vec n v m, Num v, Num m, SetDiagonal v m) => mSource

identity matrix (square)

det :: forall n a r m. (Vec n a r, Vec n r m, Det' m a) => m -> aSource

Determinant by minor expansion, i.e. Laplace's formula. Unfolds into a closed form expression. This should be the fastest way for 4x4 and smaller, but snd . gaussElim works too.

cramer'sRule :: (Map a a1 b1 v, Transpose w b1, ZipWith a2 b vv v m w, ReplConsec' a2 () b vv, Vec n b vv, Vec n a2 b, Fractional a1, Det' m a1, Det' a a1) => m -> v -> vSource

cramer'sRule m v computes the solution to m`multmv`x=v using the eponymous method. For larger than 3x3 you will want to use solve, which uses gaussElim. Cramer's rule, however, unfolds into a closed-form expression, with no branches or allocations (other than the result). You may need to increase the unfolding threshold to see this.

class GaussElim a m | m -> a whereSource

Gaussian elimination, adapted from Mirko Rahn: http://www.haskell.org/pipermail/glasgow-haskell-users/2007-May/012648.html

This is more of a proof of concept. Using a foreign C function will run slightly faster, and compile much faster. But where is the fun in that? Set your unfolding threshold as high as possible.

Methods

gaussElim :: m -> (m, a)Source

gaussElim m returns a pair (m',d) where m' is m in row echelon form and d is the determinant of m. The determinant of m' is 1 or 0, i.e., the leading coefficient of each non-zero row is 1.

Instances

(Fractional a, Map (:. a r) r (:. (:. a r) rs) rs_, Map r (:. a r) rs_ (:. (:. a r) rs), Pivot a (:. (:. a r) (:. (:. a r) rs)), GaussElim a rs_) => GaussElim a (:. (:. a r) (:. (:. a r) rs)) 
(Num a, Pivot a (:. r ())) => GaussElim a (:. r ()) 

invert :: forall n a r m r' m'. (Num r, Num m, Vec n a r, Vec n r m, Append r r r', ZipWith r r r' m m m', Drop n r' r, Map r' r m' m, SetDiagonal r m, GaussElim a m', BackSubstitute m') => m -> Maybe mSource

invert m returns Just the inverse of m or Nothing if m is singular.

invertAndDet :: forall n a r m r' m'. (Num a, Num r, Num m, Vec n a r, Vec n r m, Append r r r', ZipWith r r r' m m m', Drop n r' r, Map r' r m' m, SetDiagonal r m, GaussElim a m', BackSubstitute m') => m -> (m, a)Source

inverse and determinant. If det = 0, inverted matrix is garbage.

solve :: forall n a v r m r' m'. (Num r, Num m, Vec n a r, Vec n r m, Snoc r a r', ZipWith r a r' m r m', Drop n r' (a :. ()), Map r' a m' r, GaussElim a m', BackSubstitute m') => m -> r -> Maybe rSource

Solution of linear system by Gaussian elimination. Returns Nothing if no solution.

translation :: Num a => Vec3 a -> Mat44 aSource

A 4x4 translation matrix

rotationXSource

Arguments

:: Floating a 
=> a

The angle in radians

-> Mat44 a 

A 4x4 rotation matrix for a rotation around the X axis

rotationYSource

Arguments

:: Floating a 
=> a

The angle in radians

-> Mat44 a 

A 4x4 rotation matrix for a rotation around the Y axis

rotationZSource

Arguments

:: Floating a 
=> a

The angle in radians

-> Mat44 a 

A 4x4 rotation matrix for a rotation around the Z axis

rotationVecSource

Arguments

:: Floating a 
=> Vec3 a

The normalized vector around which the rotation goes

-> a

The angle in radians

-> Mat44 a 

A 4x4 rotation matrix for a rotation around an arbitrary normalized vector

rotationEuler :: Floating a => Vec3 a -> Mat44 aSource

A 4x4 rotation matrix from the euler angles yaw pitch and roll. Could be useful in e.g. first person shooter games,

rotationQuatSource

Arguments

:: Num a 
=> Vec4 a

The quaternion with the real part (w) last

-> Mat44 a 

A 4x4 rotation matrix from a normalized quaternion. Useful for most free flying rotations, such as airplanes.

rotationLookAtSource

Arguments

:: Floating a 
=> Vec3 a

The up direction, not necessary unit length or perpendicular to the view vector

-> Vec3 a

The viewers position

-> Vec3 a

The point to look at

-> Mat44 a 

A 4x4 rotation matrix for turning toward a point. Useful for targeting a camera to a specific point.

scaling :: Num a => Vec3 a -> Mat44 aSource

A 4x4 scaling matrix

perspectiveSource

Arguments

:: Floating a 
=> a

Near plane clipping distance (always positive)

-> a

Far plane clipping distance (always positive)

-> a

Field of view of the y axis, in radians

-> a

Aspect ratio, i.e. screen's width/height

-> Mat44 a 

A perspective projection matrix for a right handed coordinate system looking down negative z. This will project far plane to z = +1 and near plane to z = -1, i.e. into a left handed system.

orthogonalSource

Arguments

:: Fractional a 
=> a

Near plane clipping distance

-> a

Far plane clipping distance

-> Vec2 a

The size of the view (center aligned around origo)

-> Mat44 a 

An orthogonal projection matrix for a right handed coordinate system looking down negative z. This will project far plane to z = +1 and near plane to z = -1, i.e. into a left handed system.