{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Control.Algebra
( Algebra(..)
, thread
, run
, Has
, send
, Handler
, (~<~)
, (:+:) (..)
) where
import Control.Algebra.Handler
import Control.Effect.Catch.Internal
import Control.Effect.Choose.Internal
import Control.Effect.Empty.Internal
import Control.Effect.Error.Internal
import Control.Effect.Lift.Internal
import Control.Effect.NonDet.Internal
import Control.Effect.Reader.Internal
import Control.Effect.State.Internal
import Control.Effect.Sum ((:+:)(..), Member(..), Members)
import Control.Effect.Throw.Internal
import Control.Effect.Writer.Internal
import qualified Control.Monad.Trans.Except as Except
import qualified Control.Monad.Trans.Identity as Identity
import qualified Control.Monad.Trans.Maybe as Maybe
import qualified Control.Monad.Trans.Reader as Reader
#if MIN_VERSION_transformers(0,5,6)
import qualified Control.Monad.Trans.RWS.CPS as RWS.CPS
#endif
import qualified Control.Monad.Trans.RWS.Lazy as RWS.Lazy
import qualified Control.Monad.Trans.RWS.Strict as RWS.Strict
import qualified Control.Monad.Trans.State.Lazy as State.Lazy
import qualified Control.Monad.Trans.State.Strict as State.Strict
#if MIN_VERSION_transformers(0,5,6)
import qualified Control.Monad.Trans.Writer.CPS as Writer.CPS
#endif
import qualified Control.Monad.Trans.Writer.Lazy as Writer.Lazy
import qualified Control.Monad.Trans.Writer.Strict as Writer.Strict
import Data.Functor.Compose
import Data.Functor.Identity
import Data.List.NonEmpty (NonEmpty(..))
import Data.Monoid
class Monad m => Algebra sig m | m -> sig where
alg
:: Functor ctx
=> Handler ctx n m
-> sig n a
-> ctx ()
-> m (ctx a)
thread
:: ( Functor ctx1
, Functor ctx2
, Algebra sig m
)
=> Handler (Compose ctx1 ctx2) n m
-> sig n a
-> ctx1 (ctx2 ())
-> m (ctx1 (ctx2 a))
thread hdl sig = fmap getCompose . alg hdl sig . Compose
{-# INLINE thread #-}
run :: Identity a -> a
run = runIdentity
{-# INLINE run #-}
type Has eff sig m = (Members eff sig, Algebra sig m)
send :: (Member eff sig, Algebra sig m) => eff m a -> m a
send sig = runIdentity <$> alg (fmap Identity . runIdentity) (inj sig) (Identity ())
{-# INLINE send #-}
instance Algebra (Lift IO) IO where
alg hdl (LiftWith with) = with hdl
{-# INLINE alg #-}
instance Algebra (Lift Identity) Identity where
alg hdl (LiftWith with) = with hdl
{-# INLINE alg #-}
instance Algebra Choose NonEmpty where
alg _ Choose ctx = (True <$ ctx) :| [ False <$ ctx ]
{-# INLINE alg #-}
instance Algebra Empty Maybe where
alg _ Empty _ = Nothing
{-# INLINE alg #-}
instance Algebra (Error e) (Either e) where
alg hdl sig ctx = case sig of
L (Throw e) -> Left e
R (Catch m h) -> either (hdl . (<$ ctx) . h) pure (hdl (m <$ ctx))
{-# INLINE alg #-}
instance Algebra (Reader r) ((->) r) where
alg hdl sig ctx = case sig of
Ask -> (<$ ctx)
Local f m -> hdl (m <$ ctx) . f
{-# INLINE alg #-}
instance Algebra NonDet [] where
alg _ sig ctx = case sig of
L Empty -> []
R Choose -> [ True <$ ctx, False <$ ctx ]
{-# INLINE alg #-}
instance Monoid w => Algebra (Writer w) ((,) w) where
alg hdl sig ctx = case sig of
Tell w -> (w, ctx)
Listen m -> let (w, a) = hdl (m <$ ctx) in (w, (,) w <$> a)
Censor f m -> let (w, a) = hdl (m <$ ctx) in (f w, a)
{-# INLINE alg #-}
instance Algebra sig m => Algebra (Error e :+: sig) (Except.ExceptT e m) where
alg hdl sig ctx = case sig of
L (L (Throw e)) -> Except.throwE e
L (R (Catch m h)) -> Except.catchE (hdl (m <$ ctx)) (hdl . (<$ ctx) . h)
R other -> Except.ExceptT $ thread (either (pure . Left) Except.runExceptT ~<~ hdl) other (Right ctx)
{-# INLINE alg #-}
deriving instance Algebra sig m => Algebra sig (Identity.IdentityT m)
#if MIN_VERSION_base(4,12,0)
deriving instance Algebra sig m => Algebra sig (Ap m)
#endif
deriving instance Algebra sig m => Algebra sig (Alt m)
instance Algebra sig m => Algebra (Empty :+: sig) (Maybe.MaybeT m) where
alg hdl sig ctx = case sig of
L Empty -> Maybe.MaybeT (pure Nothing)
R other -> Maybe.MaybeT $ thread (maybe (pure Nothing) Maybe.runMaybeT ~<~ hdl) other (Just ctx)
{-# INLINE alg #-}
instance Algebra sig m => Algebra (Reader r :+: sig) (Reader.ReaderT r m) where
alg hdl sig ctx = case sig of
L Ask -> Reader.asks (<$ ctx)
L (Local f m) -> Reader.local f (hdl (m <$ ctx))
R other -> Reader.ReaderT $ \ r -> alg ((`Reader.runReaderT` r) . hdl) other ctx
{-# INLINE alg #-}
newtype RWSTF w s a = RWSTF { unRWSTF :: (a, s, w) }
deriving (Functor)
toRWSTF :: Monoid w => w -> (a, s, w) -> RWSTF w s a
toRWSTF w (a, s, w') = RWSTF (a, s, mappend w w')
{-# INLINE toRWSTF #-}
newtype Swap s a = Swap { getSwap :: (a, s) }
deriving (Functor)
swapAndLift :: Functor ctx => (ctx a, w) -> ctx (w, a)
swapAndLift p = (,) (snd p) <$> fst p
{-# INLINE swapAndLift #-}
#if MIN_VERSION_transformers(0,5,6)
instance (Algebra sig m, Monoid w) => Algebra (Reader r :+: Writer w :+: State s :+: sig) (RWS.CPS.RWST r w s m) where
alg hdl sig ctx = case sig of
L Ask -> RWS.CPS.asks (<$ ctx)
L (Local f m) -> RWS.CPS.local f (hdl (m <$ ctx))
R (L (Tell w)) -> ctx <$ RWS.CPS.tell w
R (L (Listen m)) -> swapAndLift <$> RWS.CPS.listen (hdl (m <$ ctx))
R (L (Censor f m)) -> RWS.CPS.censor f (hdl (m <$ ctx))
R (R (L Get)) -> RWS.CPS.gets (<$ ctx)
R (R (L (Put s))) -> ctx <$ RWS.CPS.put s
R (R (R other)) -> RWS.CPS.rwsT $ \ r s -> unRWSTF <$> thread ((\ (RWSTF (x, s, w)) -> toRWSTF w <$> RWS.CPS.runRWST x r s) ~<~ hdl) other (RWSTF (ctx, s, mempty))
{-# INLINE alg #-}
#endif
instance (Algebra sig m, Monoid w) => Algebra (Reader r :+: Writer w :+: State s :+: sig) (RWS.Lazy.RWST r w s m) where
alg hdl sig ctx = case sig of
L Ask -> RWS.Lazy.asks (<$ ctx)
L (Local f m) -> RWS.Lazy.local f (hdl (m <$ ctx))
R (L (Tell w)) -> ctx <$ RWS.Lazy.tell w
R (L (Listen m)) -> swapAndLift <$> RWS.Lazy.listen (hdl (m <$ ctx))
R (L (Censor f m)) -> RWS.Lazy.censor f (hdl (m <$ ctx))
R (R (L Get)) -> RWS.Lazy.gets (<$ ctx)
R (R (L (Put s))) -> ctx <$ RWS.Lazy.put s
R (R (R other)) -> RWS.Lazy.RWST $ \ r s -> unRWSTF <$> thread ((\ (RWSTF (x, s, w)) -> toRWSTF w <$> RWS.Lazy.runRWST x r s) ~<~ hdl) other (RWSTF (ctx, s, mempty))
{-# INLINE alg #-}
instance (Algebra sig m, Monoid w) => Algebra (Reader r :+: Writer w :+: State s :+: sig) (RWS.Strict.RWST r w s m) where
alg hdl sig ctx = case sig of
L Ask -> RWS.Strict.asks (<$ ctx)
L (Local f m) -> RWS.Strict.local f (hdl (m <$ ctx))
R (L (Tell w)) -> ctx <$ RWS.Strict.tell w
R (L (Listen m)) -> swapAndLift <$> RWS.Strict.listen (hdl (m <$ ctx))
R (L (Censor f m)) -> RWS.Strict.censor f (hdl (m <$ ctx))
R (R (L Get)) -> RWS.Strict.gets (<$ ctx)
R (R (L (Put s))) -> ctx <$ RWS.Strict.put s
R (R (R other)) -> RWS.Strict.RWST $ \ r s -> unRWSTF <$> thread ((\ (RWSTF (x, s, w)) -> toRWSTF w <$> RWS.Strict.runRWST x r s) ~<~ hdl) other (RWSTF (ctx, s, mempty))
{-# INLINE alg #-}
instance Algebra sig m => Algebra (State s :+: sig) (State.Lazy.StateT s m) where
alg hdl sig ctx = case sig of
L Get -> State.Lazy.gets (<$ ctx)
L (Put s) -> ctx <$ State.Lazy.put s
R other -> State.Lazy.StateT $ \ s -> getSwap <$> thread (fmap Swap . uncurry State.Lazy.runStateT . getSwap ~<~ hdl) other (Swap (ctx, s))
{-# INLINE alg #-}
instance Algebra sig m => Algebra (State s :+: sig) (State.Strict.StateT s m) where
alg hdl sig ctx = case sig of
L Get -> State.Strict.gets (<$ ctx)
L (Put s) -> ctx <$ State.Strict.put s
R other -> State.Strict.StateT $ \ s -> getSwap <$> thread (fmap Swap . uncurry State.Strict.runStateT . getSwap ~<~ hdl) other (Swap (ctx, s))
{-# INLINE alg #-}
#if MIN_VERSION_transformers(0,5,6)
instance (Algebra sig m, Monoid w) => Algebra (Writer w :+: sig) (Writer.CPS.WriterT w m) where
alg hdl sig ctx = case sig of
L (Tell w) -> ctx <$ Writer.CPS.tell w
L (Listen m) -> swapAndLift <$> Writer.CPS.listen (hdl (m <$ ctx))
L (Censor f m) -> Writer.CPS.censor f (hdl (m <$ ctx))
R other -> Writer.CPS.writerT $ getSwap <$> thread ((\ (Swap (x, s)) -> Swap . fmap (mappend s) <$> Writer.CPS.runWriterT x) ~<~ hdl) other (Swap (ctx, mempty))
{-# INLINE alg #-}
#endif
instance (Algebra sig m, Monoid w) => Algebra (Writer w :+: sig) (Writer.Lazy.WriterT w m) where
alg hdl sig ctx = case sig of
L (Tell w) -> ctx <$ Writer.Lazy.tell w
L (Listen m) -> swapAndLift <$> Writer.Lazy.listen (hdl (m <$ ctx))
L (Censor f m) -> Writer.Lazy.censor f (hdl (m <$ ctx))
R other -> Writer.Lazy.WriterT $ getSwap <$> thread ((\ (Swap (x, s)) -> Swap . fmap (mappend s) <$> Writer.Lazy.runWriterT x) ~<~ hdl) other (Swap (ctx, mempty))
{-# INLINE alg #-}
instance (Algebra sig m, Monoid w) => Algebra (Writer w :+: sig) (Writer.Strict.WriterT w m) where
alg hdl sig ctx = case sig of
L (Tell w) -> ctx <$ Writer.Strict.tell w
L (Listen m) -> swapAndLift <$> Writer.Strict.listen (hdl (m <$ ctx))
L (Censor f m) -> Writer.Strict.censor f (hdl (m <$ ctx))
R other -> Writer.Strict.WriterT $ getSwap <$> thread ((\ (Swap (x, s)) -> Swap . fmap (mappend s) <$> Writer.Strict.runWriterT x) ~<~ hdl) other (Swap (ctx, mempty))
{-# INLINE alg #-}