linear-1.20.3: 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.

Instances

Affine [] Source 

Associated Types

type Diff ([] :: * -> *) :: * -> * Source

Methods

(.-.) :: Num a => [a] -> [a] -> Diff [] a Source

(.+^) :: Num a => [a] -> Diff [] a -> [a] Source

(.-^) :: Num a => [a] -> Diff [] a -> [a] Source

Affine Identity Source 

Associated Types

type Diff (Identity :: * -> *) :: * -> * Source

Methods

(.-.) :: Num a => Identity a -> Identity a -> Diff Identity a Source

(.+^) :: Num a => Identity a -> Diff Identity a -> Identity a Source

(.-^) :: Num a => Identity a -> Diff Identity a -> Identity a Source

Affine Complex Source 

Associated Types

type Diff (Complex :: * -> *) :: * -> * Source

Methods

(.-.) :: Num a => Complex a -> Complex a -> Diff Complex a Source

(.+^) :: Num a => Complex a -> Diff Complex a -> Complex a Source

(.-^) :: Num a => Complex a -> Diff Complex a -> Complex a Source

Affine ZipList Source 

Associated Types

type Diff (ZipList :: * -> *) :: * -> * Source

Methods

(.-.) :: Num a => ZipList a -> ZipList a -> Diff ZipList a Source

(.+^) :: Num a => ZipList a -> Diff ZipList a -> ZipList a Source

(.-^) :: Num a => ZipList a -> Diff ZipList a -> ZipList a Source

Affine Maybe Source 

Associated Types

type Diff (Maybe :: * -> *) :: * -> * Source

Methods

(.-.) :: Num a => Maybe a -> Maybe a -> Diff Maybe a Source

(.+^) :: Num a => Maybe a -> Diff Maybe a -> Maybe a Source

(.-^) :: Num a => Maybe a -> Diff Maybe a -> Maybe a Source

Affine IntMap Source 

Associated Types

type Diff (IntMap :: * -> *) :: * -> * Source

Methods

(.-.) :: Num a => IntMap a -> IntMap a -> Diff IntMap a Source

(.+^) :: Num a => IntMap a -> Diff IntMap a -> IntMap a Source

(.-^) :: Num a => IntMap a -> Diff IntMap a -> IntMap a Source

Affine Vector Source 

Associated Types

type Diff (Vector :: * -> *) :: * -> * Source

Methods

(.-.) :: Num a => Vector a -> Vector a -> Diff Vector a Source

(.+^) :: Num a => Vector a -> Diff Vector a -> Vector a Source

(.-^) :: Num a => Vector a -> Diff Vector a -> Vector a Source

Affine V0 Source 

Associated Types

type Diff (V0 :: * -> *) :: * -> * Source

Methods

(.-.) :: Num a => V0 a -> V0 a -> Diff V0 a Source

(.+^) :: Num a => V0 a -> Diff V0 a -> V0 a Source

(.-^) :: Num a => V0 a -> Diff V0 a -> V0 a Source

Affine V1 Source 

Associated Types

type Diff (V1 :: * -> *) :: * -> * Source

Methods

(.-.) :: Num a => V1 a -> V1 a -> Diff V1 a Source

(.+^) :: Num a => V1 a -> Diff V1 a -> V1 a Source

(.-^) :: Num a => V1 a -> Diff V1 a -> V1 a Source

Affine V2 Source 

Associated Types

type Diff (V2 :: * -> *) :: * -> * Source

Methods

(.-.) :: Num a => V2 a -> V2 a -> Diff V2 a Source

(.+^) :: Num a => V2 a -> Diff V2 a -> V2 a Source

(.-^) :: Num a => V2 a -> Diff V2 a -> V2 a Source

Affine V3 Source 

Associated Types

type Diff (V3 :: * -> *) :: * -> * Source

Methods

(.-.) :: Num a => V3 a -> V3 a -> Diff V3 a Source

(.+^) :: Num a => V3 a -> Diff V3 a -> V3 a Source

(.-^) :: Num a => V3 a -> Diff V3 a -> V3 a Source

Affine V4 Source 

Associated Types

type Diff (V4 :: * -> *) :: * -> * Source

Methods

(.-.) :: Num a => V4 a -> V4 a -> Diff V4 a Source

(.+^) :: Num a => V4 a -> Diff V4 a -> V4 a Source

(.-^) :: Num a => V4 a -> Diff V4 a -> V4 a Source

Affine Plucker Source 

Associated Types

type Diff (Plucker :: * -> *) :: * -> * Source

Methods

(.-.) :: Num a => Plucker a -> Plucker a -> Diff Plucker a Source

(.+^) :: Num a => Plucker a -> Diff Plucker a -> Plucker a Source

(.-^) :: Num a => Plucker a -> Diff Plucker a -> Plucker a Source

Affine Quaternion Source 

Associated Types

type Diff (Quaternion :: * -> *) :: * -> * Source

Affine ((->) b) Source 

Associated Types

type Diff ((->) b :: * -> *) :: * -> * Source

Methods

(.-.) :: Num a => (b -> a) -> (b -> a) -> Diff ((->) b) a Source

(.+^) :: Num a => (b -> a) -> Diff ((->) b) a -> b -> a Source

(.-^) :: Num a => (b -> a) -> Diff ((->) b) a -> b -> a Source

Ord k => Affine (Map k) Source 

Associated Types

type Diff (Map k :: * -> *) :: * -> * Source

Methods

(.-.) :: Num a => Map k a -> Map k a -> Diff (Map k) a Source

(.+^) :: Num a => Map k a -> Diff (Map k) a -> Map k a Source

(.-^) :: Num a => Map k a -> Diff (Map k) a -> Map k a Source

(Eq k, Hashable k) => Affine (HashMap k) Source 

Associated Types

type Diff (HashMap k :: * -> *) :: * -> * Source

Methods

(.-.) :: Num a => HashMap k a -> HashMap k a -> Diff (HashMap k) a Source

(.+^) :: Num a => HashMap k a -> Diff (HashMap k) a -> HashMap k a Source

(.-^) :: Num a => HashMap k a -> Diff (HashMap k) a -> HashMap k a Source

Additive f => Affine (Point f) Source 

Associated Types

type Diff (Point f :: * -> *) :: * -> * Source

Methods

(.-.) :: Num a => Point f a -> Point f a -> Diff (Point f) a Source

(.+^) :: Num a => Point f a -> Diff (Point f) a -> Point f a Source

(.-^) :: Num a => Point f a -> Diff (Point f) a -> Point f a Source

Dim * n => Affine (V * n) Source 

Associated Types

type Diff (V * n :: * -> *) :: * -> * Source

Methods

(.-.) :: Num a => V * n a -> V * n a -> Diff (V * n) a Source

(.+^) :: Num a => V * n a -> Diff (V * n) a -> V * n a Source

(.-^) :: Num a => V * n a -> Diff (V * n) a -> V * n a Source

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

Unbox (f a) => Vector Vector (Point f a) Source 

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Point f a) -> m (Vector (Point f a))

basicUnsafeThaw :: PrimMonad m => Vector (Point f a) -> m (Mutable Vector (PrimState m) (Point f a))

basicLength :: Vector (Point f a) -> Int

basicUnsafeSlice :: Int -> Int -> Vector (Point f a) -> Vector (Point f a)

basicUnsafeIndexM :: Monad m => Vector (Point f a) -> Int -> m (Point f a)

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Point f a) -> Vector (Point f a) -> m ()

elemseq :: Vector (Point f a) -> Point f a -> b -> b

Unbox (f a) => MVector MVector (Point f a) Source 

Methods

basicLength :: MVector s (Point f a) -> Int

basicUnsafeSlice :: Int -> Int -> MVector s (Point f a) -> MVector s (Point f a)

basicOverlaps :: MVector s (Point f a) -> MVector s (Point f a) -> Bool

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Point f a))

basicInitialize :: PrimMonad m => MVector (PrimState m) (Point f a) -> m ()

basicUnsafeReplicate :: PrimMonad m => Int -> Point f a -> m (MVector (PrimState m) (Point f a))

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Point f a) -> Int -> m (Point f a)

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Point f a) -> Int -> Point f a -> m ()

basicClear :: PrimMonad m => MVector (PrimState m) (Point f a) -> m ()

basicSet :: PrimMonad m => MVector (PrimState m) (Point f a) -> Point f a -> m ()

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Point f a) -> MVector (PrimState m) (Point f a) -> m ()

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Point f a) -> MVector (PrimState m) (Point f a) -> m ()

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Point f a) -> Int -> m (MVector (PrimState m) (Point f a))

Monad f => Monad (Point f) Source 

Methods

(>>=) :: Point f a -> (a -> Point f b) -> Point f b

(>>) :: Point f a -> Point f b -> Point f b

return :: a -> Point f a

fail :: String -> Point f a

Functor f => Functor (Point f) Source 

Methods

fmap :: (a -> b) -> Point f a -> Point f b

(<$) :: a -> Point f b -> Point f a

Applicative f => Applicative (Point f) Source 

Methods

pure :: a -> Point f a

(<*>) :: Point f (a -> b) -> Point f a -> Point f b

(*>) :: Point f a -> Point f b -> Point f b

(<*) :: Point f a -> Point f b -> Point f a

Foldable f => Foldable (Point f) Source 

Methods

fold :: Monoid m => Point f m -> m

foldMap :: Monoid m => (a -> m) -> Point f a -> m

foldr :: (a -> b -> b) -> b -> Point f a -> b

foldr' :: (a -> b -> b) -> b -> Point f a -> b

foldl :: (b -> a -> b) -> b -> Point f a -> b

foldl' :: (b -> a -> b) -> b -> Point f a -> b

foldr1 :: (a -> a -> a) -> Point f a -> a

foldl1 :: (a -> a -> a) -> Point f a -> a

toList :: Point f a -> [a]

null :: Point f a -> Bool

length :: Point f a -> Int

elem :: Eq a => a -> Point f a -> Bool

maximum :: Ord a => Point f a -> a

minimum :: Ord a => Point f a -> a

sum :: Num a => Point f a -> a

product :: Num a => Point f a -> a

Traversable f => Traversable (Point f) Source 

Methods

traverse :: Applicative b => (a -> b c) -> Point f a -> b (Point f c)

sequenceA :: Applicative a => Point f (a b) -> a (Point f b)

mapM :: Monad m => (a -> m b) -> Point f a -> m (Point f b)

sequence :: Monad m => Point f (m a) -> m (Point f a)

Generic1 (Point f) Source 

Associated Types

type Rep1 (Point f :: * -> *) :: * -> *

Methods

from1 :: Point f a -> Rep1 (Point f) a

to1 :: Rep1 (Point f) a -> Point f a

Distributive f => Distributive (Point f) Source 

Methods

distribute :: Functor a => a (Point f b) -> Point f (a b)

collect :: Functor c => (a -> Point f b) -> c a -> Point f (c b)

distributeM :: Monad m => m (Point f a) -> Point f (m a)

collectM :: Monad m => (a -> Point f b) -> m a -> Point f (m b)

Representable f => Representable (Point f) Source 

Associated Types

type Rep (Point f :: * -> *) :: *

Methods

tabulate :: (Rep (Point f) -> a) -> Point f a

index :: Point f a -> Rep (Point f) -> a

Serial1 f => Serial1 (Point f) Source 

Methods

serializeWith :: MonadPut m => (a -> m ()) -> Point f a -> m ()

deserializeWith :: MonadGet m => m a -> m (Point f a)

Apply f => Apply (Point f) Source 

Methods

(<.>) :: Point f (a -> b) -> Point f a -> Point f b

(.>) :: Point f a -> Point f b -> Point f b

(<.) :: Point f a -> Point f b -> Point f a

Bind f => Bind (Point f) Source 

Methods

(>>-) :: Point f a -> (a -> Point f b) -> Point f b

join :: Point f (Point f a) -> Point f a

Eq1 f => Eq1 (Point f) Source 

Methods

eq1 :: Eq a => Point f a -> Point f a -> Bool

Ord1 f => Ord1 (Point f) Source 

Methods

compare1 :: Ord a => Point f a -> Point f a -> Ordering

Read1 f => Read1 (Point f) Source 

Methods

readsPrec1 :: Read a => Int -> ReadS (Point f a)

Show1 f => Show1 (Point f) Source 

Methods

showsPrec1 :: Show a => Int -> Point f a -> ShowS

Additive f => Additive (Point f) Source 

Methods

zero :: Num a => Point f a Source

(^+^) :: Num a => Point f a -> Point f a -> Point f a Source

(^-^) :: Num a => Point f a -> Point f a -> Point f a Source

lerp :: Num a => a -> Point f a -> Point f a -> Point f a Source

liftU2 :: (a -> a -> a) -> Point f a -> Point f a -> Point f a Source

liftI2 :: (a -> b -> c) -> Point f a -> Point f b -> Point f c Source

Metric f => Metric (Point f) Source 

Methods

dot :: Num a => Point f a -> Point f a -> a Source

quadrance :: Num a => Point f a -> a Source

qd :: Num a => Point f a -> Point f a -> a Source

distance :: Floating a => Point f a -> Point f a -> a Source

norm :: Floating a => Point f a -> a Source

signorm :: Floating a => Point f a -> Point f a Source

R1 f => R1 (Point f) Source 

Methods

_x :: Functor b => (a -> b a) -> Point f a -> b (Point f a) Source

R2 f => R2 (Point f) Source 

Methods

_y :: Functor b => (a -> b a) -> Point f a -> b (Point f a) Source

_xy :: Functor b => (V2 a -> b (V2 a)) -> Point f a -> b (Point f a) Source

R3 f => R3 (Point f) Source 

Methods

_z :: Functor b => (a -> b a) -> Point f a -> b (Point f a) Source

_xyz :: Functor b => (V3 a -> b (V3 a)) -> Point f a -> b (Point f a) Source

R4 f => R4 (Point f) Source 

Methods

_w :: Functor b => (a -> b a) -> Point f a -> b (Point f a) Source

_xyzw :: Functor b => (V4 a -> b (V4 a)) -> Point f a -> b (Point f a) Source

Additive f => Affine (Point f) Source 

Associated Types

type Diff (Point f :: * -> *) :: * -> * Source

Methods

(.-.) :: Num a => Point f a -> Point f a -> Diff (Point f) a Source

(.+^) :: Num a => Point f a -> Diff (Point f) a -> Point f a Source

(.-^) :: Num a => Point f a -> Diff (Point f) a -> Point f a Source

Eq (f a) => Eq (Point f a) Source 

Methods

(==) :: Point f a -> Point f a -> Bool

(/=) :: Point f a -> Point f a -> Bool

Fractional (f a) => Fractional (Point f a) Source 

Methods

(/) :: Point f a -> Point f a -> Point f a

recip :: Point f a -> Point f a

fromRational :: Rational -> Point f a

(Data (f a), Typeable (* -> *) f, Typeable * a) => Data (Point f a) Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Point f a -> c (Point f a)

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Point f a)

toConstr :: Point f a -> Constr

dataTypeOf :: Point f a -> DataType

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Point f a))

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Point f a))

gmapT :: (forall b. Data b => b -> b) -> Point f a -> Point f a

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Point f a -> r

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Point f a -> r

gmapQ :: (forall d. Data d => d -> u) -> Point f a -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Point f a -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Point f a -> m (Point f a)

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Point f a -> m (Point f a)

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Point f a -> m (Point f a)

Num (f a) => Num (Point f a) Source 

Methods

(+) :: Point f a -> Point f a -> Point f a

(-) :: Point f a -> Point f a -> Point f a

(*) :: Point f a -> Point f a -> Point f a

negate :: Point f a -> Point f a

abs :: Point f a -> Point f a

signum :: Point f a -> Point f a

fromInteger :: Integer -> Point f a

Ord (f a) => Ord (Point f a) Source 

Methods

compare :: Point f a -> Point f a -> Ordering

(<) :: Point f a -> Point f a -> Bool

(<=) :: Point f a -> Point f a -> Bool

(>) :: Point f a -> Point f a -> Bool

(>=) :: Point f a -> Point f a -> Bool

max :: Point f a -> Point f a -> Point f a

min :: Point f a -> Point f a -> Point f a

Read (f a) => Read (Point f a) Source 
Show (f a) => Show (Point f a) Source 

Methods

showsPrec :: Int -> Point f a -> ShowS

show :: Point f a -> String

showList :: [Point f a] -> ShowS

Ix (f a) => Ix (Point f a) Source 

Methods

range :: (Point f a, Point f a) -> [Point f a]

index :: (Point f a, Point f a) -> Point f a -> Int

unsafeIndex :: (Point f a, Point f a) -> Point f a -> Int

inRange :: (Point f a, Point f a) -> Point f a -> Bool

rangeSize :: (Point f a, Point f a) -> Int

unsafeRangeSize :: (Point f a, Point f a) -> Int

Generic (Point f a) Source 

Associated Types

type Rep (Point f a) :: * -> *

Methods

from :: Point f a -> Rep (Point f a) x

to :: Rep (Point f a) x -> Point f a

Storable (f a) => Storable (Point f a) Source 

Methods

sizeOf :: Point f a -> Int

alignment :: Point f a -> Int

peekElemOff :: Ptr (Point f a) -> Int -> IO (Point f a)

pokeElemOff :: Ptr (Point f a) -> Int -> Point f a -> IO ()

peekByteOff :: Ptr b -> Int -> IO (Point f a)

pokeByteOff :: Ptr b -> Int -> Point f a -> IO ()

peek :: Ptr (Point f a) -> IO (Point f a)

poke :: Ptr (Point f a) -> Point f a -> IO ()

Binary (f a) => Binary (Point f a) Source 

Methods

put :: Point f a -> Put

get :: Get (Point f a)

Serial (f a) => Serial (Point f a) Source 

Methods

serialize :: MonadPut m => Point f a -> m ()

deserialize :: MonadGet m => m (Point f a)

Serialize (f a) => Serialize (Point f a) Source 

Methods

put :: Putter (Point f a)

get :: Get (Point f a)

NFData (f a) => NFData (Point f a) Source 

Methods

rnf :: Point f a -> ()

Hashable (f a) => Hashable (Point f a) Source 

Methods

hashWithSalt :: Int -> Point f a -> Int

hash :: Point f a -> Int

Unbox (f a) => Unbox (Point f a) Source 
Ixed (f a) => Ixed (Point f a) Source 

Methods

ix :: Index (Point f a) -> Traversal' (Point f a) (IxValue (Point f a))

Wrapped (Point f a) Source 

Associated Types

type Unwrapped (Point f a) :: *

Methods

_Wrapped' :: Iso' (Point f a) (Unwrapped (Point f a))

Epsilon (f a) => Epsilon (Point f a) Source 

Methods

nearZero :: Point f a -> Bool Source

(~) * t (Point g b) => Rewrapped (Point f a) t Source 
Traversable f => Each (Point f a) (Point f b) a b Source 

Methods

each :: Traversal (Point f a) (Point f b) a b

data MVector s (Point f a) = MV_P !(MVector s (f a)) Source 
type Rep1 (Point f) Source 
type Rep (Point f) = Rep f Source 
type Diff (Point f) = f Source 
type Rep (Point f a) Source 
data Vector (Point f a) = V_P !(Vector (f a)) Source 
type Index (Point f a) = Index (f a) Source 
type IxValue (Point f a) = IxValue (f a) Source 
type Unwrapped (Point f a) = f a Source 

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.