spatial-math-0.4.0.0: 3d math including quaternions/euler angles/dcms and utility functions

Safe HaskellNone
LanguageHaskell2010

SpatialMath

Contents

Synopsis

Documentation

data Euler a Source #

3-2-1 Euler angle rotation sequence

Constructors

Euler 

Fields

Instances

Functor Euler Source # 

Methods

fmap :: (a -> b) -> Euler a -> Euler b #

(<$) :: a -> Euler b -> Euler a #

Applicative Euler Source # 

Methods

pure :: a -> Euler a #

(<*>) :: Euler (a -> b) -> Euler a -> Euler b #

(*>) :: Euler a -> Euler b -> Euler b #

(<*) :: Euler a -> Euler b -> Euler a #

Foldable Euler Source # 

Methods

fold :: Monoid m => Euler m -> m #

foldMap :: Monoid m => (a -> m) -> Euler a -> m #

foldr :: (a -> b -> b) -> b -> Euler a -> b #

foldr' :: (a -> b -> b) -> b -> Euler a -> b #

foldl :: (b -> a -> b) -> b -> Euler a -> b #

foldl' :: (b -> a -> b) -> b -> Euler a -> b #

foldr1 :: (a -> a -> a) -> Euler a -> a #

foldl1 :: (a -> a -> a) -> Euler a -> a #

toList :: Euler a -> [a] #

null :: Euler a -> Bool #

length :: Euler a -> Int #

elem :: Eq a => a -> Euler a -> Bool #

maximum :: Ord a => Euler a -> a #

minimum :: Ord a => Euler a -> a #

sum :: Num a => Euler a -> a #

product :: Num a => Euler a -> a #

Traversable Euler Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Euler a -> f (Euler b) #

sequenceA :: Applicative f => Euler (f a) -> f (Euler a) #

mapM :: Monad m => (a -> m b) -> Euler a -> m (Euler b) #

sequence :: Monad m => Euler (m a) -> m (Euler a) #

Generic1 Euler Source # 

Associated Types

type Rep1 (Euler :: * -> *) :: * -> * #

Methods

from1 :: Euler a -> Rep1 Euler a #

to1 :: Rep1 Euler a -> Euler a #

(ArcTan2 a, Floating a, Ord a) => Rotation Euler a Source # 

Methods

compose :: Rot f1 f2 Euler a -> Rot f2 f3 Euler a -> Rot f1 f3 Euler a Source #

rot :: Rot f1 f2 Euler a -> V3T f1 a -> V3T f2 a Source #

rot' :: Rot f1 f2 Euler a -> V3T f2 a -> V3T f1 a Source #

transpose :: Rot f1 f2 Euler a -> Rot f2 f1 Euler a Source #

identity :: Rot f1 f2 Euler a Source #

Eq a => Eq (Euler a) Source # 

Methods

(==) :: Euler a -> Euler a -> Bool #

(/=) :: Euler a -> Euler a -> Bool #

Data a => Data (Euler a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Euler a -> c (Euler a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Euler a) #

toConstr :: Euler a -> Constr #

dataTypeOf :: Euler a -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Euler a -> Euler a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Euler a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Euler a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Euler a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Euler a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Euler a -> m (Euler a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Euler a -> m (Euler a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Euler a -> m (Euler a) #

Ord a => Ord (Euler a) Source # 

Methods

compare :: Euler a -> Euler a -> Ordering #

(<) :: Euler a -> Euler a -> Bool #

(<=) :: Euler a -> Euler a -> Bool #

(>) :: Euler a -> Euler a -> Bool #

(>=) :: Euler a -> Euler a -> Bool #

max :: Euler a -> Euler a -> Euler a #

min :: Euler a -> Euler a -> Euler a #

Show a => Show (Euler a) Source # 

Methods

showsPrec :: Int -> Euler a -> ShowS #

show :: Euler a -> String #

showList :: [Euler a] -> ShowS #

Generic (Euler a) Source # 

Associated Types

type Rep (Euler a) :: * -> * #

Methods

from :: Euler a -> Rep (Euler a) x #

to :: Rep (Euler a) x -> Euler a #

Binary a => Binary (Euler a) Source # 

Methods

put :: Euler a -> Put #

get :: Get (Euler a) #

putList :: [Euler a] -> Put #

Serialize a => Serialize (Euler a) Source # 

Methods

put :: Putter (Euler a) #

get :: Get (Euler a) #

type Rep1 Euler Source # 
type Rep (Euler a) Source # 

class Floating a => ArcTan2 a where Source #

doesn't require RealFloat, used for overloading symbolics

Minimal complete definition

arctan2

Methods

arctan2 :: a -> a -> a Source #

rotateXyzAboutX :: Floating a => V3 a -> a -> V3 a Source #

Rotate a vector about the X axis

>>> trunc $ rotateXyzAboutX (V3 0 1 0) (pi/2)
V3 0.0 0.0 1.0
>>> trunc $ rotateXyzAboutX (V3 0 0 1) (pi/2)
V3 0.0 (-1.0) 0.0

rotateXyzAboutY :: Floating a => V3 a -> a -> V3 a Source #

Rotate a vector about the Y axis

>>> trunc $ rotateXyzAboutY (V3 0 0 1) (pi/2)
V3 1.0 0.0 0.0
>>> trunc $ rotateXyzAboutY (V3 1 0 0) (pi/2)
V3 0.0 0.0 (-1.0)

rotateXyzAboutZ :: Floating a => V3 a -> a -> V3 a Source #

Rotate a vector about the Z axis

>>> trunc $ rotateXyzAboutZ (V3 1 0 0) (pi/2)
V3 0.0 1.0 0.0
>>> trunc $ rotateXyzAboutZ (V3 0 1 0) (pi/2)
V3 (-1.0) 0.0 0.0

euler321OfQuat :: (ArcTan2 a, Ord a) => Quaternion a -> Euler a Source #

Convert quaternion to Euler angles

>>> euler321OfQuat (Quaternion 1.0 (V3 0.0 0.0 0.0))
Euler {eYaw = 0.0, ePitch = -0.0, eRoll = 0.0}
>>> euler321OfQuat (Quaternion (sqrt(2)/2) (V3 (sqrt(2)/2) 0.0 0.0))
Euler {eYaw = 0.0, ePitch = -0.0, eRoll = 1.5707963267948966}
>>> euler321OfQuat (Quaternion (sqrt(2)/2) (V3 0.0 (sqrt(2)/2) 0.0))
Euler {eYaw = 0.0, ePitch = 1.5707963267948966, eRoll = 0.0}
>>> euler321OfQuat (Quaternion (sqrt(2)/2) (V3 0.0 0.0 (sqrt(2)/2)))
Euler {eYaw = 1.5707963267948966, ePitch = -0.0, eRoll = 0.0}

unsafeEuler321OfQuat :: ArcTan2 a => Quaternion a -> Euler a Source #

Convert quaternion to Euler angles. Returns Nan if 2.0*(q1*q3 - q0*q2) is outside [-1, 1].

>>> unsafeEuler321OfQuat (Quaternion 1.0 (V3 0.0 0.0 0.0))
Euler {eYaw = 0.0, ePitch = -0.0, eRoll = 0.0}
>>> unsafeEuler321OfQuat (Quaternion (sqrt(2)/2) (V3 (sqrt(2)/2) 0.0 0.0))
Euler {eYaw = 0.0, ePitch = -0.0, eRoll = 1.5707963267948966}
>>> unsafeEuler321OfQuat (Quaternion (sqrt(2)/2) (V3 0.0 (sqrt(2)/2) 0.0))
Euler {eYaw = 0.0, ePitch = NaN, eRoll = 0.0}
>>> unsafeEuler321OfQuat (Quaternion (sqrt(2)/2) (V3 0.0 0.0 (sqrt(2)/2)))
Euler {eYaw = 1.5707963267948966, ePitch = -0.0, eRoll = 0.0}

euler321OfDcm :: (Ord a, ArcTan2 a) => M33 a -> Euler a Source #

Convert DCM to euler angles

>>> euler321OfDcm $ V3 (V3 1 0 0) (V3 0 1 0) (V3 0 0 1)
Euler {eYaw = 0.0, ePitch = -0.0, eRoll = 0.0}
>>> euler321OfDcm $ V3 (V3 0 1 0) (V3 (-1) 0 0) (V3 0 0 1)
Euler {eYaw = 1.5707963267948966, ePitch = -0.0, eRoll = 0.0}
>>> let s = sqrt(2)/2 in euler321OfDcm $ V3 (V3 s s 0) (V3 (-s) s 0) (V3 0 0 1)
Euler {eYaw = 0.7853981633974483, ePitch = -0.0, eRoll = 0.0}

unsafeEuler321OfDcm :: ArcTan2 a => M33 a -> Euler a Source #

Convert DCM to euler angles. Returns Nan if r[1,3] is outside [-1, 1].

>>> unsafeEuler321OfDcm $ V3 (V3 1 0 0) (V3 0 1 0) (V3 0 0 1)
Euler {eYaw = 0.0, ePitch = -0.0, eRoll = 0.0}
>>> unsafeEuler321OfDcm $ V3 (V3 0 1 0) (V3 (-1) 0 0) (V3 0 0 1)
Euler {eYaw = 1.5707963267948966, ePitch = -0.0, eRoll = 0.0}
>>> let s = sqrt(2)/2 in unsafeEuler321OfDcm $ V3 (V3 s s 0) (V3 (-s) s 0) (V3 0 0 1)
Euler {eYaw = 0.7853981633974483, ePitch = -0.0, eRoll = 0.0}
>>> unsafeEuler321OfDcm $ V3 (V3 0 0 1.1) (V3 0 0 0) (V3 0 0 0)
Euler {eYaw = 0.0, ePitch = NaN, eRoll = 0.0}

quatOfEuler321 :: Floating a => Euler a -> Quaternion a Source #

Convert Euler angles to quaternion. The scalar part of the result may be positive or negative.

>>> quatOfEuler321 (Euler 0 0 0)
Quaternion 1.0 (V3 0.0 0.0 0.0)
>>> quatOfEuler321 (Euler (pi/2) 0 0)
Quaternion 0.7071067811865476 (V3 0.0 0.0 0.7071067811865475)
>>> quatOfEuler321 (Euler 0 (pi/2) 0)
Quaternion 0.7071067811865476 (V3 0.0 0.7071067811865475 0.0)
>>> quatOfEuler321 (Euler 0 0 (pi/2))
Quaternion 0.7071067811865476 (V3 0.7071067811865475 0.0 0.0)

dcmOfQuat :: Num a => Quaternion a -> M33 a Source #

convert a quaternion to a DCM

>>> dcmOfQuat $ Quaternion 1.0 (V3 0.0 0.0 0.0)
V3 (V3 1.0 0.0 0.0) (V3 0.0 1.0 0.0) (V3 0.0 0.0 1.0)
>>> let s = sqrt(2)/2 in fmap trunc $ dcmOfQuat $ Quaternion s (V3 0.0 0.0 s)
V3 (V3 0.0 1.0 0.0) (V3 (-1.0) 0.0 0.0) (V3 0.0 0.0 1.0)
>>> dcmOfQuat $ Quaternion 0.9238795325112867 (V3 0.0 0.0 0.3826834323650898)
V3 (V3 0.7071067811865475 0.7071067811865476 0.0) (V3 (-0.7071067811865476) 0.7071067811865475 0.0) (V3 0.0 0.0 1.0)

dcmOfEuler321 :: Floating a => Euler a -> M33 a Source #

Convert DCM to euler angles

>>> fmap trunc $ dcmOfEuler321 $ Euler {eYaw = 0.0, ePitch = 0, eRoll = 0}
V3 (V3 1.0 0.0 0.0) (V3 0.0 1.0 0.0) (V3 0.0 0.0 1.0)
>>> fmap trunc $ dcmOfEuler321 $ Euler {eYaw = pi/2, ePitch = 0, eRoll = 0}
V3 (V3 0.0 1.0 0.0) (V3 (-1.0) 0.0 0.0) (V3 0.0 0.0 1.0)
>>> fmap trunc $ dcmOfEuler321 $ Euler {eYaw = pi/4, ePitch = 0, eRoll = 0}
V3 (V3 0.7071067811865476 0.7071067811865475 0.0) (V3 (-0.7071067811865475) 0.7071067811865476 0.0) (V3 0.0 0.0 1.0)

quatOfDcm :: (Floating a, Ord a) => M33 a -> Quaternion a Source #

convert a DCM to a quaternion

>>> quatOfDcm $ V3 (V3 1 0 0) (V3 0 1 0) (V3 0 0 1)
Quaternion 1.0 (V3 0.0 0.0 0.0)
>>> quatOfDcm $ V3 (V3 0 1 0) (V3 (-1) 0 0) (V3 0 0 1)
Quaternion 0.7071067811865476 (V3 0.0 0.0 0.7071067811865475)
>>> let s = sqrt(2)/2 in quatOfDcm $ V3 (V3 s s 0) (V3 (-s) s 0) (V3 0 0 1)
Quaternion 0.9238795325112867 (V3 0.0 0.0 0.3826834323650898)

rotVecByDcm :: Num a => M33 a -> V3 a -> V3 a Source #

vec_b = R_a2b * vec_a

rotVecByDcmB2A :: Num a => M33 a -> V3 a -> V3 a Source #

vec_a = R_a2b^T * vec_b

rotVecByQuat :: Num a => Quaternion a -> V3 a -> V3 a Source #

vec_b = q_a2b * vec_a * q_a2b^(-1) vec_b = R(q_a2b) * vec_a

rotVecByQuatB2A :: Num a => Quaternion a -> V3 a -> V3 a Source #

rotVecByEuler :: (Floating a, Ord a) => Euler a -> V3 a -> V3 a Source #

rotVecByEulerB2A :: (Floating a, Ord a) => Euler a -> V3 a -> V3 a Source #

re-exported from linear

type M33 a = V3 (V3 a) #

A 3x3 matrix with row-major representation

data V3 a :: * -> * #

A 3-dimensional vector

Constructors

V3 ~a ~a ~a 

Instances

Monad V3 

Methods

(>>=) :: V3 a -> (a -> V3 b) -> V3 b #

(>>) :: V3 a -> V3 b -> V3 b #

return :: a -> V3 a #

fail :: String -> V3 a #

Functor V3 

Methods

fmap :: (a -> b) -> V3 a -> V3 b #

(<$) :: a -> V3 b -> V3 a #

MonadFix V3 

Methods

mfix :: (a -> V3 a) -> V3 a #

Applicative V3 

Methods

pure :: a -> V3 a #

(<*>) :: V3 (a -> b) -> V3 a -> V3 b #

(*>) :: V3 a -> V3 b -> V3 b #

(<*) :: V3 a -> V3 b -> V3 a #

Foldable V3 

Methods

fold :: Monoid m => V3 m -> m #

foldMap :: Monoid m => (a -> m) -> V3 a -> m #

foldr :: (a -> b -> b) -> b -> V3 a -> b #

foldr' :: (a -> b -> b) -> b -> V3 a -> b #

foldl :: (b -> a -> b) -> b -> V3 a -> b #

foldl' :: (b -> a -> b) -> b -> V3 a -> b #

foldr1 :: (a -> a -> a) -> V3 a -> a #

foldl1 :: (a -> a -> a) -> V3 a -> a #

toList :: V3 a -> [a] #

null :: V3 a -> Bool #

length :: V3 a -> Int #

elem :: Eq a => a -> V3 a -> Bool #

maximum :: Ord a => V3 a -> a #

minimum :: Ord a => V3 a -> a #

sum :: Num a => V3 a -> a #

product :: Num a => V3 a -> a #

Traversable V3 

Methods

traverse :: Applicative f => (a -> f b) -> V3 a -> f (V3 b) #

sequenceA :: Applicative f => V3 (f a) -> f (V3 a) #

mapM :: Monad m => (a -> m b) -> V3 a -> m (V3 b) #

sequence :: Monad m => V3 (m a) -> m (V3 a) #

Generic1 V3 

Associated Types

type Rep1 (V3 :: * -> *) :: * -> * #

Methods

from1 :: V3 a -> Rep1 V3 a #

to1 :: Rep1 V3 a -> V3 a #

Distributive V3 

Methods

distribute :: Functor f => f (V3 a) -> V3 (f a) #

collect :: Functor f => (a -> V3 b) -> f a -> V3 (f b) #

distributeM :: Monad m => m (V3 a) -> V3 (m a) #

collectM :: Monad m => (a -> V3 b) -> m a -> V3 (m b) #

Representable V3 

Associated Types

type Rep (V3 :: * -> *) :: * #

Methods

tabulate :: (Rep V3 -> a) -> V3 a #

index :: V3 a -> Rep V3 -> a #

Eq1 V3 

Methods

liftEq :: (a -> b -> Bool) -> V3 a -> V3 b -> Bool #

Ord1 V3 

Methods

liftCompare :: (a -> b -> Ordering) -> V3 a -> V3 b -> Ordering #

Read1 V3 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (V3 a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [V3 a] #

Show1 V3 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> V3 a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [V3 a] -> ShowS #

MonadZip V3 

Methods

mzip :: V3 a -> V3 b -> V3 (a, b) #

mzipWith :: (a -> b -> c) -> V3 a -> V3 b -> V3 c #

munzip :: V3 (a, b) -> (V3 a, V3 b) #

Serial1 V3 

Methods

serializeWith :: MonadPut m => (a -> m ()) -> V3 a -> m () #

deserializeWith :: MonadGet m => m a -> m (V3 a) #

Traversable1 V3 

Methods

traverse1 :: Apply f => (a -> f b) -> V3 a -> f (V3 b) #

sequence1 :: Apply f => V3 (f b) -> f (V3 b) #

R3 V3 

Methods

_z :: Functor f => (a -> f a) -> V3 a -> f (V3 a) #

_xyz :: Functor f => (V3 a -> f (V3 a)) -> V3 a -> f (V3 a) #

R2 V3 

Methods

_y :: Functor f => (a -> f a) -> V3 a -> f (V3 a) #

_xy :: Functor f => (V2 a -> f (V2 a)) -> V3 a -> f (V3 a) #

R1 V3 

Methods

_x :: Functor f => (a -> f a) -> V3 a -> f (V3 a) #

Metric V3 

Methods

dot :: Num a => V3 a -> V3 a -> a #

quadrance :: Num a => V3 a -> a #

qd :: Num a => V3 a -> V3 a -> a #

distance :: Floating a => V3 a -> V3 a -> a #

norm :: Floating a => V3 a -> a #

signorm :: Floating a => V3 a -> V3 a #

Additive V3 

Methods

zero :: Num a => V3 a #

(^+^) :: Num a => V3 a -> V3 a -> V3 a #

(^-^) :: Num a => V3 a -> V3 a -> V3 a #

lerp :: Num a => a -> V3 a -> V3 a -> V3 a #

liftU2 :: (a -> a -> a) -> V3 a -> V3 a -> V3 a #

liftI2 :: (a -> b -> c) -> V3 a -> V3 b -> V3 c #

Apply V3 

Methods

(<.>) :: V3 (a -> b) -> V3 a -> V3 b #

(.>) :: V3 a -> V3 b -> V3 b #

(<.) :: V3 a -> V3 b -> V3 a #

Bind V3 

Methods

(>>-) :: V3 a -> (a -> V3 b) -> V3 b #

join :: V3 (V3 a) -> V3 a #

Foldable1 V3 

Methods

fold1 :: Semigroup m => V3 m -> m #

foldMap1 :: Semigroup m => (a -> m) -> V3 a -> m #

Unbox a => Vector Vector (V3 a) 

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (V3 a) -> m (Vector (V3 a)) #

basicUnsafeThaw :: PrimMonad m => Vector (V3 a) -> m (Mutable Vector (PrimState m) (V3 a)) #

basicLength :: Vector (V3 a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (V3 a) -> Vector (V3 a) #

basicUnsafeIndexM :: Monad m => Vector (V3 a) -> Int -> m (V3 a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (V3 a) -> Vector (V3 a) -> m () #

elemseq :: Vector (V3 a) -> V3 a -> b -> b #

Unbox a => MVector MVector (V3 a) 

Methods

basicLength :: MVector s (V3 a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (V3 a) -> MVector s (V3 a) #

basicOverlaps :: MVector s (V3 a) -> MVector s (V3 a) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (V3 a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (V3 a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> V3 a -> m (MVector (PrimState m) (V3 a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (V3 a) -> Int -> m (V3 a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (V3 a) -> Int -> V3 a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (V3 a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (V3 a) -> V3 a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (V3 a) -> MVector (PrimState m) (V3 a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (V3 a) -> MVector (PrimState m) (V3 a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (V3 a) -> Int -> m (MVector (PrimState m) (V3 a)) #

Bounded a => Bounded (V3 a) 

Methods

minBound :: V3 a #

maxBound :: V3 a #

Eq a => Eq (V3 a) 

Methods

(==) :: V3 a -> V3 a -> Bool #

(/=) :: V3 a -> V3 a -> Bool #

Floating a => Floating (V3 a) 

Methods

pi :: V3 a #

exp :: V3 a -> V3 a #

log :: V3 a -> V3 a #

sqrt :: V3 a -> V3 a #

(**) :: V3 a -> V3 a -> V3 a #

logBase :: V3 a -> V3 a -> V3 a #

sin :: V3 a -> V3 a #

cos :: V3 a -> V3 a #

tan :: V3 a -> V3 a #

asin :: V3 a -> V3 a #

acos :: V3 a -> V3 a #

atan :: V3 a -> V3 a #

sinh :: V3 a -> V3 a #

cosh :: V3 a -> V3 a #

tanh :: V3 a -> V3 a #

asinh :: V3 a -> V3 a #

acosh :: V3 a -> V3 a #

atanh :: V3 a -> V3 a #

log1p :: V3 a -> V3 a #

expm1 :: V3 a -> V3 a #

log1pexp :: V3 a -> V3 a #

log1mexp :: V3 a -> V3 a #

Fractional a => Fractional (V3 a) 

Methods

(/) :: V3 a -> V3 a -> V3 a #

recip :: V3 a -> V3 a #

fromRational :: Rational -> V3 a #

Data a => Data (V3 a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V3 a -> c (V3 a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V3 a) #

toConstr :: V3 a -> Constr #

dataTypeOf :: V3 a -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> V3 a -> V3 a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V3 a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V3 a -> r #

gmapQ :: (forall d. Data d => d -> u) -> V3 a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> V3 a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> V3 a -> m (V3 a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V3 a -> m (V3 a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V3 a -> m (V3 a) #

Num a => Num (V3 a) 

Methods

(+) :: V3 a -> V3 a -> V3 a #

(-) :: V3 a -> V3 a -> V3 a #

(*) :: V3 a -> V3 a -> V3 a #

negate :: V3 a -> V3 a #

abs :: V3 a -> V3 a #

signum :: V3 a -> V3 a #

fromInteger :: Integer -> V3 a #

Ord a => Ord (V3 a) 

Methods

compare :: V3 a -> V3 a -> Ordering #

(<) :: V3 a -> V3 a -> Bool #

(<=) :: V3 a -> V3 a -> Bool #

(>) :: V3 a -> V3 a -> Bool #

(>=) :: V3 a -> V3 a -> Bool #

max :: V3 a -> V3 a -> V3 a #

min :: V3 a -> V3 a -> V3 a #

Read a => Read (V3 a) 
Show a => Show (V3 a) 

Methods

showsPrec :: Int -> V3 a -> ShowS #

show :: V3 a -> String #

showList :: [V3 a] -> ShowS #

Ix a => Ix (V3 a) 

Methods

range :: (V3 a, V3 a) -> [V3 a] #

index :: (V3 a, V3 a) -> V3 a -> Int #

unsafeIndex :: (V3 a, V3 a) -> V3 a -> Int

inRange :: (V3 a, V3 a) -> V3 a -> Bool #

rangeSize :: (V3 a, V3 a) -> Int #

unsafeRangeSize :: (V3 a, V3 a) -> Int

Generic (V3 a) 

Associated Types

type Rep (V3 a) :: * -> * #

Methods

from :: V3 a -> Rep (V3 a) x #

to :: Rep (V3 a) x -> V3 a #

Storable a => Storable (V3 a) 

Methods

sizeOf :: V3 a -> Int #

alignment :: V3 a -> Int #

peekElemOff :: Ptr (V3 a) -> Int -> IO (V3 a) #

pokeElemOff :: Ptr (V3 a) -> Int -> V3 a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (V3 a) #

pokeByteOff :: Ptr b -> Int -> V3 a -> IO () #

peek :: Ptr (V3 a) -> IO (V3 a) #

poke :: Ptr (V3 a) -> V3 a -> IO () #

Binary a => Binary (V3 a) 

Methods

put :: V3 a -> Put #

get :: Get (V3 a) #

putList :: [V3 a] -> Put #

Serial a => Serial (V3 a) 

Methods

serialize :: MonadPut m => V3 a -> m () #

deserialize :: MonadGet m => m (V3 a) #

Serialize a => Serialize (V3 a) 

Methods

put :: Putter (V3 a) #

get :: Get (V3 a) #

NFData a => NFData (V3 a) 

Methods

rnf :: V3 a -> () #

Hashable a => Hashable (V3 a) 

Methods

hashWithSalt :: Int -> V3 a -> Int #

hash :: V3 a -> Int #

Unbox a => Unbox (V3 a) 
Ixed (V3 a) 

Methods

ix :: Index (V3 a) -> Traversal' (V3 a) (IxValue (V3 a)) #

Epsilon a => Epsilon (V3 a) 

Methods

nearZero :: V3 a -> Bool #

FunctorWithIndex (E V3) V3 

Methods

imap :: (E V3 -> a -> b) -> V3 a -> V3 b #

imapped :: (Indexable (E V3) p, Settable f) => p a (f b) -> V3 a -> f (V3 b) #

FoldableWithIndex (E V3) V3 

Methods

ifoldMap :: Monoid m => (E V3 -> a -> m) -> V3 a -> m #

ifolded :: (Indexable (E V3) p, Contravariant f, Applicative f) => p a (f a) -> V3 a -> f (V3 a) #

ifoldr :: (E V3 -> a -> b -> b) -> b -> V3 a -> b #

ifoldl :: (E V3 -> b -> a -> b) -> b -> V3 a -> b #

ifoldr' :: (E V3 -> a -> b -> b) -> b -> V3 a -> b #

ifoldl' :: (E V3 -> b -> a -> b) -> b -> V3 a -> b #

TraversableWithIndex (E V3) V3 

Methods

itraverse :: Applicative f => (E V3 -> a -> f b) -> V3 a -> f (V3 b) #

itraversed :: (Indexable (E V3) p, Applicative f) => p a (f b) -> V3 a -> f (V3 b) #

Each (V3 a) (V3 b) a b 

Methods

each :: Traversal (V3 a) (V3 b) a b #

Num a => Rotation ((:.) V3 V3) a Source # 

Methods

compose :: Rot f1 f2 (V3 :. V3) a -> Rot f2 f3 (V3 :. V3) a -> Rot f1 f3 (V3 :. V3) a Source #

rot :: Rot f1 f2 (V3 :. V3) a -> V3T f1 a -> V3T f2 a Source #

rot' :: Rot f1 f2 (V3 :. V3) a -> V3T f2 a -> V3T f1 a Source #

transpose :: Rot f1 f2 (V3 :. V3) a -> Rot f2 f1 (V3 :. V3) a Source #

identity :: Rot f1 f2 (V3 :. V3) a Source #

type Rep1 V3 
type Rep V3 
type Rep V3 = E V3
data MVector s (V3 a) 
data MVector s (V3 a) = MV_V3 ~Int ~(MVector s a)
type Rep (V3 a) 
data Vector (V3 a) 
data Vector (V3 a) = V_V3 ~Int ~(Vector a)
type Index (V3 a) 
type Index (V3 a) = E V3
type IxValue (V3 a) 
type IxValue (V3 a) = a

data Quaternion a :: * -> * #

Quaternions

Constructors

Quaternion ~a ~(V3 a) 

Instances

Monad Quaternion 

Methods

(>>=) :: Quaternion a -> (a -> Quaternion b) -> Quaternion b #

(>>) :: Quaternion a -> Quaternion b -> Quaternion b #

return :: a -> Quaternion a #

fail :: String -> Quaternion a #

Functor Quaternion 

Methods

fmap :: (a -> b) -> Quaternion a -> Quaternion b #

(<$) :: a -> Quaternion b -> Quaternion a #

MonadFix Quaternion 

Methods

mfix :: (a -> Quaternion a) -> Quaternion a #

Applicative Quaternion 

Methods

pure :: a -> Quaternion a #

(<*>) :: Quaternion (a -> b) -> Quaternion a -> Quaternion b #

(*>) :: Quaternion a -> Quaternion b -> Quaternion b #

(<*) :: Quaternion a -> Quaternion b -> Quaternion a #

Foldable Quaternion 

Methods

fold :: Monoid m => Quaternion m -> m #

foldMap :: Monoid m => (a -> m) -> Quaternion a -> m #

foldr :: (a -> b -> b) -> b -> Quaternion a -> b #

foldr' :: (a -> b -> b) -> b -> Quaternion a -> b #

foldl :: (b -> a -> b) -> b -> Quaternion a -> b #

foldl' :: (b -> a -> b) -> b -> Quaternion a -> b #

foldr1 :: (a -> a -> a) -> Quaternion a -> a #

foldl1 :: (a -> a -> a) -> Quaternion a -> a #

toList :: Quaternion a -> [a] #

null :: Quaternion a -> Bool #

length :: Quaternion a -> Int #

elem :: Eq a => a -> Quaternion a -> Bool #

maximum :: Ord a => Quaternion a -> a #

minimum :: Ord a => Quaternion a -> a #

sum :: Num a => Quaternion a -> a #

product :: Num a => Quaternion a -> a #

Traversable Quaternion 

Methods

traverse :: Applicative f => (a -> f b) -> Quaternion a -> f (Quaternion b) #

sequenceA :: Applicative f => Quaternion (f a) -> f (Quaternion a) #

mapM :: Monad m => (a -> m b) -> Quaternion a -> m (Quaternion b) #

sequence :: Monad m => Quaternion (m a) -> m (Quaternion a) #

Generic1 Quaternion 

Associated Types

type Rep1 (Quaternion :: * -> *) :: * -> * #

Distributive Quaternion 

Methods

distribute :: Functor f => f (Quaternion a) -> Quaternion (f a) #

collect :: Functor f => (a -> Quaternion b) -> f a -> Quaternion (f b) #

distributeM :: Monad m => m (Quaternion a) -> Quaternion (m a) #

collectM :: Monad m => (a -> Quaternion b) -> m a -> Quaternion (m b) #

Representable Quaternion 

Associated Types

type Rep (Quaternion :: * -> *) :: * #

Methods

tabulate :: (Rep Quaternion -> a) -> Quaternion a #

index :: Quaternion a -> Rep Quaternion -> a #

Eq1 Quaternion 

Methods

liftEq :: (a -> b -> Bool) -> Quaternion a -> Quaternion b -> Bool #

Ord1 Quaternion 

Methods

liftCompare :: (a -> b -> Ordering) -> Quaternion a -> Quaternion b -> Ordering #

Read1 Quaternion 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Quaternion a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Quaternion a] #

Show1 Quaternion 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Quaternion a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Quaternion a] -> ShowS #

MonadZip Quaternion 

Methods

mzip :: Quaternion a -> Quaternion b -> Quaternion (a, b) #

mzipWith :: (a -> b -> c) -> Quaternion a -> Quaternion b -> Quaternion c #

munzip :: Quaternion (a, b) -> (Quaternion a, Quaternion b) #

Serial1 Quaternion 

Methods

serializeWith :: MonadPut m => (a -> m ()) -> Quaternion a -> m () #

deserializeWith :: MonadGet m => m a -> m (Quaternion a) #

Complicated Quaternion 

Methods

_e :: Functor f => (a -> f a) -> Quaternion a -> f (Quaternion a) #

_i :: Functor f => (a -> f a) -> Quaternion a -> f (Quaternion a) #

Hamiltonian Quaternion 

Methods

_j :: Functor f => (a -> f a) -> Quaternion a -> f (Quaternion a) #

_k :: Functor f => (a -> f a) -> Quaternion a -> f (Quaternion a) #

_ijk :: Functor f => (V3 a -> f (V3 a)) -> Quaternion a -> f (Quaternion a) #

Metric Quaternion 

Methods

dot :: Num a => Quaternion a -> Quaternion a -> a #

quadrance :: Num a => Quaternion a -> a #

qd :: Num a => Quaternion a -> Quaternion a -> a #

distance :: Floating a => Quaternion a -> Quaternion a -> a #

norm :: Floating a => Quaternion a -> a #

signorm :: Floating a => Quaternion a -> Quaternion a #

Additive Quaternion 

Methods

zero :: Num a => Quaternion a #

(^+^) :: Num a => Quaternion a -> Quaternion a -> Quaternion a #

(^-^) :: Num a => Quaternion a -> Quaternion a -> Quaternion a #

lerp :: Num a => a -> Quaternion a -> Quaternion a -> Quaternion a #

liftU2 :: (a -> a -> a) -> Quaternion a -> Quaternion a -> Quaternion a #

liftI2 :: (a -> b -> c) -> Quaternion a -> Quaternion b -> Quaternion c #

Apply Quaternion 

Methods

(<.>) :: Quaternion (a -> b) -> Quaternion a -> Quaternion b #

(.>) :: Quaternion a -> Quaternion b -> Quaternion b #

(<.) :: Quaternion a -> Quaternion b -> Quaternion a #

Bind Quaternion 

Methods

(>>-) :: Quaternion a -> (a -> Quaternion b) -> Quaternion b #

join :: Quaternion (Quaternion a) -> Quaternion a #

Num a => Rotation Quaternion a Source # 

Methods

compose :: Rot f1 f2 Quaternion a -> Rot f2 f3 Quaternion a -> Rot f1 f3 Quaternion a Source #

rot :: Rot f1 f2 Quaternion a -> V3T f1 a -> V3T f2 a Source #

rot' :: Rot f1 f2 Quaternion a -> V3T f2 a -> V3T f1 a Source #

transpose :: Rot f1 f2 Quaternion a -> Rot f2 f1 Quaternion a Source #

identity :: Rot f1 f2 Quaternion a Source #

Unbox a => Vector Vector (Quaternion a) 
Unbox a => MVector MVector (Quaternion a) 
Eq a => Eq (Quaternion a) 

Methods

(==) :: Quaternion a -> Quaternion a -> Bool #

(/=) :: Quaternion a -> Quaternion a -> Bool #

RealFloat a => Floating (Quaternion a) 
RealFloat a => Fractional (Quaternion a) 
Data a => Data (Quaternion a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Quaternion a -> c (Quaternion a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Quaternion a) #

toConstr :: Quaternion a -> Constr #

dataTypeOf :: Quaternion a -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Quaternion a -> Quaternion a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Quaternion a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Quaternion a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Quaternion a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Quaternion a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Quaternion a -> m (Quaternion a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Quaternion a -> m (Quaternion a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Quaternion a -> m (Quaternion a) #

RealFloat a => Num (Quaternion a) 
Ord a => Ord (Quaternion a) 
Read a => Read (Quaternion a) 
Show a => Show (Quaternion a) 
Ix a => Ix (Quaternion a) 
Generic (Quaternion a) 

Associated Types

type Rep (Quaternion a) :: * -> * #

Methods

from :: Quaternion a -> Rep (Quaternion a) x #

to :: Rep (Quaternion a) x -> Quaternion a #

Storable a => Storable (Quaternion a) 

Methods

sizeOf :: Quaternion a -> Int #

alignment :: Quaternion a -> Int #

peekElemOff :: Ptr (Quaternion a) -> Int -> IO (Quaternion a) #

pokeElemOff :: Ptr (Quaternion a) -> Int -> Quaternion a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Quaternion a) #

pokeByteOff :: Ptr b -> Int -> Quaternion a -> IO () #

peek :: Ptr (Quaternion a) -> IO (Quaternion a) #

poke :: Ptr (Quaternion a) -> Quaternion a -> IO () #

Binary a => Binary (Quaternion a) 

Methods

put :: Quaternion a -> Put #

get :: Get (Quaternion a) #

putList :: [Quaternion a] -> Put #

Serial a => Serial (Quaternion a) 

Methods

serialize :: MonadPut m => Quaternion a -> m () #

deserialize :: MonadGet m => m (Quaternion a) #

Serialize a => Serialize (Quaternion a) 

Methods

put :: Putter (Quaternion a) #

get :: Get (Quaternion a) #

NFData a => NFData (Quaternion a) 

Methods

rnf :: Quaternion a -> () #

Hashable a => Hashable (Quaternion a) 

Methods

hashWithSalt :: Int -> Quaternion a -> Int #

hash :: Quaternion a -> Int #

Unbox a => Unbox (Quaternion a) 
Ixed (Quaternion a) 
(Conjugate a, RealFloat a) => Conjugate (Quaternion a) 

Methods

conjugate :: Quaternion a -> Quaternion a #

(RealFloat a, Epsilon a) => Epsilon (Quaternion a) 

Methods

nearZero :: Quaternion a -> Bool #

FunctorWithIndex (E Quaternion) Quaternion 

Methods

imap :: (E Quaternion -> a -> b) -> Quaternion a -> Quaternion b #

imapped :: (Indexable (E Quaternion) p, Settable f) => p a (f b) -> Quaternion a -> f (Quaternion b) #

FoldableWithIndex (E Quaternion) Quaternion 

Methods

ifoldMap :: Monoid m => (E Quaternion -> a -> m) -> Quaternion a -> m #

ifolded :: (Indexable (E Quaternion) p, Contravariant f, Applicative f) => p a (f a) -> Quaternion a -> f (Quaternion a) #

ifoldr :: (E Quaternion -> a -> b -> b) -> b -> Quaternion a -> b #

ifoldl :: (E Quaternion -> b -> a -> b) -> b -> Quaternion a -> b #

ifoldr' :: (E Quaternion -> a -> b -> b) -> b -> Quaternion a -> b #

ifoldl' :: (E Quaternion -> b -> a -> b) -> b -> Quaternion a -> b #

TraversableWithIndex (E Quaternion) Quaternion 

Methods

itraverse :: Applicative f => (E Quaternion -> a -> f b) -> Quaternion a -> f (Quaternion b) #

itraversed :: (Indexable (E Quaternion) p, Applicative f) => p a (f b) -> Quaternion a -> f (Quaternion b) #

Each (Quaternion a) (Quaternion b) a b 

Methods

each :: Traversal (Quaternion a) (Quaternion b) a b #

type Rep1 Quaternion 
type Rep1 Quaternion = D1 (MetaData "Quaternion" "Linear.Quaternion" "linear-1.20.5-ALqHTYew01KD1PdDd6TYmz" False) (C1 (MetaCons "Quaternion" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) Par1) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec1 V3))))
type Rep Quaternion 
data MVector s (Quaternion a) 
type Rep (Quaternion a) 
type Rep (Quaternion a) = D1 (MetaData "Quaternion" "Linear.Quaternion" "linear-1.20.5-ALqHTYew01KD1PdDd6TYmz" False) (C1 (MetaCons "Quaternion" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a)) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 (V3 a)))))
data Vector (Quaternion a) 
type Index (Quaternion a) 
type IxValue (Quaternion a) 
type IxValue (Quaternion a) = a