| Copyright | (c) 2007 Yitzak Gale, Eric Kidd | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | R.Paterson@city.ac.uk | 
| Stability | experimental | 
| Portability | portable | 
| Safe Haskell | Safe | 
| Language | Haskell98 | 
Control.Monad.Trans.Maybe
Description
The MaybeT monad transformer extends a monad with the ability to exit
 the computation without returning a value.
A sequence of actions produces a value only if all the actions in the sequence do. If one exits, the rest of the sequence is skipped and the composite action exits.
For a variant allowing a range of exception values, see Control.Monad.Trans.Except.
- newtype MaybeT m a = MaybeT {}
- mapMaybeT :: (m (Maybe a) -> n (Maybe b)) -> MaybeT m a -> MaybeT n b
- maybeToExceptT :: Functor m => e -> MaybeT m a -> ExceptT e m a
- exceptToMaybeT :: Functor m => ExceptT e m a -> MaybeT m a
- liftCallCC :: CallCC m (Maybe a) (Maybe b) -> CallCC (MaybeT m) a b
- liftCatch :: Catch e m (Maybe a) -> Catch e (MaybeT m) a
- liftListen :: Monad m => Listen w m (Maybe a) -> Listen w (MaybeT m) a
- liftPass :: Monad m => Pass w m (Maybe a) -> Pass w (MaybeT m) a
The MaybeT monad transformer
The parameterizable maybe monad, obtained by composing an arbitrary
 monad with the Maybe monad.
Computations are actions that may produce a value or exit.
The return function yields a computation that produces that
 value, while >>= sequences two subcomputations, exiting if either
 computation does.
Instances
| MonadTrans MaybeT Source | |
| Monad m => Monad (MaybeT m) Source | |
| Functor m => Functor (MaybeT m) Source | |
| MonadFix m => MonadFix (MaybeT m) Source | |
| (Functor m, Monad m) => Applicative (MaybeT m) Source | |
| Foldable f => Foldable (MaybeT f) Source | |
| Traversable f => Traversable (MaybeT f) Source | |
| MonadZip m => MonadZip (MaybeT m) Source | |
| (Functor m, Monad m) => Alternative (MaybeT m) Source | |
| Monad m => MonadPlus (MaybeT m) Source | |
| MonadIO m => MonadIO (MaybeT m) Source | |
| Show1 m => Show1 (MaybeT m) Source | |
| Read1 m => Read1 (MaybeT m) Source | |
| Ord1 m => Ord1 (MaybeT m) Source | |
| Eq1 m => Eq1 (MaybeT m) Source | |
| (Eq1 m, Eq a) => Eq (MaybeT m a) Source | |
| (Ord1 m, Ord a) => Ord (MaybeT m a) Source | |
| (Read1 m, Read a) => Read (MaybeT m a) Source | |
| (Show1 m, Show a) => Show (MaybeT m a) Source | 
Conversion
maybeToExceptT :: Functor m => e -> MaybeT m a -> ExceptT e m a Source
exceptToMaybeT :: Functor m => ExceptT e m a -> MaybeT m a Source
Lifting other operations
liftCallCC :: CallCC m (Maybe a) (Maybe b) -> CallCC (MaybeT m) a b Source
Lift a callCC operation to the new monad.
liftCatch :: Catch e m (Maybe a) -> Catch e (MaybeT m) a Source
Lift a catchE operation to the new monad.