rsagl-0.2.1: The RogueStar Animation and Graphics LibrarySource codeContentsIndex
RSAGL.CoordinateSystems
Documentation
type AffineTransformation = Affine -> AffineSource
affine_identity :: AffineTransformationSource
data CoordinateSystem Source
show/hide Instances
newtype Affine Source
Constructors
Affine
affine_transformation :: forall a. AffineTransformable a => a -> a
show/hide Instances
affineOf :: AffineTransformation -> AffineSource
class CoordinateSystemClass csc whereSource
Methods
getCoordinateSystem :: csc -> CoordinateSystemSource
storeCoordinateSystem :: CoordinateSystem -> csc -> cscSource
show/hide Instances
class NestedCoordinateSystemTransformer a Source
show/hide Instances
root_coordinate_system :: CoordinateSystemSource
migrate :: AffineTransformable a => CoordinateSystem -> CoordinateSystem -> a -> aSource
transformation :: AffineTransformable a => AffineTransformation -> a -> aSource
inverseTransformation :: AffineTransformable a => AffineTransformation -> a -> aSource
data CSN a Source
show/hide Instances
Show a => Show (CSN a)
importCSN :: AffineTransformable a => CoordinateSystem -> CSN a -> aSource
exportCSN :: AffineTransformable a => CoordinateSystem -> a -> CSN aSource
remoteCSN :: (AffineTransformable a, AffineTransformable b) => CoordinateSystem -> (a -> b) -> CSN a -> CSN bSource
importM :: (Monad m, MonadState s m, CoordinateSystemClass s, AffineTransformable a) => CSN a -> m aSource
exportM :: (Monad m, MonadState s m, CoordinateSystemClass s, AffineTransformable a) => a -> m (CSN a)Source
remoteM :: (Monad m, MonadState s m, CoordinateSystemClass s, AffineTransformable a, AffineTransformable b) => CoordinateSystem -> (a -> b) -> a -> m bSource
importA :: (Arrow arr, ArrowState s arr, CoordinateSystemClass s, AffineTransformable a) => arr (CSN a) aSource
importFromA :: (Arrow arr, ArrowState s arr, CoordinateSystemClass s, AffineTransformable a) => CoordinateSystem -> arr a aSource
exportA :: (Arrow arr, ArrowState s arr, CoordinateSystemClass s, AffineTransformable a) => arr a (CSN a)Source
exportToA :: (Arrow arr, ArrowState s arr, CoordinateSystemClass s, AffineTransformable a) => CoordinateSystem -> arr a aSource
exportCoordinateSystem :: (Arrow arr, ArrowState s arr, CoordinateSystemClass s) => arr AffineTransformation CoordinateSystemSource
remoteA :: (Arrow arr, ArrowState s arr, CoordinateSystemClass s, AffineTransformable a, AffineTransformable b) => arr (CoordinateSystem, a -> b, a) bSource
transformM :: (Monad m, MonadState s m, CoordinateSystemClass s, NestedCoordinateSystemTransformer cst) => cst -> m a -> m aSource
transformA :: (Arrow arr, ArrowState s arr, CoordinateSystemClass s, NestedCoordinateSystemTransformer cst) => arr a b -> arr (cst, a) bSource
data Distance Source
show/hide Instances
measure :: (AffineTransformable p, Xyz p) => p -> p -> DistanceSource
distance :: Distance -> DoubleSource
distanceSquared :: Distance -> DoubleSource
Produced by Haddock version 2.1.0