Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- class Rotation p a | p -> a where
- newtype Rot f1 f2 r = Rot {
- unR :: r
- newtype V3T f a = V3T {}
- class R1 (t :: Type -> Type) where
- class R1 t => R2 (t :: Type -> Type) where
- class R2 t => R3 (t :: Type -> Type) where
- type M33T f1 f2 a = V3T f1 (V3T f2 a)
- cross :: Num a => V3T f a -> V3T f a -> V3T f a
- orthonormalize :: Floating a => Rot f1 f2 (M33 a) -> Rot f1 f2 (M33 a)
Documentation
class Rotation p a | p -> a where Source #
compose :: Rot f1 f2 p -> Rot f2 f3 p -> Rot f1 f3 p Source #
rot :: Rot f1 f2 p -> V3T f1 a -> V3T f2 a Source #
rot' :: Rot f1 f2 p -> V3T f2 a -> V3T f1 a Source #
Instances
Num a => Rotation (M33 a) a Source # | |
Defined in SpatialMathT compose :: Rot f1 f2 (M33 a) -> Rot f2 f3 (M33 a) -> Rot f1 f3 (M33 a) Source # rot :: Rot f1 f2 (M33 a) -> V3T f1 a -> V3T f2 a Source # rot' :: Rot f1 f2 (M33 a) -> V3T f2 a -> V3T f1 a Source # toDcm :: Rot f1 f2 (M33 a) -> Rot f1 f2 (M33 a) Source # transpose :: Rot f1 f2 (M33 a) -> Rot f2 f1 (M33 a) Source # | |
Num a => Rotation (Quaternion a) a Source # | |
Defined in SpatialMathT 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 # toDcm :: Rot f1 f2 (Quaternion a) -> Rot f1 f2 (M33 a) Source # transpose :: Rot f1 f2 (Quaternion a) -> Rot f2 f1 (Quaternion a) Source # |
Instances
Generic1 (Rot f1 f2 :: Type -> Type) Source # | |
Foldable (Rot f1 f2) Source # | |
Defined in SpatialMathT fold :: Monoid m => Rot f1 f2 m -> m # foldMap :: Monoid m => (a -> m) -> Rot f1 f2 a -> m # foldMap' :: Monoid m => (a -> m) -> Rot f1 f2 a -> m # foldr :: (a -> b -> b) -> b -> Rot f1 f2 a -> b # foldr' :: (a -> b -> b) -> b -> Rot f1 f2 a -> b # foldl :: (b -> a -> b) -> b -> Rot f1 f2 a -> b # foldl' :: (b -> a -> b) -> b -> Rot f1 f2 a -> b # foldr1 :: (a -> a -> a) -> Rot f1 f2 a -> a # foldl1 :: (a -> a -> a) -> Rot f1 f2 a -> a # toList :: Rot f1 f2 a -> [a] # length :: Rot f1 f2 a -> Int # elem :: Eq a => a -> Rot f1 f2 a -> Bool # maximum :: Ord a => Rot f1 f2 a -> a # minimum :: Ord a => Rot f1 f2 a -> a # | |
Traversable (Rot f1 f2) Source # | |
Functor (Rot f1 f2) Source # | |
Storable r => Storable (Rot f1 f2 r) Source # | |
Defined in SpatialMathT sizeOf :: Rot f1 f2 r -> Int # alignment :: Rot f1 f2 r -> Int # peekElemOff :: Ptr (Rot f1 f2 r) -> Int -> IO (Rot f1 f2 r) # pokeElemOff :: Ptr (Rot f1 f2 r) -> Int -> Rot f1 f2 r -> IO () # peekByteOff :: Ptr b -> Int -> IO (Rot f1 f2 r) # pokeByteOff :: Ptr b -> Int -> Rot f1 f2 r -> IO () # | |
Generic (Rot f1 f2 r) Source # | |
Num r => Num (Rot f1 f2 r) Source # | |
Defined in SpatialMathT (+) :: Rot f1 f2 r -> Rot f1 f2 r -> Rot f1 f2 r # (-) :: Rot f1 f2 r -> Rot f1 f2 r -> Rot f1 f2 r # (*) :: Rot f1 f2 r -> Rot f1 f2 r -> Rot f1 f2 r # negate :: Rot f1 f2 r -> Rot f1 f2 r # abs :: Rot f1 f2 r -> Rot f1 f2 r # signum :: Rot f1 f2 r -> Rot f1 f2 r # fromInteger :: Integer -> Rot f1 f2 r # | |
Fractional r => Fractional (Rot f1 f2 r) Source # | |
Show r => Show (Rot f1 f2 r) Source # | |
Binary r => Binary (Rot f1 f2 r) Source # | |
Serialize r => Serialize (Rot f1 f2 r) Source # | |
Eq r => Eq (Rot f1 f2 r) Source # | |
Ord r => Ord (Rot f1 f2 r) Source # | |
type Rep1 (Rot f1 f2 :: Type -> Type) Source # | |
Defined in SpatialMathT | |
type Rep (Rot f1 f2 r) Source # | |
Defined in SpatialMathT |
Instances
Generic1 (V3T f :: Type -> TYPE LiftedRep) Source # | |
Foldable (V3T f) Source # | |
Defined in SpatialMathT fold :: Monoid m => V3T f m -> m # foldMap :: Monoid m => (a -> m) -> V3T f a -> m # foldMap' :: Monoid m => (a -> m) -> V3T f a -> m # foldr :: (a -> b -> b) -> b -> V3T f a -> b # foldr' :: (a -> b -> b) -> b -> V3T f a -> b # foldl :: (b -> a -> b) -> b -> V3T f a -> b # foldl' :: (b -> a -> b) -> b -> V3T f a -> b # foldr1 :: (a -> a -> a) -> V3T f a -> a # foldl1 :: (a -> a -> a) -> V3T f a -> a # elem :: Eq a => a -> V3T f a -> Bool # maximum :: Ord a => V3T f a -> a # minimum :: Ord a => V3T f a -> a # | |
Traversable (V3T f) Source # | |
Applicative (V3T f) Source # | |
Functor (V3T f) Source # | |
Metric (V3T f) Source # | |
R1 (V3T f) Source # | |
Defined in SpatialMathT | |
R2 (V3T f) Source # | |
R3 (V3T f) Source # | |
Additive (V3T f) Source # | |
Defined in SpatialMathT | |
Storable a => Storable (V3T f a) Source # | |
Generic (V3T f a) Source # | |
Num a => Num (V3T f a) Source # | |
Fractional a => Fractional (V3T f a) Source # | |
Show a => Show (V3T f a) Source # | |
Binary a => Binary (V3T f a) Source # | |
Serialize a => Serialize (V3T f a) Source # | |
Eq a => Eq (V3T f a) Source # | |
Ord a => Ord (V3T f a) Source # | |
type Rep1 (V3T f :: Type -> TYPE LiftedRep) Source # | |
type Rep (V3T f a) Source # | |
Defined in SpatialMathT |
class R1 (t :: Type -> Type) where #
A space that has at least 1 basis vector _x
.