polysemy-1.1.0.0: Higher-order, low-boilerplate, zero-cost free monads.

Safe HaskellNone
LanguageHaskell2010

Polysemy.Output

Contents

Synopsis

Effect

data Output o m a where Source #

An effect capable of sending messages. Useful for streaming output and for logging.

Constructors

Output :: o -> Output o m () 
Instances
type DefiningModule (Output :: Type -> k -> Type -> Type) Source # 
Instance details

Defined in Polysemy.Output

type DefiningModule (Output :: Type -> k -> Type -> Type) = "Polysemy.Output"

Actions

output :: forall o r. MemberWithError (Output o) r => o -> Sem r () Source #

Interpretations

runOutputList :: forall o r a. Sem (Output o ': r) a -> Sem r ([o], a) Source #

Run an Output effect by transforming it into a list of its values.

Since: 1.0.0.0

runOutputMonoid :: forall o m r a. Monoid m => (o -> m) -> Sem (Output o ': r) a -> Sem r (m, a) Source #

Run an Output effect by transforming it into a monoid.

Since: 1.0.0.0

runOutputMonoidAssocR :: forall o m r a. Monoid m => (o -> m) -> Sem (Output o ': r) a -> Sem r (m, a) Source #

Like runOutputMonoid, but right-associates uses of <>.

This asymptotically improves performance if the time complexity of <> for the Monoid depends only on the size of the first argument.

You should always use this instead of runOutputMonoid if the monoid is a list, such as String.

runOutputMonoidIORef :: forall o m r a. (Monoid m, Member (Embed IO) r) => IORef m -> (o -> m) -> Sem (Output o ': r) a -> Sem r a Source #

Run an Output effect by transforming it into atomic operations over an IORef.

runOutputMonoidTVar :: forall o m r a. (Monoid m, Member (Embed IO) r) => TVar m -> (o -> m) -> Sem (Output o ': r) a -> Sem r a Source #

Run an Output effect by transforming it into atomic operations over a TVar.

ignoreOutput :: Sem (Output o ': r) a -> Sem r a Source #

Run an Output effect by ignoring it.

Since: 1.0.0.0

runOutputBatched :: forall o r a. Member (Output [o]) r => Int -> Sem (Output o ': r) a -> Sem r a Source #

Accumulate outputs so they are delayed until they reach at least size size.

If size is 0, this interpretation will not emit anything in the resulting Output effect.

Since: 1.0.0.0

runOutputSem :: (o -> Sem r ()) -> Sem (Output o ': r) a -> Sem r a Source #

Runs an Output effect by running a monadic action for each of its values.