module DeepControl.Commutative (
Commutative(..),
cmap,
cfor,
fmapDefault,
foldMapDefault,
sink2, float2,
sink3, float3,
sink4, float4,
sink5, float5,
) where
import DeepControl.Applicative
import Data.Monoid
import Control.Monad.Identity (Identity(..))
import Control.Monad.Except (Except, ExceptT(..), runExcept)
import Control.Monad.Writer (Writer, WriterT(..), runWriter)
class (Applicative c) => Commutative c where
commute :: Applicative f => c (f a) -> f (c a)
cmap :: (Applicative f, Commutative c) => (a -> f b) -> c a -> f (c b)
cmap f = commute . (f |$>)
cfor :: (Applicative f, Commutative c) => c a -> (a -> f b) -> f (c b)
cfor = flip cmap
instance Commutative Maybe where
commute (Just fa) = Just |$> fa
commute Nothing = (*:) Nothing
instance Commutative [] where
commute = foldr (\x acc -> x <$|(:)|*> acc) ((*:) [])
instance (Monoid w) => Commutative (Writer w) where
commute x =
let (a, b) = runWriter x
in (WriterT . Identity) |$> (a <$|(,)|* b)
instance Commutative (Either a) where
commute (Right x) = Right |$> x
commute (Left x) = (*:) $ Left x
instance Commutative (Except e) where
commute x = ExceptT . Identity |$> commute (runExcept x)
fmapDefault :: Commutative t => (a -> b) -> t a -> t b
fmapDefault f = getId . cmap (Id . f)
foldMapDefault :: (Commutative t, Monoid m) => (a -> m) -> t a -> m
foldMapDefault f = getConst . cmap (Const . f)
newtype Id a = Id { getId :: a }
instance Functor Id where
fmap f (Id x) = Id (f x)
instance Applicative Id where
pure = Id
Id f <*> Id x = Id (f x)
sink2 :: (Commutative m1, Commutative m2, Applicative m3) =>
m1 (m2 (m3 a)) -> m2 (m3 (m1 a))
sink2 = (commute|$>) . commute
float2 :: (Applicative m1, Commutative m2, Commutative m3) =>
m2 (m3 (m1 a)) -> m1 (m2 (m3 a))
float2 = commute . (commute|$>)
sink3 :: (Commutative m1, Commutative m2, Commutative m3, Applicative m4) =>
m1 (m2 (m3 (m4 a))) -> m2 (m3 (m4 (m1 a)))
sink3 = (sink2|$>) . commute
float3 :: (Applicative m1, Commutative m2, Commutative m3, Commutative m4) =>
m2 (m3 (m4 (m1 a))) -> m1 (m2 (m3 (m4 a)))
float3 = commute . (float2|$>)
sink4 :: (Commutative m1, Commutative m2, Commutative m3, Commutative m4, Applicative m5) =>
m1 (m2 (m3 (m4 (m5 a)))) -> m2 (m3 (m4 (m5 (m1 a))))
sink4 = (sink3|$>) . commute
float4 :: (Applicative m1, Commutative m2, Commutative m3, Commutative m4, Commutative m5) =>
m2 (m3 (m4 (m5 (m1 a)))) -> m1 (m2 (m3 (m4 (m5 a))))
float4 = commute . (float3|$>)
sink5 :: (Commutative m1, Commutative m2, Commutative m3, Commutative m4, Commutative m5, Applicative m6) =>
m1 (m2 (m3 (m4 (m5 (m6 a))))) -> m2 (m3 (m4 (m5 (m6 (m1 a)))))
sink5 = (sink4|$>) . commute
float5 :: (Applicative m1, Commutative m2, Commutative m3, Commutative m4, Commutative m5, Commutative m6) =>
m2 (m3 (m4 (m5 (m6 (m1 a))))) -> m1 (m2 (m3 (m4 (m5 (m6 a)))))
float5 = commute . (float4|$>)