[Haskell-cafe] combining monads with IO
Miguel Mitrofanov
miguelimo38 at yandex.ru
Thu Jun 25 09:26:28 EDT 2009
Well, without "fail" part:
newtype IOMayfail a = IOMayfail (MaybeT IO a) deriving Monad
Matthias Görgens wrote on 25.06.2009 17:14:
> By the way, how would one write the following with Monad Transformers?
>
>> newtype IOMayfail a = IOMayfail (IO (Maybe a))
>
>> instance Monad IOMayfail where
>> return = IOMayfail . return . return
>> (>>=) a f = IOMayfail (bind (run a) (run . f))
>> fail s = trace s (IOMayfail $ return Nothing)
>
>> run :: IOMayfail a -> IO (Maybe a)
>> run (IOMayfail a) = a
>
>> bind :: IO (Maybe a) -> (a -> IO (Maybe b)) -> IO (Maybe b)
>> bind a f = do r <- a
>> case r of Nothing -> return Nothing
>> Just r' -> f r'
>> Lift :: IO a -> IOMayfail a
>> lift f = IOMayfail (f >>= return . return)
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
More information about the Haskell-Cafe
mailing list