Data.Vect.Double.Base
- class AbelianGroup g where
- vecSum :: AbelianGroup g => [g] -> g
- class MultSemiGroup r where
- class (AbelianGroup r, MultSemiGroup r) => Ring r
- semigroupProduct :: MultSemiGroup r => [r] -> r
- class LeftModule r m where
- class RightModule m r where
- class AbelianGroup v => Vector v where
- class DotProd v where
- class CrossProd v where
- normalize :: (Vector v, DotProd v) => v -> v
- distance :: (Vector v, DotProd v) => v -> v -> Double
- angle :: (Vector v, DotProd v) => v -> v -> Double
- angle' :: (Vector v, UnitVector v u, DotProd v) => u -> u -> Double
- class (Vector v, DotProd v) => UnitVector v u | v -> u, u -> v where
- mkNormal :: v -> u
- toNormalUnsafe :: v -> u
- fromNormal :: u -> v
- fromNormalRadius :: Double -> u -> v
- class Pointwise v where
- class Extend u v where
- extendZero :: u -> v
- extendWith :: Double -> u -> v
- trim :: v -> u
- class HasCoordinates v x | v -> x where
- class Dimension a where
- class Matrix m where
- class Tensor t v | t -> v where
- outer :: v -> v -> t
- class Diagonal s t | t -> s where
- diag :: s -> t
- class Determinant m where
- class Matrix m => Orthogonal m o | m -> o, o -> m where
- fromOrtho :: o -> m
- toOrthoUnsafe :: m -> o
- 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 where
- fromProjective :: p -> m
- toProjectiveUnsafe :: m -> p
- orthogonal :: o -> p
- linear :: n -> p
- translation :: v -> p
- scaling :: v -> p
- class (AbelianGroup m, Matrix m) => MatrixNorms m where
- frobeniusNorm :: m -> Double
- matrixDistance :: m -> m -> Double
- operatorNorm :: m -> Double
- data Vec2 = Vec2 !Double !Double
- data Vec3 = Vec3 !Double !Double !Double
- data Vec4 = Vec4 !Double !Double !Double !Double
- data Mat2 = Mat2 !Vec2 !Vec2
- data Mat3 = Mat3 !Vec3 !Vec3 !Vec3
- data Mat4 = Mat4 !Vec4 !Vec4 !Vec4 !Vec4
- data Ortho2
- data Ortho3
- data Ortho4
- data Normal2
- data Normal3
- data Normal4
- data Proj3
- data Proj4
- mkVec2 :: (Double, Double) -> Vec2
- mkVec3 :: (Double, Double, Double) -> Vec3
- mkVec4 :: (Double, Double, Double, Double) -> Vec4
- project :: (Vector v, DotProd v) => v -> v -> v
- project' :: (Vector v, UnitVector v u, DotProd v) => v -> u -> v
- projectUnsafe :: (Vector v, DotProd v) => v -> v -> v
- flipNormal :: UnitVector v n => n -> n
- householder :: (Vector v, UnitVector v u, Matrix m, Vector m, Tensor m v) => u -> m
- householderOrtho :: (Vector v, UnitVector v u, Matrix m, Vector m, Tensor m v, Orthogonal m o) => u -> o
Documentation
class AbelianGroup g whereSource
vecSum :: AbelianGroup g => [g] -> gSource
class MultSemiGroup r whereSource
class (AbelianGroup r, MultSemiGroup r) => Ring r Source
semigroupProduct :: MultSemiGroup r => [r] -> rSource
class LeftModule r m whereSource
class RightModule m r whereSource
Instances
class AbelianGroup v => Vector v whereSource
Cross product
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
Arguments
:: v | |
-> u | normalizes the input |
Arguments
:: v | |
-> u | does not normalize the input! |
fromNormal :: u -> vSource
fromNormalRadius :: Double -> u -> vSource
Pointwise multiplication
conversion between vectors (and matrices) of different dimensions
Methods
Arguments
:: u | |
-> v | example: |
Arguments
:: Double | |
-> u | |
-> v | example: |
Arguments
:: v | |
-> u | example: |
class HasCoordinates v x | v -> x whereSource
class Determinant m whereSource
class Matrix m => Orthogonal m o | m -> o, o -> m whereSource
Instances
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.
Methods
fromProjective :: p -> mSource
toProjectiveUnsafe :: m -> pSource
orthogonal :: o -> pSource
translation :: v -> pSource
class (AbelianGroup m, Matrix m) => MatrixNorms m whereSource
Methods
Arguments
:: m | |
-> Double | the frobenius norm (= euclidean norm in the space of matrices) |
Arguments
:: m | |
-> m | |
-> Double | euclidean distance in the space of matrices |
Arguments
:: m | |
-> Double | (euclidean) operator norm (not implemented yet) |
Instances
Instances
Instances
Instances
The components are row vectors
Instances
Instances
Instances
Orthogonal matrices.
Note: the Random instances generates orthogonal matrices with determinant 1 (that is, orientation-preserving orthogonal transformations)!
The assumption when dealing with these is always that they are of unit length. Also, interpolation works differently.
Projective matrices, encoding affine transformations in dimension one less.
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