[Haskell-cafe] Re: Nested Monads Questions

2006-08-12 Thread Dan Doel

On 8/12/06, Dan Doel <[EMAIL PROTECTED]> wrote:

Viola.

Egads!

In my haste, I failed to note that my mapping from the type synonym to
the data constructor only works for a single nested transformer. lift
will build arbitrarily nested CombinatorTs, but I'm not sure how to
extract them into the component transformers. Hardly ideal.

Perhaps someone more enterprising will fix my error, if it is indeed
possible to do so. Until then, my apologies for triple posting.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Nested Monads Questions

2006-08-12 Thread Dan Doel

On 8/11/06, Dan Doel <[EMAIL PROTECTED]> wrote:

The difference is in what the parameters to the classes MonadTrans and
MonadIO represent. MonadIO m means that m is a monad into which
IO-actions can be lifted. MonadTrans t means that (t m) is a monad
into which m-actions can be lifted. However, since the type class
doesn't know about m, it's impossible to exprss that composition of
two transformers is itself a transformer, whereas you can easily
declare that the result of transforming a MonadIO with a certain
transformer results in a MonadIO.

Apologies for replying to myself.

I played around a bit, and I was essentially able to express
composition of transformers without extra class parameters. Ideally,
it'd go something like this:

 type CombinatorT (t :: (* -> *) -> * -> *)
  (u :: (* -> *) -> * -> *)
  (m :: * -> *)
  (a :: *) = t (u m) a

 instance (MonadTrans t, MonadTrans u) =>
 MonadTrans (CombinatorT t u) where
 lift = lift . lift

This says that the combinator transformer is a monad transformer if t
and u are. However, since the combinator transformer is just a type
synonym, it would (I think) end up reducing to all combinations of
transformers being transformers.

However, partially applied type synonyms aren't allowed (for good
reasons, I hear; this example is particularly weird; is it possible to
write without using type synonym syntax? MonadTrans (forall m. t (u
m)) ?), so instead, you have to use a data declaration (maybe a
newtype? I don't know):

 data (MonadTrans t, MonadTrans u, Monad m) =>
 CombinatorT t u m a = CombinatorT (m a)

 instance (MonadTrans t, MonadTrans u) =>
 MonadTrans (CombinatorT t u) where
 lift = CombinatorT

However, that doesn't really give the types we want, and obviously
doesn't do the lift composition, so we need a way to get it out of the
container:

 unC :: (MonadTrans t, MonadTrans u, Monad m, Monad (u m)) =>
 CombinatorT t u m a -> t (u m) a
 unC (CombinatorT m)= lift (lift m)

And for less typing:

 liftC = unC . lift

And now an example, shamefully stolen from Mr. Kuklewicz

 type Foo a = (WriterT [Int] (ReaderT String [])) a

 foo :: Foo String
 foo = do
 x <- liftC [1, 2, 3]
 s <- ask
 tell [succ x]
 return (s ++ show x)

 test = runReaderT (runWriterT foo) "hello"

 *Transform> test
 [("hello1",[2]),("hello2",[3]),("hello3",[4])]

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


[Haskell-cafe] Re: Nested Monads Questions

2006-08-11 Thread Dan Doel

On 8/11/06, Stefan Aeschbacher <[EMAIL PROTECTED]> wrote:

I'm trying to understand Monad Transformers. The code below works as
expected but I have the following questions:

I'll take a shot.


 - why can I use liftIO but not lift in the doSomething function?

I fooled around a bit, and the answer I came up with is that lift is
only able to lift through the first transformer, while liftIO is able
to lift through them both. You'd need to use something like (lift .
lift).

The difference is in what the parameters to the classes MonadTrans and
MonadIO represent. MonadIO m means that m is a monad into which
IO-actions can be lifted. MonadTrans t means that (t m) is a monad
into which m-actions can be lifted. However, since the type class
doesn't know about m, it's impossible to exprss that composition of
two transformers is itself a transformer, whereas you can easily
declare that the result of transforming a MonadIO with a certain
transformer results in a MonadIO.

It's not immediately clear to me how to express that composition of
transformers results in a transformer even with multi-parameter type
classes, but I'm not a type-hacking guru. I wouldn't be surprised if
it's possible.


 - why is there no liftSTM function?

Because there is no MonadSTM typeclass specifying which monads can
have STM actions properly lifted into them. You could write your own.
here's a first pass:

   class Monad m => MonadSTM m where
   liftSTM :: STM a -> m a

   instance MonadSTM STM where
   liftSTM = id

   instance (MonadSTM m) => MonadSTM (ReaderT m) where
   liftSTM = lift . liftSTM

   instance (MonadSTM m) => MonadSTM (WriterT m) where
   liftSTM = lift . liftSTM

   Et cetera...

However, I have no idea if there were reasons why such a class was not
included other than simple oversight. It's possible that lifting like
the above may not work like you'd expect, and perhaps it's difficult
to make it do so. But, if you're willing to be a guinea pig, go ahead
and try those out. :)

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