vect-0.4.0: A low-dimensional linear algebra library, tailored to computer graphics.Source codeContentsIndex
Data.Vect.Float.Base
Synopsis
class AbelianGroup g where
(&+) :: g -> g -> g
(&-) :: g -> g -> g
neg :: g -> g
zero :: g
vecSum :: AbelianGroup g => [g] -> g
class AbelianGroup r => Ring r where
(.*.) :: r -> r -> r
one :: r
ringProduct :: Ring r => [r] -> r
class LeftModule r m where
lmul :: r -> m -> m
(*.) :: r -> m -> m
class RightModule m r where
rmul :: m -> r -> m
(.*) :: m -> r -> m
class AbelianGroup v => Vector v where
mapVec :: (Float -> Float) -> v -> v
scalarMul :: Float -> v -> v
(*&) :: Float -> v -> v
(&*) :: v -> Float -> v
class DotProd v where
(&.) :: v -> v -> Float
norm :: v -> Float
normsqr :: v -> Float
len :: v -> Float
lensqr :: v -> Float
dotprod :: v -> v -> Float
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
mkNormal :: v -> u
toNormalUnsafe :: v -> u
fromNormal :: u -> v
fromNormalRadius :: Float -> u -> v
project' :: (Vector v, UnitVector v u, DotProd v) => v -> u -> v
projectUnsafe :: (Vector v, DotProd v) => v -> v -> v
project :: (Vector v, DotProd v) => v -> v -> v
flipNormal :: UnitVector v n => n -> n
class CrossProd v where
crossprod :: v -> v -> v
(&^) :: v -> v -> v
class Pointwise v where
pointwise :: v -> v -> v
(&!) :: v -> v -> v
class HasCoordinates v x | v -> x where
_1 :: v -> x
_2 :: v -> x
_3 :: v -> x
_4 :: v -> x
class Extend u v where
extendZero :: u -> v
extendWith :: Float -> u -> v
trim :: v -> u
class Diagonal s t | t -> s where
diag :: s -> t
class Matrix m where
transpose :: m -> m
inverse :: m -> m
idmtx :: m
class Tensor t v | t -> v where
outer :: v -> v -> t
class Determinant m where
det :: m -> Float
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
newtype Normal2 = Normal2 Vec2
newtype Normal3 = Normal3 Vec3
newtype Normal4 = Normal4 Vec4
mkVec2 :: (Float, Float) -> Vec2
mkVec3 :: (Float, Float, Float) -> Vec3
mkVec4 :: (Float, Float, Float, Float) -> Vec4
rndUnit :: (RandomGen g, Random v, Vector v, DotProd v) => g -> (v, g)
Documentation
class AbelianGroup g whereSource
Methods
(&+) :: g -> g -> gSource
(&-) :: g -> g -> gSource
neg :: g -> gSource
zero :: gSource
show/hide Instances
vecSum :: AbelianGroup g => [g] -> gSource
class AbelianGroup r => Ring r whereSource
Methods
(.*.) :: r -> r -> rSource
one :: rSource
show/hide Instances
ringProduct :: Ring r => [r] -> rSource
class LeftModule r m whereSource
Methods
lmul :: r -> m -> mSource
(*.) :: r -> m -> mSource
show/hide Instances
class RightModule m r whereSource
Methods
rmul :: m -> r -> mSource
(.*) :: m -> r -> mSource
show/hide Instances
class AbelianGroup v => Vector v whereSource
Methods
mapVec :: (Float -> Float) -> v -> vSource
scalarMul :: Float -> v -> vSource
(*&) :: Float -> v -> vSource
(&*) :: v -> Float -> vSource
show/hide Instances
class DotProd v whereSource
Methods
(&.) :: v -> v -> FloatSource
norm :: v -> FloatSource
normsqr :: v -> FloatSource
len :: v -> FloatSource
lensqr :: v -> FloatSource
dotprod :: v -> v -> FloatSource
show/hide Instances
normalize :: (Vector v, DotProd v) => v -> vSource
distance :: (Vector v, DotProd v) => v -> v -> FloatSource
angle :: (Vector v, DotProd v) => v -> v -> FloatSource
the angle between two vectors
angle' :: (Vector v, UnitVector v u, DotProd v) => u -> u -> FloatSource
the angle between two unit vectors
class (Vector v, DotProd v) => UnitVector v u | v -> u, u -> v whereSource
Methods
mkNormalSource
:: v
-> unormalizes the input
toNormalUnsafeSource
:: v
-> udoes not normalize the input!
fromNormal :: u -> vSource
fromNormalRadius :: Float -> u -> vSource
show/hide Instances
project' :: (Vector v, UnitVector v u, DotProd v) => v -> u -> vSource
projects the first vector onto the direction of the second (unit) vector
projectUnsafe :: (Vector v, DotProd v) => v -> v -> vSource
direction (second argument) is assumed to be a unit vector!
project :: (Vector v, DotProd v) => v -> v -> vSource
flipNormal :: UnitVector v n => n -> nSource
since unit vectors are not a group, we need a separate function.
class CrossProd v whereSource
Methods
crossprod :: v -> v -> vSource
(&^) :: v -> v -> vSource
show/hide Instances
class Pointwise v whereSource
Methods
pointwise :: v -> v -> vSource
(&!) :: v -> v -> vSource
show/hide Instances
class HasCoordinates v x | v -> x whereSource
Methods
_1 :: v -> xSource
_2 :: v -> xSource
_3 :: v -> xSource
_4 :: v -> xSource
show/hide Instances
class Extend u v whereSource
conversion between vectors (and matrices) of different dimensions
Methods
extendZeroSource
:: u
-> vexample: extendZero (Vec2 5 6) = Vec4 5 6 0 0
extendWithSource
:: Float
-> u
-> vexample: extendWith 1 (Vec2 5 6) = Vec4 5 6 1 1
trimSource
:: v
-> uexample: trim (Vec4 5 6 7 8) = Vec2 5 6
show/hide Instances
class Diagonal s t | t -> s whereSource
makes a diagonal matrix from a vector
Methods
diag :: s -> tSource
show/hide Instances
class Matrix m whereSource
Methods
transpose :: m -> mSource
inverse :: m -> mSource
idmtx :: mSource
show/hide Instances
class Tensor t v | t -> v whereSource
Outer product (could be unified with Diagonal?)
Methods
outer :: v -> v -> tSource
show/hide Instances
class Determinant m whereSource
Methods
det :: m -> FloatSource
show/hide Instances
data Vec2 Source
Constructors
Vec2 !Float !Float
show/hide Instances
data Vec3 Source
Constructors
Vec3 !Float !Float !Float
show/hide Instances
data Vec4 Source
Constructors
Vec4 !Float !Float !Float !Float
show/hide Instances
data Mat2 Source
these are row vectors
Constructors
Mat2 !Vec2 !Vec2
show/hide Instances
data Mat3 Source
Constructors
Mat3 !Vec3 !Vec3 !Vec3
show/hide Instances
data Mat4 Source
Constructors
Mat4 !Vec4 !Vec4 !Vec4 !Vec4
show/hide Instances
newtype Normal2 Source
The assumption when dealing with these is always that they are of unit length. Also, interpolation works differently.
Constructors
Normal2 Vec2
show/hide Instances
newtype Normal3 Source
Constructors
Normal3 Vec3
show/hide Instances
newtype Normal4 Source
Constructors
Normal4 Vec4
show/hide Instances
mkVec2 :: (Float, Float) -> Vec2Source
mkVec3 :: (Float, Float, Float) -> Vec3Source
mkVec4 :: (Float, Float, Float, Float) -> Vec4Source
rndUnit :: (RandomGen g, Random v, Vector v, DotProd v) => g -> (v, g)Source
Produced by Haddock version 2.4.2