vect-floating-0.1.0.3: A low-dimensional linear algebra library, operating on the Floating typeclass

Safe HaskellNone

Data.Vect.Floating.Base

Synopsis

Documentation

class AbelianGroup g whereSource

Methods

(&+) :: g -> g -> gSource

(&-) :: g -> g -> gSource

neg :: g -> gSource

zero :: gSource

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

class (AbelianGroup r, MultSemiGroup r) => Ring r Source

Instances

Floating a => Ring (Mat4 a) 
Floating a => Ring (Mat3 a) 
Floating a => Ring (Mat2 a) 

class LeftModule r m whereSource

Methods

lmul :: r -> m -> mSource

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

Instances

class RightModule m r | m -> r, r -> m whereSource

Methods

rmul :: m -> r -> mSource

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

Instances

Floating a => RightModule (Vec4 a) (Mat4 a) 
Floating a => RightModule (Vec3 a) (Mat3 a) 
Floating a => RightModule (Vec2 a) (Mat2 a) 

class AbelianGroup (v a) => Vector a v whereSource

Methods

mapVec :: (a -> a) -> v a -> v aSource

scalarMul :: a -> v a -> v aSource

(*&) :: a -> v a -> v aSource

(&*) :: v a -> a -> v aSource

class Floating a => DotProd a v whereSource

Methods

(&.) :: v a -> v a -> aSource

norm :: v a -> aSource

normsqr :: v a -> aSource

len :: v a -> aSource

lensqr :: v a -> aSource

dotprod :: v a -> v a -> aSource

class CrossProd v whereSource

Cross product

Methods

crossprod :: v -> v -> vSource

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

Instances

normalize :: (Vector a v, DotProd a v) => v a -> v aSource

distance :: (Vector a v, DotProd a v) => v a -> v a -> aSource

angle :: (Vector a v, DotProd a v) => v a -> v a -> aSource

the angle between two vectors

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

the angle between two unit vectors

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

Methods

mkNormalSource

Arguments

:: v a 
-> u a

normalizes the input

toNormalUnsafeSource

Arguments

:: v a 
-> u a

does not normalize the input!

fromNormal :: u a -> v aSource

fromNormalRadius :: a -> u a -> v aSource

class Pointwise v whereSource

Pointwise multiplication

Methods

pointwise :: v -> v -> vSource

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

Instances

Floating a => Pointwise (Mat4 a) 
Floating a => Pointwise (Mat3 a) 
Floating a => Pointwise (Mat2 a) 
Num a => Pointwise (Vec4 a) 
Num a => Pointwise (Vec3 a) 
Floating a => Pointwise (Vec2 a) 

class Extend a u v whereSource

conversion between vectors (and matrices) of different dimensions

Methods

extendZeroSource

Arguments

:: u a 
-> v a

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

extendWithSource

Arguments

:: a 
-> u a 
-> v a

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

trimSource

Arguments

:: v a 
-> u a

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

class HasCoordinates v x | v -> x whereSource

Methods

_1 :: v -> xSource

_2 :: v -> xSource

_3 :: v -> xSource

_4 :: v -> xSource

class Matrix m whereSource

Methods

transpose :: m -> mSource

inverse :: m -> mSource

idmtx :: mSource

Instances

Floating a => Matrix (Proj4 a) 
Floating a => Matrix (Proj3 a) 
Floating a => Matrix (Ortho4 a) 
Floating a => Matrix (Ortho3 a) 
Floating a => Matrix (Ortho2 a) 
Floating a => Matrix (Mat4 a) 
Floating a => Matrix (Mat3 a) 
Floating a => Matrix (Mat2 a) 

class Tensor t v | t -> v whereSource

Outer product (could be unified with Diagonal?)

Methods

outer :: v -> v -> tSource

Instances

Floating a => Tensor (Mat4 a) (Vec4 a) 
Floating a => Tensor (Mat3 a) (Vec3 a) 
Floating a => Tensor (Mat2 a) (Vec2 a) 

class Diagonal s t | t -> s whereSource

makes a diagonal matrix from a vector

Methods

diag :: s -> tSource

Instances

Floating a => Diagonal (Vec4 a) (Mat4 a) 
Floating a => Diagonal (Vec3 a) (Mat3 a) 
Floating a => Diagonal (Vec2 a) (Mat2 a) 

class Determinant a m whereSource

Methods

det :: m -> aSource

Instances

class Matrix (m a) => Orthogonal a m o | m -> o, o -> m whereSource

Methods

fromOrtho :: o a -> m aSource

toOrthoUnsafe :: m a -> o aSource

class (Vector a v, Orthogonal a n o, Diagonal (v a) (n a)) => Projective a 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.

Methods

fromProjective :: p a -> m aSource

toProjectiveUnsafe :: m a -> p aSource

orthogonal :: o a -> p aSource

linear :: n a -> p aSource

translation :: v a -> p aSource

scaling :: v a -> p aSource

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

Methods

frobeniusNormSource

Arguments

:: m 
-> a

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

matrixDistanceSource

Arguments

:: m 
-> m 
-> a

euclidean distance in the space of matrices

operatorNormSource

Arguments

:: m 
-> a

(euclidean) operator norm (not implemented yet)

Instances

data Vec2 a Source

Constructors

Vec2 !a !a 

data Vec3 a Source

Constructors

Vec3 !a !a !a 

data Vec4 a Source

Constructors

Vec4 !a !a !a !a 

Instances

data Mat2 a Source

The components are row vectors

Constructors

Mat2 !(Vec2 a) !(Vec2 a) 

data Mat3 a Source

Constructors

Mat3 !(Vec3 a) !(Vec3 a) !(Vec3 a) 

data Mat4 a Source

Constructors

Mat4 !(Vec4 a) !(Vec4 a) !(Vec4 a) !(Vec4 a) 

data Ortho2 a Source

Orthogonal matrices.

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

data Ortho4 a Source

Instances

data Normal2 a Source

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

data Proj3 a Source

Projective matrices, encoding affine transformations in dimension one less.

Instances

data Proj4 a Source

Instances

mkVec2 :: (a, a) -> Vec2 aSource

mkVec3 :: (a, a, a) -> Vec3 aSource

mkVec4 :: (a, a, a, a) -> Vec4 aSource

project :: (Vector a v, DotProd a v) => v a -> v a -> v aSource

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

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

projectUnsafe :: (Vector a v, DotProd a v) => v a -> v a -> v aSource

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

flipNormal :: UnitVector a v n => n a -> n aSource

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

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

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 a v, UnitVector a v u, Matrix (m a), Vector a m, Tensor (m a) (v a), Orthogonal a m o) => u a -> o aSource