-- | -- Module : Cartesian.Internal.Types -- Description : -- Copyright : (c) Jonatan H Sundqvist, 2015 -- License : MIT -- Maintainer : Jonatan H Sundqvist -- Stability : experimental|stable -- Portability : POSIX (not sure) -- -- Created October 31 2015 -- TODO | - Use TemplateHaskell (?) -- - Strictness -- SPEC | - -- - -------------------------------------------------------------------------------------------------------------------------------------------- -- GHC Pragmas -------------------------------------------------------------------------------------------------------------------------------------------- {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} -------------------------------------------------------------------------------------------------------------------------------------------- -- API -------------------------------------------------------------------------------------------------------------------------------------------- module Cartesian.Internal.Types where -------------------------------------------------------------------------------------------------------------------------------------------- -- We'll need these -------------------------------------------------------------------------------------------------------------------------------------------- -------------------------------------------------------------------------------------------------------------------------------------------- -- Types -------------------------------------------------------------------------------------------------------------------------------------------- -- Types ----------------------------------------------------------------------------------------------------------------------------------- -- | -- TODO: Anchors (eg. C, N, S, E W and combinations thereof, perhaps represented as relative Vectors) data BoundingBox v = BoundingBox { centreOf :: v, sizeOf :: v } -- Classes --------------------------------------------------------------------------------------------------------------------------------- -- | -- TODO: Use GADT instead (?) -- TODO: Reduce boilerplate, figure out deriving, choose interface carefully class Vector v where vfold :: (f' -> f -> f') -> f' -> v f -> f' vzip :: (f -> f' -> f'') -> v f -> v f' -> v f'' -- | class HasX a f | a -> f where getX :: a -> f setX :: a -> f -> a -- | class HasY a f | a -> f where getY :: a -> f setY :: a -> f -> a -- | class HasZ a f | a -> f where getZ :: a -> f setZ :: a -> f -> a -- Instances -------------------------------------------------------------------------------------------------------------------------------