module Diagrams.Core.Juxtapose
( Juxtaposable(..), juxtaposeDefault
) where
import Control.Applicative
import qualified Data.Map as M
import qualified Data.Set as S
import Diagrams.Core.Envelope
import Diagrams.Core.Measure
import Diagrams.Core.HasOrigin
import Diagrams.Core.V
import Linear.Metric
import Linear.Vector
class Juxtaposable a where
juxtapose :: Vn a -> a -> a -> a
juxtaposeDefault :: (Enveloped a, HasOrigin a) => Vn a -> a -> a -> a
juxtaposeDefault v a1 a2 =
case (mv1, mv2) of
(Just v1, Just v2) -> moveOriginBy (v1 ^+^ v2) a2
_ -> a2
where mv1 = negated <$> envelopeVMay v a1
mv2 = envelopeVMay (negated v) a2
instance (Metric v, OrderedField n) => Juxtaposable (Envelope v n) where
juxtapose = juxtaposeDefault
instance (Enveloped a, HasOrigin a, Enveloped b, HasOrigin b, V a ~ V b, N a ~ N b)
=> Juxtaposable (a,b) where
juxtapose = juxtaposeDefault
instance (Enveloped b, HasOrigin b) => Juxtaposable [b] where
juxtapose = juxtaposeDefault
instance (Enveloped b, HasOrigin b) => Juxtaposable (M.Map k b) where
juxtapose = juxtaposeDefault
instance (Enveloped b, HasOrigin b, Ord b) => Juxtaposable (S.Set b) where
juxtapose = juxtaposeDefault
instance Juxtaposable a => Juxtaposable (b -> a) where
juxtapose v f1 f2 b = juxtapose v (f1 b) (f2 b)
instance Juxtaposable a => Juxtaposable (Measured n a) where
juxtapose v = liftA2 (juxtapose v)