| 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 | Safe | 
| Language | Haskell2010 | 
Data.VectorSpace
Description
Vector space type relation and basic instances.
 Heavily inspired by Yampa's FRP.Yampa.VectorSpace module.
- class Num (Groundring v) => RModule v where- type Groundring v
 
- class (Fractional (Groundring v), RModule v) => VectorSpace v where
- type family Groundfield v :: *
- class RModule v => InnerProductSpace v where
- class RModule v => NormedSpace v where
Documentation
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 
Minimal complete definition
Associated Types
type Groundring v Source #
Methods
zeroVector :: v Source #
(*^) :: Groundring v -> v -> v infixr 6 Source #
(^*) :: v -> Groundring v -> v Source #
negateVector :: v -> v Source #
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.
Methods
(^/) :: v -> Groundfield v -> v infixl 6 Source #
type family Groundfield 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.
Instances
| type Groundfield v Source # | |
class RModule v => InnerProductSpace v where Source #
An inner product space is a module with an inner product,
   i.e. a map dot satisfying
Minimal complete definition
Methods
dot :: v -> v -> Groundfield v infix 6 Source #
class RModule 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)
Minimal complete definition
Methods
norm :: v -> Groundfield v Source #