Copyright | (c) Ivan Perez and Manuel Bärenz |
---|---|
License | See the LICENSE file in the distribution. |
Maintainer | ivan.perez@keera.co.uk |
Stability | provisional |
Portability | non-portable (GHC extensions) |
Safe Haskell | None |
Language | Haskell2010 |
Vector space type relation and basic instances.
Heavily inspired by Yampa's FRP.Yampa.VectorSpace
module.
Synopsis
- class Num (Groundring v) => RModule v where
- type Groundring v
- zeroVector :: v
- (*^) :: Groundring v -> v -> v
- (^*) :: v -> Groundring v -> v
- negateVector :: v -> v
- (^+^) :: v -> v -> v
- (^-^) :: v -> v -> v
- class (Fractional (Groundring v), RModule v) => VectorSpace v where
- (^/) :: v -> Groundfield v -> v
- type Groundfield v = Groundring v
- class RModule v => InnerProductSpace v where
- dot :: v -> v -> Groundfield v
- class (Floating (Groundfield v), InnerProductSpace v, VectorSpace v) => NormedSpace v where
- norm :: v -> Groundfield v
- normalize :: (Eq (Groundfield v), NormedSpace v) => v -> v
- break3Tuple :: (a, b, c) -> ((a, b), c)
- join3Tuple :: ((a, b), c) -> (a, b, c)
- break4Tuple :: (a, b, c, d) -> ((a, b), (c, d))
- join4Tuple :: ((a, b), (c, d)) -> (a, b, c, d)
- break5Tuple :: (a, b, c, d, e) -> ((a, b), (c, d, e))
- join5Tuple :: ((a, b), (c, d, e)) -> (a, b, c, d, e)
- newtype FractionalVectorSpace a = FractionalVectorSpace {
- getFractional :: a
Vector space classes
class Num (Groundring v) => RModule v where Source #
R-modules.
A module v
over a ring Groundring v
is an abelian group with a linear multiplication.
The hat ^
denotes the side of an operation
on which the vector stands,
i.e. a *^ v
for v
a vector.
A minimal definition should include the type Groundring
and the
implementations of zeroVector
, ^+^
, and one of *^
or ^*
.
The following laws must be satisfied:
v1 ^+^ v2 == v2 ^+^ v1
a *^ zeroVector == zeroVector
- @a *^ (v1 ^+^ v2) == a *^ v1 ^+^ a*^ v2
a *^ v == v ^* a
negateVector v == (-1) *^ v
v1 ^-^ v2 == v1 ^+^ negateVector v2
type Groundring v Source #
zeroVector :: v Source #
(*^) :: Groundring v -> v -> v infixr 6 Source #
(^*) :: v -> Groundring v -> v Source #
negateVector :: v -> v Source #
Instances
class (Fractional (Groundring v), RModule v) => VectorSpace v where Source #
A vector space is a module over a field, i.e. a commutative ring with inverses.
It needs to satisfy the axiom
v ^ a == (1a) *^ v
,
which is the default implementation.
Nothing
(^/) :: v -> Groundfield v -> v infixl 6 Source #
Instances
type Groundfield v = Groundring v Source #
The ground ring of a vector space is required to be commutative
and to possess inverses.
It is then called the "ground field".
Commutativity amounts to the law a * b = b * a
,
and the existence of inverses is given
by the requirement of the Fractional
type class.
class RModule v => InnerProductSpace v where Source #
An inner product space is a module with an inner product,
i.e. a map dot
satisfying
dot :: v -> v -> Groundfield v infix 6 Source #
Instances
class (Floating (Groundfield v), InnerProductSpace v, VectorSpace v) => NormedSpace v where Source #
A normed space is a module with a norm,
i.e. a function norm
satisfying
norm (a ^* v) = a ^* norm v
norm (v1 ^+^ v2) <= norm v1 ^+^ norm v2
(the "triangle inequality")
A typical example is sqrt (v
,
for an inner product space.dot
v)
Nothing
norm :: v -> Groundfield v Source #
Instances
normalize :: (Eq (Groundfield v), NormedSpace v) => v -> v Source #
Divides a vector by its norm, resulting in a vector of norm 1. Throws an error on vectors with norm 0.
Utilities to work with n-tuples for n = 3, 4, 5
break3Tuple :: (a, b, c) -> ((a, b), c) Source #
join3Tuple :: ((a, b), c) -> (a, b, c) Source #
break4Tuple :: (a, b, c, d) -> ((a, b), (c, d)) Source #
join4Tuple :: ((a, b), (c, d)) -> (a, b, c, d) Source #
break5Tuple :: (a, b, c, d, e) -> ((a, b), (c, d, e)) Source #
join5Tuple :: ((a, b), (c, d, e)) -> (a, b, c, d, e) Source #
Vector spaces from arbitrary Fractional
s
newtype FractionalVectorSpace a Source #
Wrap an arbitrary Fractional
in this newtype
in order to get VectorSpace
, and related instances.