|
Control.Monad.Maybe | Portability | non-portable (multi-parameter type classes, undecidable instances) | Stability | experimental |
|
|
|
|
|
Description |
The MaybeT monad. See
http://www.haskell.org/haskellwiki/New_monads/MaybeT for more widely-used
version. Our Functor instance and our implementation of >>= are
borrowed from there.
- Computation type:
- Computations which may fail or return nothing.
- Binding strategy:
- Failure returns the value Nothing, bypassing any
bound functions which follow. Success returns a value wrapped in Just.
- Useful for:
- Building computations from steps which may fail. No error
information is returned. (If error information is required, see
Error.)
|
|
Synopsis |
|
|
|
Documentation |
|
newtype MaybeT m a |
A monad transformer which adds Maybe semantics to an existing monad.
| Constructors | MaybeT | | runMaybeT :: (m (Maybe a)) | |
|
| Instances | |
|
|
Limitations
|
|
The instance MonadPlus is not provided, because it has ambiguous
semantics. It could refer to either
instance MonadPlus m => MonadPlus (MaybeT m)
...lifting the semantics of an underlying MaybeT monad, or
instance MonadPlus (MaybeT m)
...with semantics similar to MonadPlus Maybe.
|
|
Example
|
|
Here is an example that shows how to use MaybeT to propagate an
end-of-file condition in the IO monad. In the example below, both
maybeReadLine and failIfQuit may cause a failure, which will propagate
out to main without further intervention.
import System.Console.Readline
import Data.Maybe
import Control.Monad
import Control.Monad.Trans
import Control.Monad.Maybe
-- 'MaybeIO' is the type of computations which do IO, and which may fail.
type MaybeIO = MaybeT IO
-- 'readline' already has type 'String -> IO (Maybe String)'; we just need
-- to wrap it.
maybeReadLine :: String -> MaybeIO String
maybeReadLine prompt = MaybeT (readline prompt)
-- Fail if 'str' equals "quit".
failIfQuit :: (Monad m) => String -> m ()
failIfQuit str = when (str == "quit") (fail "Quitting")
-- This task may fail in several places. Try typing Control-D or "quit" at
-- any prompt.
concatTwoInputs :: MaybeIO ()
concatTwoInputs = do
s1 <- maybeReadLine "String 1> "
failIfQuit s1
s2 <- maybeReadLine "String 2> "
failIfQuit s2
liftIO (putStrLn ("Concatenated: " ++ s1 ++ s2))
-- Loop until failure.
main :: IO ()
main = do
result <- runMaybeT concatTwoInputs
if isNothing result
then putStrLn "Bye!"
else main
|
|
Produced by Haddock version 0.8 |