simple-affine-space-0.2: A simple library for affine and vector spaces.
Copyright(c) Antony Courtney and Henrik Nilsson Yale University 2003
LicenseBSD-style (see the LICENSE file in the distribution)
Maintainerivan.perez@keera.co.uk
Stabilityprovisional
Portabilitynon-portable (GHC extensions)
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.VectorSpace

Description

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

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.

Minimal complete definition

zeroVector, (*^), (^+^), dot

Methods

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.

norm :: v -> a Source #

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.

default norm :: Floating a => v -> a Source #

normalize :: v -> v Source #

Return a vector with the same origin and orientation (angle), but such that the norm is one (the unit for multiplication by a scalar).

default normalize :: (Eq a, Floating a) => v -> v Source #

Instances

Instances details
VectorSpace Double Double Source #

Vector space instance for Doubles, with Double scalars.

Instance details

Defined in Data.VectorSpace

VectorSpace Float Float Source #

Vector space instance for Floats, with Float scalars.

Instance details

Defined in Data.VectorSpace

RealFloat a => VectorSpace (Vector2 a) a Source # 
Instance details

Defined in Data.Vector2

RealFloat a => VectorSpace (Vector3 a) a Source # 
Instance details

Defined in Data.Vector3

(Eq a, Floating a) => VectorSpace (a, a) a Source #

Vector space instance for pairs of Floating point numbers.

Instance details

Defined in Data.VectorSpace

Methods

zeroVector :: (a, a) Source #

(*^) :: a -> (a, a) -> (a, a) Source #

(^/) :: (a, a) -> a -> (a, a) Source #

(^+^) :: (a, a) -> (a, a) -> (a, a) Source #

(^-^) :: (a, a) -> (a, a) -> (a, a) Source #

negateVector :: (a, a) -> (a, a) Source #

dot :: (a, a) -> (a, a) -> a Source #

norm :: (a, a) -> a Source #

normalize :: (a, a) -> (a, a) Source #

(Eq a, Floating a) => VectorSpace (a, a, a) a Source #

Vector space instance for triplets of Floating point numbers.

Instance details

Defined in Data.VectorSpace

Methods

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 #

norm :: (a, a, a) -> a Source #

normalize :: (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 Floating point numbers.

Instance details

Defined in Data.VectorSpace

Methods

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 #

norm :: (a, a, a, a) -> a Source #

normalize :: (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 Floating point numbers.

Instance details

Defined in Data.VectorSpace

Methods

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 #

norm :: (a, a, a, a, a) -> a Source #

normalize :: (a, a, a, a, a) -> (a, a, a, a, a) Source #