[Haskell-cafe] combining monads with IO

Matthias Görgens matthias.goergens at googlemail.com
Thu Jun 25 09:14:16 EDT 2009


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)


More information about the Haskell-Cafe mailing list