[Haskell-cafe] combining monads with IO

2009-06-25 Thread Richard Silverman


Hi all,

I'm puzzled by something. Suppose I have some code that does lots of 
IO, and also occasionally refers to some global state. No problem, use 
ReaderT for the state, combining with the IO monad. Except... since IO 
is on the bottom, simple uses of do-notation such as foo - ask work 
in the Reader monad, and to access the IO monad, I need to lift, e.g. 
(bar - liftIO getLine). If my code does lots of IO, this is *very* 
ugly -- the code is littered with lift functions!  Is there no cleaner 
way to do this?


Thanks,

- Richard

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] combining monads with IO

2009-06-25 Thread Martijn van Steenbergen

Richard Silverman wrote:
I'm puzzled by something. Suppose I have some code that does lots of IO, 
and also occasionally refers to some global state. No problem, use 
ReaderT for the state, combining with the IO monad. Except... since IO 
is on the bottom, simple uses of do-notation such as foo - ask work 
in the Reader monad, and to access the IO monad, I need to lift, e.g. 
(bar - liftIO getLine). If my code does lots of IO, this is *very* ugly 
-- the code is littered with lift functions!  Is there no cleaner way to 
do this?


Not that I know of. However, you can usually group IO-statements 
together in one bigger block:


blah = do
  foo - ask
  biz - liftIO $ do
meep
bop foo
bleep foo
  zap biz

etc.

And if there is a limited number of specific functions you need to lift 
often, you can write generalised MonadIO-based versions of these so that 
you can call them directly from the monad transformer:


  getLine :: MonadIO m = m String
  getLine = liftIO SystemIO.getLine

Assuming an appropriate MonadIO instance of ReaderT, of course.

Does that help?

Martijn.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] combining monads with IO

2009-06-25 Thread Matthias Görgens
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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] combining monads with IO

2009-06-25 Thread Miguel Mitrofanov

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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] combining monads with IO

2009-06-25 Thread Matthias Görgens
Thanks.  Can I add something like fail?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] combining monads with IO

2009-06-25 Thread Miguel Mitrofanov

Sure:

newtype IOMayfail a = IOMayfail {runIOMayfail :: MaybeT IO a}

instance Monad IOMayfail where
  return = IOMayfail . return
  IOMayfail m = f = IOMayfail $ m = runIOMayfail . f
  fail = whatever you like

Matthias Görgens wrote on 25.06.2009 17:28:

Thanks.  Can I add something like fail?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] combining monads with IO

2009-06-25 Thread wren ng thornton

Richard Silverman wrote:


Hi all,

I'm puzzled by something. Suppose I have some code that does lots of IO, 
and also occasionally refers to some global state. No problem, use 
ReaderT for the state, combining with the IO monad. Except... since IO 
is on the bottom, simple uses of do-notation such as foo - ask work 
in the Reader monad, and to access the IO monad, I need to lift, e.g. 
(bar - liftIO getLine). If my code does lots of IO, this is *very* ugly 
-- the code is littered with lift functions!  Is there no cleaner way to 
do this?


Depending on the exact structure of your program, embracing imperativism 
may help. That is, you can use IORefs (or STRefs, or...) to store your 
global state instead of using StateT. Sometimes it helps, sometimes not; 
it depends a lot on the structure of the state, how fond you are of 
combinators, how you want to pass the IORefs down to the combinators,...



The cleanest approach to issues like this is usually to wrap a newtype 
wrapper around your specialty monad and use -XGeneralizedNewtypeDeriving 
to hoist all the layers up to the top. Or if you want to ensure 
portability then you can hand-write all the boilerplate instances for 
MonadFoo MyMonad. Depending on how you use IO, you'll want to mix this 
with judicious use of liftIO or define some wrappers or a typeclass for 
lifting your common IO functions to work on MyMonad.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe