{-# LANGUAGE DeriveFunctor, ExistentialQuantification, FlexibleContexts, FlexibleInstances, GeneralizedNewtypeDeriving, LambdaCase, MultiParamTypeClasses, StandaloneDeriving, TypeOperators, UndecidableInstances #-}
module Control.Effect.Cull
( Cull(..)
, cull
, runCull
, CullC(..)
, runNonDetOnce
, OnceC(..)
) where
import Control.Applicative (Alternative(..))
import Control.Effect.Carrier
import Control.Effect.NonDet
import Control.Effect.Reader
import Control.Effect.Sum
import Control.Monad (MonadPlus(..))
import Control.Monad.Fail
import Control.Monad.IO.Class
import Control.Monad.Trans.Class
import Prelude hiding (fail)
data Cull m k
= forall a . Cull (m a) (a -> k)
deriving instance Functor (Cull m)
instance HFunctor Cull where
hmap f (Cull m k) = Cull (f m) k
{-# INLINE hmap #-}
instance Effect Cull where
handle state handler (Cull m k) = Cull (handler (m <$ state)) (handler . fmap k)
{-# INLINE handle #-}
cull :: (Carrier sig m, Member Cull sig) => m a -> m a
cull m = send (Cull m pure)
runCull :: Alternative m => CullC m a -> m a
runCull (CullC m) = runNonDetC (runReader False m) ((<|>) . pure) empty
newtype CullC m a = CullC { runCullC :: ReaderC Bool (NonDetC m) a }
deriving (Applicative, Functor, Monad, MonadFail, MonadIO)
instance Alternative (CullC m) where
empty = CullC empty
{-# INLINE empty #-}
l <|> r = CullC $ ReaderC $ \ cull -> NonDetC $ \ cons nil -> do
runNonDetC (runReader cull (runCullC l))
(\ a as -> cons a (if cull then nil else as))
(runNonDetC (runReader cull (runCullC r)) cons nil)
{-# INLINE (<|>) #-}
instance MonadPlus (CullC m)
instance MonadTrans CullC where
lift = CullC . lift . lift
{-# INLINE lift #-}
instance (Carrier sig m, Effect sig) => Carrier (Cull :+: NonDet :+: sig) (CullC m) where
eff (L (Cull m k)) = CullC (local (const True) (runCullC m)) >>= k
eff (R (L Empty)) = empty
eff (R (L (Choose k))) = k True <|> k False
eff (R (R other)) = CullC (eff (R (R (handleCoercible other))))
{-# INLINE eff #-}
runNonDetOnce :: (Alternative f, Carrier sig m, Effect sig) => OnceC m a -> m (f a)
runNonDetOnce = runNonDet . runCull . cull . runOnceC
newtype OnceC m a = OnceC { runOnceC :: CullC (NonDetC m) a }
deriving (Alternative, Applicative, Functor, Monad, MonadFail, MonadIO, MonadPlus)
instance (Carrier sig m, Effect sig) => Carrier (NonDet :+: sig) (OnceC m) where
eff = OnceC . eff . R . R . handleCoercible
{-# INLINE eff #-}