Re: [Haskell-cafe] More Flexible Monad Transformer OR Bad Coding Style

2010-08-09 Thread C. McCann
On Mon, Aug 9, 2010 at 3:42 PM, Job Vranish  wrote:
> For monads like StateT, WriterT, ReaderT, the order doesn't matter (except
> perhaps for some pesky performance details). However, for monad transformers
> like ErrorT or ListT, the order _does_ matter.

Is it really correct to say that order doesn't matter for the
transformers you mention? More precise would be to say that order
doesn't matter when two or more of those are stacked *consecutively*.
Unless a function is completely independent of what other functions do
with the state values, it can matter a great deal what order two State
transformers occur in if there happens to be a ContT sandwiched
between them. Furthermore, MonadState doesn't even promise that much;
an arbitrary transformer that provides state operations may not
"commute" generally with a StateT. Imagine, for instance, a state
transformer augmented with error checking and transactions, that rolls
back to a checkpoint if something 'put's an invalid state value.

A polymorphic function with multiple monad typeclasses is thus
effectively asserting that it does something sensible and well-defined
for any set of transformers providing those classes, for any ordering
of those transformers in the stack, and with any other possible
transformers inside, outside, or amidst them. Combinatorics are not
your friend here.

Monad transformer polymorphism leads all too easily into a pit of
despair. Don't go there unwisely.

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


Re: [Haskell-cafe] More Flexible Monad Transformer OR Bad Coding Style

2010-08-09 Thread Gregory Crosswhite
 I've never used this myself, but the package mtlx seems to offer one
possible solution to this problem by tagging the monad transformers with
index types:

http://hackage.haskell.org/package/mtlx

Cheers,
Greg

On 08/09/10 12:39, Gábor Lehel wrote:
> Actually, while I haven't even used monad transformers before (just
> read about them a lot), I was thinking that something like this might
> be the way to solve the lift . lift . lift . lift . foo problem on the
> one hand, and by wrapping the 'contents' (e.g. the environment of a
> reader monad) of every level of the stack in a unique newtype (if the
> type isn't otherwise unique), the problem of "what if I want to use
> the same transformer more than once, how do I disambiguate them". (Do
> I have roughly the right idea?)
>
> On Mon, Aug 9, 2010 at 9:05 PM, aditya siram  wrote:
>> Hi all,
>> I was experimenting with monad transformers and realized that the stacking
>> order of the monads can remain unknown until it is used. Take for example
>> the following code:
>>
>> import "mtl" Control.Monad.State
>> import "mtl" Control.Monad.Writer
>> import "mtl" Control.Monad.Identity
>>
>> test :: (MonadWriter [Char] m, Num t, MonadState t m) => m ()
>> test = do
>>  put 1
>>  tell "hello"
>>
>> main = do
>>  x <- return $ runIdentity $ runStateT (runWriterT test) 1 -- test ::
>> WriterT String (StateT Int Identity)
>>  y <- return $ runIdentity $ runWriterT $ runStateT test 1 -- test ::
>> StateT Int (WriterT String Identity)
>>  z <- runWriterT $ runStateT test 1-- test ::
>> StateT Int (WriterT String IO) (((), Int), String)
>>  print x
>>  print y
>>  print z
>>
>> *Main> main
>> (((),"hello"),1)
>> (((),1),"hello")
>> (((),1),"hello")
>>
>> Until test is called in 'main' we don't know the order of monads. In fact
>> even the base monad is not know. All we know is that it uses the State and
>> Writer monad. In each call to 'test' in main we can determine the stacking
>> order and the base monad yielding different results. This seems to be a more
>> flexible way of using monad transformers but I haven't seen this in code
>> before so is there anything wrong with this style?
>>
>> -deech
>>
>> ___
>> 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] More Flexible Monad Transformer OR Bad Coding Style

2010-08-09 Thread Gábor Lehel
2010/8/9 Edward Z. Yang :
> Excerpts from Gábor Lehel's message of Mon Aug 09 15:39:49 -0400 2010:
>> Actually, while I haven't even used monad transformers before (just
>> read about them a lot), I was thinking that something like this might
>> be the way to solve the lift . lift . lift . lift . foo problem on the
>> one hand, and by wrapping the 'contents' (e.g. the environment of a
>> reader monad) of every level of the stack in a unique newtype (if the
>> type isn't otherwise unique), the problem of "what if I want to use
>> the same transformer more than once, how do I disambiguate them". (Do
>> I have roughly the right idea?)
>
> In fact, what you describe is already in use by current monad transformer
> libraries. :-)  Take for example StateT in mtl [1]:
>
> MonadWriter w m => MonadWriter w (StateT s m)
> MonadError e m => MonadError e (StateT s m)
> Monad m => MonadState s (StateT s m)
> MonadReader r m => MonadReader r (StateT s m)
> MonadTrans (StateT s)
> Monad m => Monad (StateT s m)
> Monad m => Functor (StateT s m)
> MonadFix m => MonadFix (StateT s m)
> MonadPlus m => MonadPlus (StateT s m)
> MonadIO m => MonadIO (StateT s m)
> MonadCont m => MonadCont (StateT s m)
>
> By default, it comes with all of these instances, so that if you use a 
> function
> that relies on say MonadReader and not Reader, no lifting is necessary.  
> However,
> newtyping every reader monad because you want to use multiple copies of them
> isn't as good, because you still have to manually add all of these instances.

What I meant was to make certain that the 'r' in `ReaderT r m a`, say,
is a unique type in every case, so that when you write `foo ::
MonadReader SomethingOrOther m => m a -> m a` (for example), it's
always unambiguous which MonadReader in the stack you might've meant.
(If it's not... would you get an overlapping instances error, or
what?)

>
> Cheers,
> Edward
>
> [1] 
> http://hackage.haskell.org/packages/archive/mtl/1.1.0.2/doc/html/Control-Monad-State-Lazy.html
>



-- 
Work is punishment for failing to procrastinate effectively.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] More Flexible Monad Transformer OR Bad Coding Style

2010-08-09 Thread Edward Z. Yang
Excerpts from Gábor Lehel's message of Mon Aug 09 15:39:49 -0400 2010:
> Actually, while I haven't even used monad transformers before (just
> read about them a lot), I was thinking that something like this might
> be the way to solve the lift . lift . lift . lift . foo problem on the
> one hand, and by wrapping the 'contents' (e.g. the environment of a
> reader monad) of every level of the stack in a unique newtype (if the
> type isn't otherwise unique), the problem of "what if I want to use
> the same transformer more than once, how do I disambiguate them". (Do
> I have roughly the right idea?)

In fact, what you describe is already in use by current monad transformer
libraries. :-)  Take for example StateT in mtl [1]:

MonadWriter w m => MonadWriter w (StateT s m)
MonadError e m => MonadError e (StateT s m)
Monad m => MonadState s (StateT s m)
MonadReader r m => MonadReader r (StateT s m)
MonadTrans (StateT s)
Monad m => Monad (StateT s m)
Monad m => Functor (StateT s m)
MonadFix m => MonadFix (StateT s m)
MonadPlus m => MonadPlus (StateT s m)
MonadIO m => MonadIO (StateT s m)
MonadCont m => MonadCont (StateT s m)

By default, it comes with all of these instances, so that if you use a function
that relies on say MonadReader and not Reader, no lifting is necessary.  
However,
newtyping every reader monad because you want to use multiple copies of them
isn't as good, because you still have to manually add all of these instances.

Cheers,
Edward

[1] 
http://hackage.haskell.org/packages/archive/mtl/1.1.0.2/doc/html/Control-Monad-State-Lazy.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] More Flexible Monad Transformer OR Bad Coding Style

2010-08-09 Thread Job Vranish
For monads like StateT, WriterT, ReaderT, the order doesn't matter (except
perhaps for some pesky performance details). However, for monad transformers
like ErrorT or ListT, the order _does_ matter.

The code you have there is perfectly fine, sometimes the added generality
can be quite handy (especially if you have your own MonadState'esk type
classes).
The two major drawbacks to this approach (that I can think of off the top of
my head) are:
1) Rather large and complicated contexts on quite a few of your functions
2) Can lead to nearly indecypherable error messages

Personally, I try to avoid multiparameter typeclasses whenever possible;
I've found them to be more trouble than they are worth.

My advice would be to leave the code general if the code actually does
something general (it actually has more than one use case) and give the code
a fixed signature if the code really one has just one purpose (even if ghci
can infer a general type for you).
This is just a personal preference, but it seems to work well for me :)

- Job


On Mon, Aug 9, 2010 at 3:05 PM, aditya siram  wrote:

> Hi all,
> I was experimenting with monad transformers and realized that the stacking
> order of the monads can remain unknown until it is used. Take for example
> the following code:
>
> import "mtl" Control.Monad.State
> import "mtl" Control.Monad.Writer
> import "mtl" Control.Monad.Identity
>
> test :: (MonadWriter [Char] m, Num t, MonadState t m) => m ()
> test = do
>  put 1
>  tell "hello"
>
> main = do
>  x <- return $ runIdentity $ runStateT (runWriterT test) 1 -- test ::
> WriterT String (StateT Int Identity)
>  y <- return $ runIdentity $ runWriterT $ runStateT test 1 -- test ::
> StateT Int (WriterT String Identity)
>  z <- runWriterT $ runStateT test 1-- test ::
> StateT Int (WriterT String IO) (((), Int), String)
>  print x
>  print y
>  print z
>
> *Main> main
> (((),"hello"),1)
> (((),1),"hello")
> (((),1),"hello")
>
> Until test is called in 'main' we don't know the order of monads. In fact
> even the base monad is not know. All we know is that it uses the State and
> Writer monad. In each call to 'test' in main we can determine the stacking
> order and the base monad yielding different results. This seems to be a more
> flexible way of using monad transformers but I haven't seen this in code
> before so is there anything wrong with this style?
>
> -deech
>
> ___
> 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] More Flexible Monad Transformer OR Bad Coding Style

2010-08-09 Thread Gábor Lehel
Actually, while I haven't even used monad transformers before (just
read about them a lot), I was thinking that something like this might
be the way to solve the lift . lift . lift . lift . foo problem on the
one hand, and by wrapping the 'contents' (e.g. the environment of a
reader monad) of every level of the stack in a unique newtype (if the
type isn't otherwise unique), the problem of "what if I want to use
the same transformer more than once, how do I disambiguate them". (Do
I have roughly the right idea?)

On Mon, Aug 9, 2010 at 9:05 PM, aditya siram  wrote:
> Hi all,
> I was experimenting with monad transformers and realized that the stacking
> order of the monads can remain unknown until it is used. Take for example
> the following code:
>
> import "mtl" Control.Monad.State
> import "mtl" Control.Monad.Writer
> import "mtl" Control.Monad.Identity
>
> test :: (MonadWriter [Char] m, Num t, MonadState t m) => m ()
> test = do
>  put 1
>  tell "hello"
>
> main = do
>  x <- return $ runIdentity $ runStateT (runWriterT test) 1 -- test ::
> WriterT String (StateT Int Identity)
>  y <- return $ runIdentity $ runWriterT $ runStateT test 1 -- test ::
> StateT Int (WriterT String Identity)
>  z <- runWriterT $ runStateT test 1    -- test ::
> StateT Int (WriterT String IO) (((), Int), String)
>  print x
>  print y
>  print z
>
> *Main> main
> (((),"hello"),1)
> (((),1),"hello")
> (((),1),"hello")
>
> Until test is called in 'main' we don't know the order of monads. In fact
> even the base monad is not know. All we know is that it uses the State and
> Writer monad. In each call to 'test' in main we can determine the stacking
> order and the base monad yielding different results. This seems to be a more
> flexible way of using monad transformers but I haven't seen this in code
> before so is there anything wrong with this style?
>
> -deech
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>



-- 
Work is punishment for failing to procrastinate effectively.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] More Flexible Monad Transformer OR Bad Coding Style

2010-08-09 Thread Edward Z. Yang
Excerpts from aditya siram's message of Mon Aug 09 15:05:14 -0400 2010:
> Until test is called in 'main' we don't know the order of monads. In fact
> even the base monad is not know. All we know is that it uses the State and
> Writer monad. In each call to 'test' in main we can determine the stacking
> order and the base monad yielding different results. This seems to be a more
> flexible way of using monad transformers but I haven't seen this in code
> before so is there anything wrong with this style?

There are two points here:

* You have observed that running the monads in different orders results
  in different values: however, in the case of the examples you've chosen,
  the essential character of the result is still the same.  This is not
  universally true: only some monads "commute", so to speak.  So you definitely
  do not want to leave the ordering implicit if order matters.  But when
  the monads are commutative...

* The general feeling on this issue, as I've heard from Don, is that generic
  types for specifying monad stacks are too fragile: due to the extra 
generality,
  it's a lot easier to write code that typechecks but doesn't do what you 
actually
  want it to.  A decent compromise might be to use a concrete stack, and offer
  a utility function that "lifts" it into the generic monad typeclasses.

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


[Haskell-cafe] More Flexible Monad Transformer OR Bad Coding Style

2010-08-09 Thread aditya siram
Hi all,
I was experimenting with monad transformers and realized that the stacking
order of the monads can remain unknown until it is used. Take for example
the following code:

import "mtl" Control.Monad.State
import "mtl" Control.Monad.Writer
import "mtl" Control.Monad.Identity

test :: (MonadWriter [Char] m, Num t, MonadState t m) => m ()
test = do
 put 1
 tell "hello"

main = do
 x <- return $ runIdentity $ runStateT (runWriterT test) 1 -- test ::
WriterT String (StateT Int Identity)
 y <- return $ runIdentity $ runWriterT $ runStateT test 1 -- test ::
StateT Int (WriterT String Identity)
 z <- runWriterT $ runStateT test 1-- test ::
StateT Int (WriterT String IO) (((), Int), String)
 print x
 print y
 print z

*Main> main
(((),"hello"),1)
(((),1),"hello")
(((),1),"hello")

Until test is called in 'main' we don't know the order of monads. In fact
even the base monad is not know. All we know is that it uses the State and
Writer monad. In each call to 'test' in main we can determine the stacking
order and the base monad yielding different results. This seems to be a more
flexible way of using monad transformers but I haven't seen this in code
before so is there anything wrong with this style?

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