{-# LANGUAGE DerivingVia, MagicHash #-}
module Control.Effect.BaseControl
(
BaseControl
, withLowerToBase
, gainBaseControl
, runBaseControl
, baseControlToFinal
, MonadBaseControl(..)
, control
, threadBaseControlViaClass
, powerAlgBaseControl
, powerAlgBaseControlFinal
, GainBaseControlC(..)
, BaseControlC
, BaseControlToFinalC
) where
import Data.Coerce
import Control.Monad
import Control.Effect
import Control.Effect.Carrier
import Control.Effect.Type.Internal.BaseControl
import Control.Effect.Internal.BaseControl
import Control.Effect.Internal.Itself
import Control.Effect.Internal.Utils
import Control.Monad.Trans.Identity
import Control.Monad.Trans.Control
import GHC.Exts (Proxy#, proxy#)
newtype GainBaseControlC b z m a = GainBaseControlC {
unGainBaseControlC :: m a
}
deriving ( Functor, Applicative, Monad
, Alternative, MonadPlus
, MonadFix, MonadFail, MonadIO
, MonadThrow, MonadCatch, MonadMask
, Carrier
)
deriving (MonadTrans, MonadTransControl) via IdentityT
instance (Monad m, MonadBase b z, Coercible z m)
=> MonadBase b (GainBaseControlC b z m) where
liftBase = coerce #. liftBase @_ @z
{-# INLINE liftBase #-}
instance (Monad m, MonadBaseControl b z, Coercible z m)
=> MonadBaseControl b (GainBaseControlC b z m) where
type StM (GainBaseControlC b z m) a = StM z a
liftBaseWith m = coerce $ liftBaseWith @_ @z $ \lower -> m (coerceTrans lower)
{-# INLINE liftBaseWith #-}
restoreM =
coerce (restoreM @_ @z @a) :: forall a. StM z a -> GainBaseControlC b z m a
{-# INLINE restoreM #-}
newtype Stateful m a = Stateful { getStateful :: StM m a }
withLowerToBase :: forall b m a
. Eff (BaseControl b) m
=> (forall f. (forall x. m x -> b (f x)) -> b (f a))
-> m a
withLowerToBase main = join $ send $
GainBaseControl @b $ \(_ :: Proxy# z) -> coerceM $ control @_ @z $ \lower ->
getStateful @z @a <$> main (fmap (Stateful @z) . coerceTrans lower)
{-# INLINE withLowerToBase #-}
gainBaseControl
:: forall b m a
. Eff (BaseControl b) m
=> ( forall z
. (MonadBaseControl b z, Coercible z m)
=> GainBaseControlC b z m a
)
-> m a
gainBaseControl main = join $ send $
GainBaseControl @b (\(_ :: Proxy# z) -> unGainBaseControlC (main @z))
{-# INLINE gainBaseControl #-}
runBaseControl :: Carrier m => BaseControlC m a -> m a
runBaseControl = unBaseControlC
{-# INLINE runBaseControl #-}
data BaseControlToFinalH
type BaseControlToFinalC b = InterpretPrimC BaseControlToFinalH (BaseControl b)
instance ( MonadBaseControl b m
, Carrier m
)
=> PrimHandler BaseControlToFinalH (BaseControl b) m where
effPrimHandler (GainBaseControl main) = return $ main (proxy# :: Proxy# m)
{-# INLINEABLE effPrimHandler #-}
baseControlToFinal :: (MonadBaseControl b m, Carrier m)
=> BaseControlToFinalC b m a -> m a
baseControlToFinal = interpretPrimViaHandler
{-# INLINE baseControlToFinal #-}
powerAlgBaseControl :: forall m p a
. Monad m
=> Algebra' p m a
-> Algebra' (BaseControl m ': p) m a
powerAlgBaseControl alg = powerAlg alg $ \case
GainBaseControl main -> return $ main (proxy# :: Proxy# (Itself m))
{-# INLINEABLE powerAlgBaseControl #-}
powerAlgBaseControlFinal :: forall b m p a
. MonadBaseControl b m
=> Algebra' p m a
-> Algebra' (BaseControl b ': p) m a
powerAlgBaseControlFinal alg = powerAlg alg $ \case
GainBaseControl main -> return $ main (proxy# :: Proxy# m)
{-# INLINEABLE powerAlgBaseControlFinal #-}