questions on lazy pattern, StateT monad

Hi Haskell gurus, I'm very puzzled on some code I saw in GHC Monad.StateT (which is about state monad transformers) source and hope you can kindly give me some insight into this. newtype StateT s m a = S (s -> m (a,s)) instance MonadPlus m => MonadPlus (StateT s m) where mzero = lift mzero mplus m1 m2 = do s <- peek let m1' = runState s m1 m2' = runState s m2 ???????----> ~(a,s') <- lift (mplus m1' m2') poke s' return a To illustrate my puzzle, say m is of List type and runState s m1 = m1' = [(a1, s1)] runState s m2 = m2' = [(a2, s2)] With the definition of lift (also in the StateT.hs file) as instance Trans (StateT s) where lift m = S (\s -> do x <- m return (x,s)) I got lift (mplus m1' m2') = lift ([(a1,s1), (a2,s2)]) = S (\s -> [ ((a1,s1),s), ((a2,s2),s)]) I'm puzzled over this line: ~(a,s') <- lift (mplus m1' m2') I think ~(a,s') shall be the value of the (StateT s m a) which is generated by "lift (mplus m1' m2')". My questions are - why use lazy pattern? - how is ~(a,s') extracted from (StateT s m a)? This looks like magic to me. In the example I have (a1,s1) and (a2,s2) in the lifted monad, but it seems (a,s') only represents one at a time. It looks like how data is pulled out of a List monad. Your help is highly appreciated. Thanks, Fan

Am Mittwoch, 23. November 2005 10:03 schrieb Fan Wu:
[...]
I'm puzzled over this line:
~(a,s') <- lift (mplus m1' m2')
Why is this line in Monad.State.StateT? Recently, we discussed that StateT does *not* use a lazy pattern here but that it should be changed to using one. So where did you see this lazy pattern?
[...]
Best wishes, Wolfgang

HI Wolfgang,
The code is from GHC source
ghc-6.4.1/libraries/monads/Monad/StateT.hs, am I looking at the wrong
place?
I found the thread discussing "Monad strictness", where is your StateT defined?
But it is still not clear to me why lazy pattern is used here. Any ideas?
Thanks,
Fan
On 11/23/05, Wolfgang Jeltsch
Am Mittwoch, 23. November 2005 10:03 schrieb Fan Wu:
[...]
I'm puzzled over this line:
~(a,s') <- lift (mplus m1' m2')
Why is this line in Monad.State.StateT? Recently, we discussed that StateT does *not* use a lazy pattern here but that it should be changed to using one. So where did you see this lazy pattern?
[...]
Best wishes, Wolfgang _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Am Mittwoch, 23. November 2005 19:02 schrieb Fan Wu:
HI Wolfgang,
The code is from GHC source ghc-6.4.1/libraries/monads/Monad/StateT.hs, am I looking at the wrong place?
I found the thread discussing "Monad strictness", where is your StateT defined?
Hello Fan, the GHC source is just where I looked, except that my GHC version is 6.2.2. Obviously they corrected the implementation of (>>=) for StateT to use a lazy pattern between 6.2.2 and 6.4.1.
But it is still not clear to me why lazy pattern is used here. Any ideas?
Let's discuss this for State instead of StateT because this makes the discussion easier. A state transformer should ideally be implemented as a kind of function which gets one argument (the initial state) and returns *two* results (the output and the final state). Of course, a real function cannot return two results, so the obvious solution is to use a function which returns a pair, consisting of the output and the final state. If we would do so, it would work. But Haskell's pairs are not real pairs but lifted pairs. There are pairs like (x,y) which are an application of the data constructor (,) to x and y, and there is the special pair _|_ which denotes undefinedness. Note that _|_ is not the same as (_|_,_|_). Pattern matching of _|_ against the pattern (_,_) will not be successful while matching (_|_,_|_) against the same pattern will. The problem now is that when using Haskell pairs for implementing state transformers, it might not immediately be clear for a given state transformer if it returns an application of (,) (i.e., a "true pair") or if it returns _|_. Pattern matching of a state transformer's result against a pattern of the form (x,y) may therefore result in unnecessary evaluation of certain expressions. Let's look at an example. We have two types S and T as well as some state transformer next :: State S T. Now we want to construct a state transformer which calls next infinitely many times and returns the outputs of the next invocations as an infinite list. We would write: everything :: State S [T] everything = do x <- next xs <- everything return (x : xs) The do expression can be rewritten as: next >>= (\x -> everything >>= \xs -> return (x : xs)) If we use an implementation of State *without lazy patterns*, it becomes something like this: \s -> case next s of (x,s') -> case everyting s' of (xs,s'') -> ((x : xs),s'') Note that I used case expressions to realize strict patterns because pattern binding in let expressions is implicitely lazy. Now lets apply the function denoted by the last code fragment to some initial state and try to extract just the first element of the output. In order to do so we have to take the result of the function and match it against ((x : _),_). Especially, we have to reduce the pair, i.e., we have to make sure that it's really an application of (,) and not _|_. In order to do so we have to first reduce next s. After this, s' has to be taken and the result of everything s' has to be reduced. We cannot tell that the result of the whole function is really a (,) application until we have reduced everything s' and made sure that its result is not bottom. The problem is that for reducing everything s', we have to start the whole procedure again. So we end up in an infinite recursion and never get any result. However, if we use lazy patterns, we don't have to reduce next s at first. We also don't have to reduce everything s'. No matter whether these two expressions are _|_ or not, we know that the whole function always has a result of the form ((x : xs),s''). The first component of the pair can be immediately extracted from the pair and so can the first element of the list. Only if we start to evaluate this first element, next s has to be reduced. But only next s! I hope, this did clarify this problem a bit. If you still have questions, feel free to ask.
Thanks, Fan
Best wishes, Wolfgang

From your example I can see "Lazy patterns are useful in contexts where infinite data structures are being defined recursively" (quote
Hi Wolfgang, Thanks for your response and examples! It helps a lot. section 4.4 of Gentle Introduction to Haskell). But does it apply to the mplus case? I mean the mplus in (mplus m1 m2) and the mplus in (mplus m1' m2') are different due to the difference of Monads (one is StateT s m, the other is just m). If I change the mplus inside lift to something else like: mplus m1 m2 = do s <- peek let m1' = runState s m1 m2' = runState s m2 ~(a,s') <- lift (other_func m1' m2') poke s' return a Is it still required that (a,s') be lazy? I just want to see how things works in an less obvious example like this one. Thanks, Fan

Am Donnerstag, 24. November 2005 01:49 schrieb Fan Wu:
Hi Wolfgang,
Thanks for your response and examples! It helps a lot.
From your example I can see "Lazy patterns are useful in contexts where infinite data structures are being defined recursively" (quote section 4.4 of Gentle Introduction to Haskell).
They are useful not only in conjunction with infinite data structures. Take my example state transformer "everything" and modify it so that it calls next exactly two times, not infinitely many times, and outputs a pair of the outputs of the two next invocations. Now let's assume you use this pair in a context where only its first component is used. Without lazy patterns, next would be invoked two times although it need to be invoked only one time. So you might have unnecessary evaluation. And you might have something even worse. Let's assume that when we apply the function making up next on the output state of the first next invocation then we get _|_. Without lazy patterns, just using the output of the first next invocation would result in your program aborting. Of course, it shouldn't do so.
But does it apply to the mplus case? I mean the mplus in (mplus m1 m2) and the mplus in (mplus m1' m2') are different due to the difference of Monads (one is StateT s m, the other is just m). If I change the mplus inside lift to something else like:
mplus m1 m2 = do s <- peek let m1' = runState s m1 m2' = runState s m2 ~(a,s') <- lift (other_func m1' m2') poke s' return a
Is it still required that (a,s') be lazy?
I thought a bit about the lazy pattern in the mplus implementation and still don't know if it's necessary. :-(
I just want to see how things works in an less obvious example like this one.
Thanks, Fan
Best wishes, Wolfgang

They are useful not only in conjunction with infinite data structures. Take my example state transformer "everything" and modify it so that it calls next exactly two times, not infinitely many times, and outputs a pair of the outputs of the two next invocations.
Now let's assume you use this pair in a context where only its first component is used. Without lazy patterns, next would be invoked two times although it need to be invoked only one time. So you might have unnecessary evaluation. And you might have something even worse. Let's assume that when we apply the function making up next on the output state of the first next invocation then we get _|_. Without lazy patterns, just using the output of the first next invocation would result in your program aborting. Of course, it shouldn't do so.
This is a good example! But now I got the impression that pattern match failure could happen in many places, so unless you want it to fail loudly, you shall always use lazy pattern? Thanks, Fan

Am Donnerstag, 24. November 2005 21:37 schrieb Fan Wu:
[...]
This is a good example! But now I got the impression that pattern match failure could happen in many places, so unless you want it to fail loudly, you shall always use lazy pattern?
Often you need pattern matching for distinguishing different cases (e.g., empty vs. non-empty list). In these cases, lazy patterns are useless. Our discussion was only about lazy patterns in conjunction with tuples. The deeper reason for using lazy patterns was that we actually want unlifted tuples (because we just want to group several things together) while Haskell provides us only with lifted tuples. In such cases it might be generally advisable to use lazy patterns. An alternative to using lazy patterns would be to use unlifted tuples which come as an extension with GHC, named "unboxed tuples" there.
Thanks, Fan
Best wishes, Wolfgang

Wolfgang Jeltsch writes:
If we use an implementation of State *without lazy patterns*, it becomes something like this:
\s -> case next s of (x,s') -> case everyting s' of (xs,s'') -> ((x : xs),s'')
Note that I used case expressions to realize strict patterns because pattern binding in let expressions is implicitely lazy.
Now lets apply the function denoted by the last code fragment to some initial state and try to extract just the first element of the output. In order to do so we have to take the result of the function and match it against ((x : _),_). Especially, we have to reduce the pair, i.e., we have to make sure that it's really an application of (,) and not _|_.
Would the lazy pattern match be equivalent to using fst and snd?
\s -> case next s of
p1 -> case everything (snd p1) of
p2 -> (fst p1 : fst p2, snd p2)
--
David Menendez

Am Donnerstag, 24. November 2005 02:08 schrieb David Menendez:
Wolfgang Jeltsch writes:
If we use an implementation of State *without lazy patterns*, it becomes something like this:
\s -> case next s of (x,s') -> case everyting s' of (xs,s'') -> ((x : xs),s'')
Note that I used case expressions to realize strict patterns because pattern binding in let expressions is implicitely lazy.
Now lets apply the function denoted by the last code fragment to some initial state and try to extract just the first element of the output. In order to do so we have to take the result of the function and match it against ((x : _),_). Especially, we have to reduce the pair, i.e., we have to make sure that it's really an application of (,) and not _|_.
Would the lazy pattern match be equivalent to using fst and snd?
\s -> case next s of p1 -> case everything (snd p1) of p2 -> (fst p1 : fst p2, snd p2)
I think so. Best wishes, Wolfgang

Am Mittwoch, 23. November 2005 20:42 schrieb Wolfgang Jeltsch:
Am Mittwoch, 23. November 2005 19:02 schrieb Fan Wu: [...]
But it is still not clear to me why lazy pattern is used here. Any ideas?
Let's discuss this for State instead of StateT because this makes the discussion easier.
[...]
Oops, I've answered a question you didn't ask. I haven't looked at your message carefully enough and thought that you were refering to the implementation of (>>=) while in fact you were refering to the implementation of mplus. But I think the reasons behind lazy pattern usage in the mplus implementation are similar to those behind lazy pattern usage in the (>>=) implementation.
[...]
Best wishes, Wolfgang

But I think the reasons behind lazy pattern usage in the mplus implementation are similar to those behind lazy pattern usage in the (>>=) implementation.
I find the explanation of "Lazy patterns are useful in contexts where infinite data structures are being defined recursively" is easier to understand. Actually all the lazy pattern examples I have seen so far belong to this category. Here I want to correct a statement I made previously about: mplus m1 m2 = do ... ~(a,s') <- lift (mplus m1' m2') In one of my emails to the thread I mentioned m1/m2 and m1'/m2' could be different Monads so mplus works differently (so that this is not exactly a recusrive data structure), but even so the lazy pattern works. The problem is when m1/m2 and m1'/m2' are of the same Monad type, then the problem of recursive definition comes up and this is the place lazy patterns are particularly useful. Thanks, Fan

Am Donnerstag, 24. November 2005 21:19 schrieben Sie:
[...]
Here I want to correct a statement I made previously about:
mplus m1 m2 = do ... ~(a,s') <- lift (mplus m1' m2')
In one of my emails to the thread I mentioned m1/m2 and m1'/m2' could be different Monads so mplus works differently (so that this is not exactly a recusrive data structure), but even so the lazy pattern works. The problem is when m1/m2 and m1'/m2' are of the same Monad type, then the problem of recursive definition comes up and this is the place lazy patterns are particularly useful.
They cannot belong to the same monad. If s is the state type and m1' and m2' belong to the monad m then m1 and m2 belong to the monad StateT s m.
Thanks, Fan
Best wishes, Wolfgang

They cannot belong to the same monad. If s is the state type and m1' and m2' belong to the monad m then m1 and m2 belong to the monad StateT s m.
I know it looks insane, I'm just trying to make a recursive case of it: technically it's still possible to have a StateT monad as the m in "StateT s m" right? Thanks, Fan

Am Donnerstag, 24. November 2005 21:52 schrieb Fan Wu:
They cannot belong to the same monad. If s is the state type and m1' and m2' belong to the monad m then m1 and m2 belong to the monad StateT s m.
I know it looks insane, I'm just trying to make a recursive case of it: technically it's still possible to have a StateT monad as the m in "StateT s m" right?
Yes, but this StateT type application cannot be equal to the outer StateT type application because this would result in an infinite type which Haskell doesn't support. Example: StateT Int (StateT Int (StateT Int ...))
Thanks, Fan
Best wishes, Wolfgang

Yes, but this StateT type application cannot be equal to the outer StateT type application because this would result in an infinite type which Haskell doesn't support. Example:
StateT Int (StateT Int (StateT Int ...))
I see. I was trying to justify the lazy pattern in this mplus, now i'm at end of my wit:-( Thanks, Fan

On Wed, Nov 23, 2005 at 02:03:22AM -0700, Fan Wu wrote:
instance MonadPlus m => MonadPlus (StateT s m) where mzero = lift mzero mplus m1 m2 = do s <- peek let m1' = runState s m1 m2' = runState s m2 ???????----> ~(a,s') <- lift (mplus m1' m2') poke s' return a
Perhaps you were wondering, as I did when I read this, how ~(a,s') <- lift (mplus m1' m2') poke s' return a differs from lift (mplus m1' m2') It helped me to rewrite mplus: mplus m1 m2 = S (\s -> let m1' = runState s m1 m2' = runState s m2 in ~(a, s') <- mplus m1' m2' return (a, s')) (If you reduce the first definition to this, you can verify that the lazy pattern matches in the two correspond.) So my question boils down to, can you ever distinguish S (\s -> m >>= ~(a, s') -> return (a, s')) from S (\s -> m) using only exported operators? I don't think so, because a subsequent bind will do the lazy pattern match itself. Did I miss something, or is this use of ~ (and the subsequent poke, return) superfluous? Andrew

Am Mittwoch, 23. November 2005 10:03 schrieb Fan Wu:
Hi Haskell gurus,
I'm very puzzled on some code I saw in GHC Monad.StateT (which is about state monad transformers) source and hope you can kindly give me some insight into this.
newtype StateT s m a = S (s -> m (a,s))
instance MonadPlus m => MonadPlus (StateT s m) where mzero = lift mzero mplus m1 m2 = do s <- peek let m1' = runState s m1 m2' = runState s m2 ???????----> ~(a,s') <- lift (mplus m1' m2') poke s' return a
Is this a new implementation of state transformers since I'ver never heard about peek and poke before (only get and put) and also thought that the argument order of runState was the other way round? If yes, why did this new library retain this terrible naming of monad types? Values of State don't denote states but state *transformers*. I like to use significant variable names in my code and therefore I often use just the type name as a variable name. So a value of type State would sometimes be named "state". But what if I also have a variable that denotes a state?
[...]
Best wishes, Wolfgang

Hi Wolfgang, I don't know the history so maybe this is a new implementation of State transformer. The Peek and poke functions are defined below (copied from StateT.hs): instance Monad m => StateM (StateT s m) s where peek = S (\s -> return (s,s)) poke s = S (\s1 -> return (s1,s)) The question is why can't the mplus be written as simple as what Andrew suggested: mplus m1 m2 = S (\s -> let m1' = runState s m1 m2' = runState s m2 in ~(a, s') <- mplus m1' m2' return (a, s')) this is easier to understand. I don't see what's the purpose of the peek, lift, poke, return in the new implementattion. Cheers, Fan

Am Donnerstag, 24. November 2005 19:24 schrieb Fan Wu:
Hi Wolfgang,
I don't know the history so maybe this is a new implementation of State transformer. The Peek and poke functions are defined below (copied from StateT.hs):
instance Monad m => StateM (StateT s m) s where peek = S (\s -> return (s,s)) poke s = S (\s1 -> return (s1,s))
This is obviously a newer implementation. peek and poke are obviously what get and put were in the old one.
The question is why can't the mplus be written as simple as what Andrew suggested:
mplus m1 m2 = S (\s -> let m1' = runState s m1 m2' = runState s m2 in ~(a, s') <- mplus m1' m2' return (a, s'))
this is easier to understand. I don't see what's the purpose of the peek, lift, poke, return in the new implementattion.
[There is a "do" missing before the lazy pattern, isn't it?] Maybe the point is that Andrew's implementation needs access to the internal structure of a state transformer while the solution with peek, poke etc. doesn't need this kind of access. So the non-Andrew solution can be considered more elegant because it doesn't depend on the implementation of state transformers, can be put into a different module and shows clearly that mplus is not yet another primitive StateT operation but can be defined in terms of primitives.
Cheers, Fan
Best wishes, Wolfgang
participants (4)
-
Andrew Pimlott
-
David Menendez
-
Fan Wu
-
Wolfgang Jeltsch