vect-0.4.6: A low-dimensional linear algebra library, tailored to computer graphics.

Data.Vect.Double.Base

Synopsis

Documentation

vecSum :: AbelianGroup g => [g] -> gSource

class LeftModule r m whereSource

Methods

lmul :: r -> m -> mSource

(*.) :: r -> m -> mSource

class RightModule m r whereSource

Methods

rmul :: m -> r -> mSource

(.*) :: m -> r -> mSource

class AbelianGroup v => Vector v whereSource

Methods

mapVec :: (Double -> Double) -> v -> vSource

scalarMul :: Double -> v -> vSource

(*&) :: Double -> v -> vSource

(&*) :: v -> Double -> vSource

class CrossProd v whereSource

Cross product

Methods

crossprod :: v -> v -> vSource

(&^) :: v -> v -> vSource

normalize :: (Vector v, DotProd v) => v -> vSource

distance :: (Vector v, DotProd v) => v -> v -> DoubleSource

angle :: (Vector v, DotProd v) => v -> v -> DoubleSource

the angle between two vectors

angle' :: (Vector v, UnitVector v u, DotProd v) => u -> u -> DoubleSource

the angle between two unit vectors

class (Vector v, DotProd v) => UnitVector v u | v -> u, u -> v whereSource

Methods

mkNormalSource

Arguments

:: v 
-> u

normalizes the input

toNormalUnsafeSource

Arguments

:: v 
-> u

does not normalize the input!

fromNormal :: u -> vSource

fromNormalRadius :: Double -> u -> vSource

class Pointwise v whereSource

Pointwise multiplication

Methods

pointwise :: v -> v -> vSource

(&!) :: v -> v -> vSource

class Extend u v whereSource

conversion between vectors (and matrices) of different dimensions

Methods

extendZeroSource

Arguments

:: u 
-> v

example: extendZero (Vec2 5 6) = Vec4 5 6 0 0

extendWithSource

Arguments

:: Double 
-> u 
-> v

example: extendWith 1 (Vec2 5 6) = Vec4 5 6 1 1

trimSource

Arguments

:: v 
-> u

example: trim (Vec4 5 6 7 8) = Vec2 5 6

class Tensor t v | t -> v whereSource

Outer product (could be unified with Diagonal?)

Methods

outer :: v -> v -> tSource

class Diagonal s t | t -> s whereSource

makes a diagonal matrix from a vector

Methods

diag :: s -> tSource

class Matrix m => Orthogonal m o | m -> o, o -> m whereSource

Methods

fromOrtho :: o -> mSource

toOrthoUnsafe :: m -> oSource

class (Vector v, Orthogonal n o, Diagonal v n) => Projective v n o m p | m -> p, p -> m, p -> o, o -> p, p -> n, n -> p, p -> v, v -> p, n -> o, n -> v, v -> n whereSource

"Projective" matrices have the following form: the top left corner is an any matrix, the bottom right corner is 1, and the top-right column is zero. These describe the affine orthogonal transformation of the space one dimension less.

class (AbelianGroup m, Matrix m) => MatrixNorms m whereSource

Methods

frobeniusNormSource

Arguments

:: m 
-> Double

the frobenius norm (= euclidean norm in the space of matrices)

matrixDistanceSource

Arguments

:: m 
-> m 
-> Double

euclidean distance in the space of matrices

operatorNormSource

Arguments

:: m 
-> Double

(euclidean) operator norm (not implemented yet)

data Ortho2 Source

Orthogonal matrices.

Note: the Random instances generates orthogonal matrices with determinant 1 (that is, orientation-preserving orthogonal transformations)!

data Normal2 Source

The assumption when dealing with these is always that they are of unit length. Also, interpolation works differently.

data Proj3 Source

Projective matrices, encoding affine transformations in dimension one less.

project :: (Vector v, DotProd v) => v -> v -> vSource

project' :: (Vector v, UnitVector v u, DotProd v) => v -> u -> vSource

Projects the first vector down to the hyperplane orthogonal to the second (unit) vector

projectUnsafe :: (Vector v, DotProd v) => v -> v -> vSource

Direction (second argument) is assumed to be a unit vector!

flipNormal :: UnitVector v n => n -> nSource

Since unit vectors are not a group, we need a separate function.

householder :: (Vector v, UnitVector v u, Matrix m, Vector m, Tensor m v) => u -> mSource

Householder matrix, see http://en.wikipedia.org/wiki/Householder_transformation. In plain words, it is the reflection to the hyperplane orthogonal to the input vector.

householderOrtho :: (Vector v, UnitVector v u, Matrix m, Vector m, Tensor m v, Orthogonal m o) => u -> oSource