linear-1.19: Linear Algebra

LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell98

Linear.Affine

Description

Operations on affine spaces.

Synopsis

Documentation

class Additive (Diff p) => Affine p where Source

An affine space is roughly a vector space in which we have forgotten or at least pretend to have forgotten the origin.

a .+^ (b .-. a)  =  b@
(a .+^ u) .+^ v  =  a .+^ (u ^+^ v)@
(a .-. b) ^+^ v  =  (a .+^ v) .-. q@

Minimal complete definition

(.-.), (.+^)

Associated Types

type Diff p :: * -> * Source

Methods

(.-.) :: Num a => p a -> p a -> Diff p a infixl 6 Source

Get the difference between two points as a vector offset.

(.+^) :: Num a => p a -> Diff p a -> p a infixl 6 Source

Add a vector offset to a point.

(.-^) :: Num a => p a -> Diff p a -> p a infixl 6 Source

Subtract a vector offset from a point.

qdA :: (Affine p, Foldable (Diff p), Num a) => p a -> p a -> a Source

Compute the quadrance of the difference (the square of the distance)

distanceA :: (Floating a, Foldable (Diff p), Affine p) => p a -> p a -> a Source

Distance between two points in an affine space

newtype Point f a Source

A handy wrapper to help distinguish points from vectors at the type level

Constructors

P (f a) 

Instances

Monad f => Monad (Point f) 
Functor f => Functor (Point f) 
Applicative f => Applicative (Point f) 
Foldable f => Foldable (Point f) 
Traversable f => Traversable (Point f) 
Generic1 (Point f) 
Distributive f => Distributive (Point f) 
Representable f => Representable (Point f) 
Serial1 f => Serial1 (Point f) 
Apply f => Apply (Point f) 
Bind f => Bind (Point f) 
Eq1 f => Eq1 (Point f) 
Ord1 f => Ord1 (Point f) 
Read1 f => Read1 (Point f) 
Show1 f => Show1 (Point f) 
Additive f => Additive (Point f) 
Metric f => Metric (Point f) 
R1 f => R1 (Point f) 
R2 f => R2 (Point f) 
R3 f => R3 (Point f) 
R4 f => R4 (Point f) 
Additive f => Affine (Point f) 
Eq (f a) => Eq (Point f a) 
Fractional (f a) => Fractional (Point f a) 
(Data (f a), Typeable (* -> *) f, Typeable * a) => Data (Point f a) 
Num (f a) => Num (Point f a) 
Ord (f a) => Ord (Point f a) 
Read (f a) => Read (Point f a) 
Show (f a) => Show (Point f a) 
Ix (f a) => Ix (Point f a) 
Generic (Point f a) 
Storable (f a) => Storable (Point f a) 
Binary (f a) => Binary (Point f a) 
Serial (f a) => Serial (Point f a) 
Serialize (f a) => Serialize (Point f a) 
NFData (f a) => NFData (Point f a) 
Hashable (f a) => Hashable (Point f a) 
Ixed (f a) => Ixed (Point f a) 
Wrapped (Point f a) 
Epsilon (f a) => Epsilon (Point f a) 
Typeable ((* -> *) -> * -> *) Point 
(~) * t (Point g b) => Rewrapped (Point f a) t 
Traversable f => Each (Point f a) (Point f b) a b 
type Rep1 (Point f) 
type Rep (Point f) = Rep f 
type Diff (Point f) = f 
type Rep (Point f a) 
type Index (Point f a) = Index (f a) 
type IxValue (Point f a) = IxValue (f a) 
type Unwrapped (Point f a) = f a 

lensP :: Lens' (Point g a) (g a) Source

_Point :: Iso' (Point f a) (f a) Source

origin :: (Additive f, Num a) => Point f a Source

Vector spaces have origins.

relative :: (Additive f, Num a) => Point f a -> Iso' (Point f a) (f a) Source

An isomorphism between points and vectors, given a reference point.