operating on nested monads

Hello everyone, I have some operations that have to be done in sequence, with each one having the result of the previous as input. They can fail, so they have signature a -> Maybe b Checking for error can be quite tedious so I use monadic operations: f :: a -> Maybe b do y <- foo x z <- boo y moo z The problems arise when I try to do the same thing within the IO Monad, i.e. the functions have signature a->IO (Maybe b) How can I achieve the same effect (if it is ever possible)? I feel like it should be something almost trivial, but I really can't get it. Thanks Marco

Hello, I was wondering the same thing, here is what I came up with: module Main where import Control.Monad import Data.Maybe import System.IO newtype MaybeIO a = MaybeIO { unMaybeIO :: IO (Maybe a) } instance Monad MaybeIO where (>>=) k f = MaybeIO (do ma <- unMaybeIO k case ma of Nothing -> return Nothing Just a -> unMaybeIO (f a) ) return a = MaybeIO (return (Just a)) ioMaybe :: IO a -> MaybeIO a ioMaybe i = MaybeIO $ do v <- i return (Just v) maybeGetChar :: IO (Maybe Char) maybeGetChar = do hSetBuffering stdin NoBuffering c <- getChar let mc = case c of 'a' -> Just 'a' 'b' -> Just 'b' 'c' -> Just 'c' o -> Nothing return mc getChars :: IO (Maybe (Char,Char,Char,Char)) getChars = unMaybeIO $ do v1 <- MaybeIO maybeGetChar v2 <- MaybeIO maybeGetChar ioMaybe (putStrLn "\nhalf-way there...") v3 <- MaybeIO maybeGetChar v4 <- MaybeIO maybeGetChar return (v1, v2, v3, v4) main = do maybeChars <- getChars putStrLn (show maybeChars) NOTE: if you run this program under emacs it won't work quite right because emacs will do line buffering, but the program excepts no buffering. I am not sure if there is a better way to do this or not. It seems like a bit of a pain to have to keep using MaybeIO, unMaybeIO, and ioMaybe... Jeremy Shaw. At Fri, 26 Mar 2004 16:21:08 +0100, Marco Righele wrote:
Hello everyone,
I have some operations that have to be done in sequence, with each one having the result of the previous as input. They can fail, so they have signature a -> Maybe b Checking for error can be quite tedious so I use monadic operations:
f :: a -> Maybe b do y <- foo x z <- boo y moo z
The problems arise when I try to do the same thing within the IO Monad, i.e. the functions have signature a->IO (Maybe b)
How can I achieve the same effect (if it is ever possible)? I feel like it should be something almost trivial, but I really can't get it.
Thanks Marco
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Marco Righele wrote:
Hello everyone,
I have some operations that have to be done in sequence, with each one having the result of the previous as input. They can fail, so they have signature a -> Maybe b Checking for error can be quite tedious so I use monadic operations:
f :: a -> Maybe b do y <- foo x z <- boo y moo z
The problems arise when I try to do the same thing within the IO Monad, i.e. the functions have signature a->IO (Maybe b)
How can I achieve the same effect (if it is ever possible)? I feel like it should be something almost trivial, but I really can't get it.
Hi. How about giving your functions the type a -> IO b and representing failure with either 'fail', 'ioError' or 'throwError'? They propagate the same way as Nothing in the Maybe monad. http://www.haskell.org/ghc/docs/latest/html/libraries/base/System.IO.Error.h... http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control.Monad.Err... Regards, Tom

G'day Marco.
Quoting Marco Righele
How can I achieve the same effect (if it is ever possible)? I feel like it should be something almost trivial, but I really can't get it.
One approach is to use a monad which works like Maybe, but as a monad transformer over IO. You might want to try NegateT, which does pretty much precisely this: http://cvs.sourceforge.net/viewcvs.py/hfl/hfl/mtl/Negate.hs?rev=1.2 Cheers, Andrew Bromage
participants (4)
-
ajb@spamcop.net
-
Jeremy Shaw
-
Marco Righele
-
Tom Pledger