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

Safe HaskellNone
LanguageHaskell98

Data.Vect.Floating.Base

Synopsis

Documentation

class AbelianGroup g where Source

Methods

(&+) :: g -> g -> g infixl 6 Source

(&-) :: g -> g -> g infixl 6 Source

neg :: g -> g Source

zero :: g Source

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

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 where Source

Minimal complete definition

lmul

Methods

lmul :: r -> m -> m Source

(*.) :: r -> m -> m infixr 7 Source

Instances

class RightModule m r | m -> r, r -> m where Source

Minimal complete definition

rmul

Methods

rmul :: m -> r -> m Source

(.*) :: m -> r -> m infixl 7 Source

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 where Source

Minimal complete definition

mapVec, scalarMul

Methods

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

scalarMul :: a -> v a -> v a Source

(*&) :: a -> v a -> v a infixr 7 Source

(&*) :: v a -> a -> v a infixl 7 Source

class Floating a => DotProd a v where Source

Minimal complete definition

(&.)

Methods

(&.) :: v a -> v a -> a infix 7 Source

norm :: v a -> a Source

normsqr :: v a -> a Source

len :: v a -> a Source

lensqr :: v a -> a Source

dotprod :: v a -> v a -> a Source

class CrossProd v where Source

Cross product

Minimal complete definition

crossprod

Methods

crossprod :: v -> v -> v Source

(&^) :: v -> v -> v infix 7 Source

Instances

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

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

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

the angle between two vectors

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

the angle between two unit vectors

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

Minimal complete definition

mkNormal, toNormalUnsafe, fromNormal

Methods

mkNormal Source

Arguments

:: v a 
-> u a

normalizes the input

toNormalUnsafe Source

Arguments

:: v a 
-> u a

does not normalize the input!

fromNormal :: u a -> v a Source

fromNormalRadius :: a -> u a -> v a Source

class Pointwise v where Source

Pointwise multiplication

Minimal complete definition

pointwise

Methods

pointwise :: v -> v -> v Source

(&!) :: v -> v -> v infix 7 Source

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 where Source

conversion between vectors (and matrices) of different dimensions

Methods

extendZero Source

Arguments

:: u a 
-> v a

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

extendWith Source

Arguments

:: a 
-> u a 
-> v a

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

trim Source

Arguments

:: v a 
-> u a

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

class HasCoordinates v x | v -> x where Source

Minimal complete definition

Nothing

Methods

_1 :: v -> x Source

_2 :: v -> x Source

_3 :: v -> x Source

_4 :: v -> x Source

class Dimension a where Source

Methods

dim :: a -> Int Source

class Matrix m where Source

Methods

transpose :: m -> m Source

inverse :: m -> m Source

idmtx :: m Source

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 where Source

Outer product (could be unified with Diagonal?)

Methods

outer :: v -> v -> t Source

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 where Source

makes a diagonal matrix from a vector

Methods

diag :: s -> t Source

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 where Source

Methods

det :: m -> a Source

Instances

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

Methods

fromOrtho :: o a -> m a Source

toOrthoUnsafe :: m a -> o a Source

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 where Source

"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 a Source

toProjectiveUnsafe :: m a -> p a Source

orthogonal :: o a -> p a Source

linear :: n a -> p a Source

translation :: v a -> p a Source

scaling :: v a -> p a Source

class (AbelianGroup m, Matrix m) => MatrixNorms a m where Source

Minimal complete definition

frobeniusNorm

Methods

frobeniusNorm Source

Arguments

:: m 
-> a

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

matrixDistance Source

Arguments

:: m 
-> m 
-> a

euclidean distance in the space of matrices

operatorNorm Source

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

Floating a => DotProd a Vec4 
Floating a => Vector a Vec4 
Floating a => Extend a Vec3 Vec4 
Floating a => Extend a Vec2 Vec4 
Floating a => UnitVector a Vec4 Normal4 
Floating a => Interpolate a (Vec4 a) 
Read a => Read (Vec4 a) 
Show a => Show (Vec4 a) 
(Floating a, Storable a) => Storable (Vec4 a) 
(Floating a, Random a) => Random (Vec4 a) 
Floating a => Dimension (Vec4 a) 
Num a => Pointwise (Vec4 a) 
Floating a => AbelianGroup (Vec4 a) 
Floating a => HasCoordinates (Vec4 a) a 
Floating a => Tensor (Mat4 a) (Vec4 a) 
Floating a => Diagonal (Vec4 a) (Mat4 a) 
Floating a => HasCoordinates (Mat4 a) (Vec4 a) 
Floating a => RightModule (Vec4 a) (Mat4 a) 
Floating a => LeftModule (Mat4 a) (Vec4 a) 
Floating a => GramSchmidt (Vec4 a, Vec4 a) 
Typeable (* -> *) Vec4 
Floating a => GramSchmidt (Vec4 a, Vec4 a, Vec4 a) 
Floating a => GramSchmidt (Vec4 a, Vec4 a, Vec4 a, Vec4 a) 

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 a Source

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

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

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

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

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 a Source

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

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

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 a Source

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 a Source