Re: [Haskell-cafe] operating on nested monads

2004-03-28 Thread MR K P SCHUPKE
For operating on nested monads is do: declare a class MonadIO which contains the IO functions along with monad monad-transformer lifted versions, for example: class Monad m = MonadIO m where ioPrint :: Show a = a - m () instance MonadIO IO where ioPrint = print instance (MonadIO m,MonadT

Re: [Haskell-cafe] operating on nested monads

2004-03-28 Thread ajb
G'day Marco. Quoting Marco Righele [EMAIL PROTECTED]: 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

Re: [Haskell-cafe] operating on nested monads

2004-03-27 Thread Tom Pledger
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

[Haskell-cafe] operating on nested monads

2004-03-26 Thread Marco Righele
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

Re: [Haskell-cafe] operating on nested monads

2004-03-26 Thread Jeremy Shaw
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