in-other-words-0.2.0.0: A higher-order effect system where the sky's the limit
Safe HaskellNone
LanguageHaskell2010

Control.Effect.Type.ListenPrim

Synopsis

Effects

data ListenPrim o :: Effect where Source #

A primitive effect that may be used for interpreters of connected Tell and Listen effects.

This combines Tell and Listen. This may be relevant if there are monad transformers that may only lift listen if they also have access to tell.

ListenPrim is only used as a primitive effect. If you define a Carrier that relies on a novel non-trivial monad transformer t, then you need to make a Monoid o => ThreadsEff t (ListenPrim o) instance (if possible). threadListenPrim and threadListenPrimViaClass can help you with that.

The following threading constraints accept ListenPrim:

Constructors

ListenPrimTell :: o -> ListenPrim o m () 
ListenPrimListen :: m a -> ListenPrim o m (o, a) 

Instances

Instances details
Monoid s => ThreadsEff ListT (ListenPrim s) Source # 
Instance details

Defined in Control.Monad.Trans.List.Church

Methods

threadEff :: Monad m => (forall x. ListenPrim s m x -> m x) -> ListenPrim s (ListT m) a -> ListT m a Source #

(Monoid w, Carrier m, Threaders '[SteppedThreads] m p) => PrimHandler ListenSteppedH (ListenPrim w) (SteppedC (Tell w) m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

(Reifies s (ReifiedEffAlgebra (ListenPrim o) m), Monoid o, Monad m) => MonadWriter o (ViaAlg s (ListenPrim o) m) Source # 
Instance details

Defined in Control.Effect.Type.ListenPrim

Methods

writer :: (a, o) -> ViaAlg s (ListenPrim o) m a #

tell :: o -> ViaAlg s (ListenPrim o) m () #

listen :: ViaAlg s (ListenPrim o) m a -> ViaAlg s (ListenPrim o) m (a, o) #

pass :: ViaAlg s (ListenPrim o) m (a, o -> o) -> ViaAlg s (ListenPrim o) m a #

Monoid threadedMonoid => ThreadsEff (ExceptT e) (ListenPrim threadedMonoid) Source # 
Instance details

Defined in Control.Effect.Type.ListenPrim

Methods

threadEff :: Monad m => (forall x. ListenPrim threadedMonoid m x -> m x) -> ListenPrim threadedMonoid (ExceptT e m) a -> ExceptT e m a Source #

Monoid s => ThreadsEff (WriterT s) (ListenPrim o) Source # 
Instance details

Defined in Control.Effect.Type.ListenPrim

Methods

threadEff :: Monad m => (forall x. ListenPrim o m x -> m x) -> ListenPrim o (WriterT s m) a -> WriterT s m a Source #

Monoid threadedMonoid => ThreadsEff (StateT s) (ListenPrim threadedMonoid) Source # 
Instance details

Defined in Control.Effect.Type.ListenPrim

Methods

threadEff :: Monad m => (forall x. ListenPrim threadedMonoid m x -> m x) -> ListenPrim threadedMonoid (StateT s m) a -> StateT s m a Source #

Monoid threadedMonoid => ThreadsEff (ReaderT i) (ListenPrim threadedMonoid) Source # 
Instance details

Defined in Control.Effect.Type.ListenPrim

Methods

threadEff :: Monad m => (forall x. ListenPrim threadedMonoid m x -> m x) -> ListenPrim threadedMonoid (ReaderT i m) a -> ReaderT i m a Source #

Monoid threadedMonoid => ThreadsEff (StateT s) (ListenPrim threadedMonoid) Source # 
Instance details

Defined in Control.Effect.Type.ListenPrim

Methods

threadEff :: Monad m => (forall x. ListenPrim threadedMonoid m x -> m x) -> ListenPrim threadedMonoid (StateT s m) a -> StateT s m a Source #

Monoid s => ThreadsEff (WriterT s) (ListenPrim o) Source # 
Instance details

Defined in Control.Effect.Type.ListenPrim

Methods

threadEff :: Monad m => (forall x. ListenPrim o m x -> m x) -> ListenPrim o (WriterT s m) a -> WriterT s m a Source #

Monoid s => ThreadsEff (WriterT s) (ListenPrim o) Source # 
Instance details

Defined in Control.Effect.Type.ListenPrim

Methods

threadEff :: Monad m => (forall x. ListenPrim o m x -> m x) -> ListenPrim o (WriterT s m) a -> WriterT s m a Source #

Monoid w => ThreadsEff (FreeT f) (ListenPrim w) Source # 
Instance details

Defined in Control.Monad.Trans.Free.Church.Alternate

Methods

threadEff :: Monad m => (forall x. ListenPrim w m x -> m x) -> ListenPrim w (FreeT f m) a -> FreeT f m a Source #

Threading utilities

threadListenPrim :: forall o t m a. (MonadTrans t, Monad m) => (forall x. (forall y. ListenPrim o m y -> m y) -> t m x -> t m (o, x)) -> (forall x. ListenPrim o m x -> m x) -> ListenPrim o (t m) a -> t m a Source #

Construct a valid definition of threadEff for a ThreadsEff t (ListenPrim o) instance only be specifying how ListenPrimListen should be lifted.

This uses lift to lift ListenPrimTell.

threadListenPrimViaClass :: forall o t m a. (Monoid o, Monad m) => (RepresentationalT t, MonadTrans t, forall b. MonadWriter o b => MonadWriter o (t b)) => (forall x. ListenPrim o m x -> m x) -> ListenPrim o (t m) a -> t m a Source #

A valid definition of threadEff for a ThreadsEff t (ListenPrim o) instance, given that t lifts MonadWriter w.

BEWARE: threadListenPrimViaClass is only safe if the implementation of listen for t m only makes use of listen and tell for m, and not pass.