alternators-1.0.0.0: Handy functions when using transformers.

Safe HaskellSafe
LanguageHaskell2010

Control.Monad.Delegate

Synopsis

Documentation

class Monad m => MonadDelegate r m | m -> r where Source #

Minimal complete definition

delegate

Methods

delegate :: ((a -> m r) -> m r) -> m a Source #

The inverse of delegate is bind

(>>=) :: Monad m => m a -> (a -> m r) -> m r
Instances
MonadDelegate r m => MonadDelegate r (MaybeT m) Source #

Passthrough instance

Instance details

Defined in Control.Monad.Delegate

Methods

delegate :: ((a -> MaybeT m r) -> MaybeT m r) -> MaybeT m a Source #

MonadDelegate r m => MonadDelegate r (ExceptT e m) Source #

Passthrough instance

Instance details

Defined in Control.Monad.Delegate

Methods

delegate :: ((a -> ExceptT e m r) -> ExceptT e m r) -> ExceptT e m a Source #

MonadDelegate r m => MonadDelegate r (IdentityT m) Source #

Passthrough instance

Instance details

Defined in Control.Monad.Delegate

Methods

delegate :: ((a -> IdentityT m r) -> IdentityT m r) -> IdentityT m a Source #

MonadDelegate r m => MonadDelegate r (ReaderT env m) Source #

Passthrough instance

Instance details

Defined in Control.Monad.Delegate

Methods

delegate :: ((a -> ReaderT env m r) -> ReaderT env m r) -> ReaderT env m a Source #

Monad m => MonadDelegate r (ContT r m) Source #

Instance that does real work using continuations

Instance details

Defined in Control.Monad.Delegate

Methods

delegate :: ((a -> ContT r m r) -> ContT r m r) -> ContT r m a Source #

finish :: forall a r m. MonadDelegate r m => m r -> m a Source #

Only handle with given monad, and ignore anything else. This means subseqent fmap, aps, binds are always ignored. forall so TypeApplications can be used to specify the type of a

multitask :: MonadDelegate r m => ((a -> m r) -> (b -> m r) -> m r) -> m (Either a b) Source #

Convert two handler to a monad that may fire two possibilities The inverse is bind2.

bind2 :: Monad m => m (Either a b) -> (a -> m r) -> (b -> m r) -> m r Source #

Convert a monad that fires two possibilites to a two handlers.

bindRight :: Monad m => m (Either a b) -> (b -> m c) -> m (Either a c) Source #

bind only the Right possibility.

bindLeft :: Monad m => m (Either a b) -> (a -> m c) -> m (Either c b) Source #

bind only the Left possibility.

finishLeft :: MonadDelegate r m => m (Either r b) -> m b Source #

finish the Left possibility

finishRight :: MonadDelegate r m => m (Either a r) -> m a Source #

finish the Right possibility

maybeDelegate :: MonadDelegate r m => r -> m (Maybe a) -> m a Source #

maybe delegate the Just value, or just use the r.