|
|
|
|
| Synopsis |
|
| 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 -> Float | | | angle :: (Vector v, DotProd v) => v -> v -> Float | | | angle' :: (Vector v, UnitVector v u, DotProd v) => u -> u -> Float | | | class (Vector v, DotProd v) => UnitVector v u | v -> u, u -> v where | | | | class Pointwise v where | | | | class Extend u v where | | | | class HasCoordinates v x | v -> x where | | _1 :: v -> x | | _2 :: v -> x | | _3 :: v -> x | | _4 :: v -> x |
| | | class Dimension a where | | | | class Matrix m where | | | | class Tensor t v | t -> v where | | | | class Diagonal s t | t -> s where | | | | class Determinant m where | | | | class Matrix m => Orthogonal m o | m -> o, o -> m where | | | | 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 | | | | class (AbelianGroup m, Matrix m) => MatrixNorms m where | | | | data Vec2 = Vec2 !Float !Float | | | data Vec3 = Vec3 !Float !Float !Float | | | data Vec4 = Vec4 !Float !Float !Float !Float | | | 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 :: (Float, Float) -> Vec2 | | | mkVec3 :: (Float, Float, Float) -> Vec3 | | | mkVec4 :: (Float, Float, Float, Float) -> 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 where | Source |
|
| | Methods | | | Instances | |
|
|
|
|
| class MultSemiGroup r where | Source |
|
| | Methods | | | Instances | |
|
|
|
| Instances | |
|
|
|
|
| class LeftModule r m where | Source |
|
| | Methods | | | Instances | |
|
|
| class RightModule m r where | Source |
|
| | Methods | | | Instances | |
|
|
|
| | Methods | | | Instances | |
|
|
|
| | Methods | | | Instances | |
|
|
|
| Cross product
| | | Methods | | crossprod :: v -> v -> v | Source |
| | |
| | Instances | |
|
|
|
|
|
|
|
| the angle between two vectors
|
|
|
| the angle between two unit vectors
|
|
|
| | Methods | | | :: v | | | -> u | normalizes the input
|
| | | | :: v | | | -> u | does not normalize the input!
|
| | | | |
| | Instances | |
|
|
|
| Pointwise multiplication
| | | Methods | | pointwise :: v -> v -> v | Source |
| | |
| | Instances | |
|
|
|
| conversion between vectors (and matrices) of different dimensions
| | | Methods | | | :: u | | | -> v | example: extendZero (Vec2 5 6) = Vec4 5 6 0 0
|
| | | | :: Float | | | -> u | | | -> v | example: extendWith 1 (Vec2 5 6) = Vec4 5 6 1 1
|
| | | | :: v | | | -> u | example: trim (Vec4 5 6 7 8) = Vec2 5 6
|
|
| | Instances | |
|
|
| class HasCoordinates v x | v -> x where | Source |
|
| | Methods | | | Instances | |
|
|
|
| | Methods | | | Instances | |
|
|
|
| | Methods | | | Instances | |
|
|
| class Tensor t v | t -> v where | Source |
|
| Outer product (could be unified with Diagonal?)
| | | Methods | | | Instances | |
|
|
| class Diagonal s t | t -> s where | Source |
|
| makes a diagonal matrix from a vector
| | | Methods | | | Instances | |
|
|
| class Determinant m where | Source |
|
| | Methods | | | Instances | |
|
|
| class Matrix m => Orthogonal m o | m -> o, o -> m where | Source |
|
| | Methods | | | 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 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 -> m | Source |
| | | toProjectiveUnsafe :: m -> p | Source |
| | | | | | | | |
| | Instances | |
|
|
|
| | Methods | | | :: m | | | -> Float | the frobenius norm (= euclidean norm in the space of matrices)
|
| | | | :: m | | | -> m | | | -> Float | euclidean distance in the space of matrices
|
| | | | :: m | | | -> Float | (euclidean) operator norm (not implemented yet)
|
|
| | Instances | |
|
|
|
| Constructors | | Instances | |
|
|
|
| Constructors | | Instances | |
|
|
|
| Constructors | | Instances | |
|
|
|
| The components are row vectors
| | Constructors | | Instances | |
|
|
|
| Constructors | | Instances | |
|
|
|
| Constructors | | Instances | |
|
|
|
Orthogonal matrices.
Note: the Random instances generates orthogonal matrices with determinant 1
(that is, orientation-preserving orthogonal transformations)!
| Instances | |
|
|
|
Instances | |
|
|
|
Instances | |
|
|
|
| The assumption when dealing with these is always that they are of unit length.
Also, interpolation works differently.
| Instances | |
|
|
|
Instances | |
|
|
|
Instances | |
|
|
|
| Projective matrices, encoding affine transformations in dimension one less.
| Instances | |
|
|
|
Instances | |
|
|
|
|
|
|
|
|
|
|
|
| Projects the first vector onto the direction of the second (unit) vector
|
|
|
| Direction (second argument) is assumed to be a unit vector!
|
|
|
| Since unit vectors are not a group, we need a separate function.
|
|
|
| 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.
|
|
|
|
| Produced by Haddock version 2.4.2 |