Copyright | (c) Antony Courtney and Henrik Nilsson Yale University 2003 |
---|---|
License | BSD-style (see the LICENSE file in the distribution) |
Maintainer | ivan.perez@keera.co.uk |
Stability | provisional |
Portability | non-portable (GHC extensions) |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Vector space type relation and basic instances.
There can be other implementations of VectorSpace, for example you could implement it with linear like this:
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} import FRP.Yampa import Linear as L instance (Eq a, Floating a) => VectorSpace (V2 a) a where zeroVector = L.zero (*^) = (L.*^) (^) = (L.^) negateVector = L.negated (^+^) = (L.^+^) (^-^) = (L.^-^) dot = L.dot
Using this you could benefit from more advanced vector operators and the improved performance linear brings while keeping a simple type class interface with few dependencies.
Synopsis
- class VectorSpace v a | v -> a where
- zeroVector :: v
- (*^) :: a -> v -> v
- (^/) :: v -> a -> v
- (^+^) :: v -> v -> v
- (^-^) :: v -> v -> v
- negateVector :: v -> v
- dot :: v -> v -> a
- norm :: v -> a
- normalize :: v -> v
Documentation
class VectorSpace v a | v -> a where Source #
Vector space type relation.
A vector space is a set (type) closed under addition and multiplication by
a scalar. The type of the scalar is the field of the vector space, and
it is said that v
is a vector space over a
.
The encoding uses a type class |VectorSpace| v a
, where v
represents
the type of the vectors and a
represents the types of the scalars.
zeroVector, (*^), (^+^), dot
zeroVector :: v Source #
Vector with no magnitude (unit for addition).
(*^) :: a -> v -> v infixr 9 Source #
Multiplication by a scalar.
(^/) :: v -> a -> v infixl 9 Source #
Division by a scalar.
default (^/) :: Fractional a => v -> a -> v Source #
(^+^) :: v -> v -> v infixl 6 Source #
Vector addition
(^-^) :: v -> v -> v infixl 6 Source #
Vector subtraction
negateVector :: v -> v Source #
Vector negation. Addition with a negated vector should be same as subtraction.
default negateVector :: Num a => v -> v Source #
dot :: v -> v -> a infix 7 Source #
Dot product (also known as scalar or inner product).
For two vectors, mathematically represented as a = a1,a2,...,an
and b
= b1,b2,...,bn
, the dot product is a . b = a1*b1 + a2*b2 + ... +
an*bn
.
Some properties are derived from this. The dot product of a vector with
itself is the square of its magnitude (norm
), and the dot product of
two orthogonal vectors is zero.
Vector's norm (also known as magnitude).
For a vector represented mathematically as a = a1,a2,...,an
, the norm
is the square root of a1^2 + a2^2 + ... + an^2
.
Return a vector with the same origin and orientation (angle), but such that the norm is one (the unit for multiplication by a scalar).
Instances
VectorSpace Double Double Source # | |
Defined in Data.VectorSpace zeroVector :: Double Source # (*^) :: Double -> Double -> Double Source # (^/) :: Double -> Double -> Double Source # (^+^) :: Double -> Double -> Double Source # (^-^) :: Double -> Double -> Double Source # negateVector :: Double -> Double Source # dot :: Double -> Double -> Double Source # | |
VectorSpace Float Float Source # | |
Defined in Data.VectorSpace | |
RealFloat a => VectorSpace (Vector2 a) a Source # | |
Defined in Data.Vector2 zeroVector :: Vector2 a Source # (*^) :: a -> Vector2 a -> Vector2 a Source # (^/) :: Vector2 a -> a -> Vector2 a Source # (^+^) :: Vector2 a -> Vector2 a -> Vector2 a Source # (^-^) :: Vector2 a -> Vector2 a -> Vector2 a Source # negateVector :: Vector2 a -> Vector2 a Source # dot :: Vector2 a -> Vector2 a -> a Source # | |
RealFloat a => VectorSpace (Vector3 a) a Source # | |
Defined in Data.Vector3 zeroVector :: Vector3 a Source # (*^) :: a -> Vector3 a -> Vector3 a Source # (^/) :: Vector3 a -> a -> Vector3 a Source # (^+^) :: Vector3 a -> Vector3 a -> Vector3 a Source # (^-^) :: Vector3 a -> Vector3 a -> Vector3 a Source # negateVector :: Vector3 a -> Vector3 a Source # dot :: Vector3 a -> Vector3 a -> a Source # | |
(Eq a, Floating a) => VectorSpace (a, a) a Source # | Vector space instance for pairs of |
(Eq a, Floating a) => VectorSpace (a, a, a) a Source # | Vector space instance for triplets of |
Defined in Data.VectorSpace zeroVector :: (a, a, a) Source # (*^) :: a -> (a, a, a) -> (a, a, a) Source # (^/) :: (a, a, a) -> a -> (a, a, a) Source # (^+^) :: (a, a, a) -> (a, a, a) -> (a, a, a) Source # (^-^) :: (a, a, a) -> (a, a, a) -> (a, a, a) Source # negateVector :: (a, a, a) -> (a, a, a) Source # dot :: (a, a, a) -> (a, a, a) -> a Source # | |
(Eq a, Floating a) => VectorSpace (a, a, a, a) a Source # | Vector space instance for tuples with four |
Defined in Data.VectorSpace zeroVector :: (a, a, a, a) Source # (*^) :: a -> (a, a, a, a) -> (a, a, a, a) Source # (^/) :: (a, a, a, a) -> a -> (a, a, a, a) Source # (^+^) :: (a, a, a, a) -> (a, a, a, a) -> (a, a, a, a) Source # (^-^) :: (a, a, a, a) -> (a, a, a, a) -> (a, a, a, a) Source # negateVector :: (a, a, a, a) -> (a, a, a, a) Source # dot :: (a, a, a, a) -> (a, a, a, a) -> a Source # | |
(Eq a, Floating a) => VectorSpace (a, a, a, a, a) a Source # | Vector space instance for tuples with five |
Defined in Data.VectorSpace zeroVector :: (a, a, a, a, a) Source # (*^) :: a -> (a, a, a, a, a) -> (a, a, a, a, a) Source # (^/) :: (a, a, a, a, a) -> a -> (a, a, a, a, a) Source # (^+^) :: (a, a, a, a, a) -> (a, a, a, a, a) -> (a, a, a, a, a) Source # (^-^) :: (a, a, a, a, a) -> (a, a, a, a, a) -> (a, a, a, a, a) Source # negateVector :: (a, a, a, a, a) -> (a, a, a, a, a) Source # dot :: (a, a, a, a, a) -> (a, a, a, a, a) -> a Source # |