Re: [Haskell-cafe] State monad strictness - how?

Dean Herington wrote:
I can't seem to figure out how to achieve strictness in the context of the State monad.
Unfortunately, the current situation is that State is only available as a lazy monad, and StateT is only available as a strict monad. It seems to me that this should clearly be considered a serious bug in the library. It has been reported on numerous occasions over the years, but it has still not been fixed. At the very least, the two should be consistent. I would much prefer for them both to be lazy. I have written a lot of code that depends on that; it is the natural assumption in Haskell that everything is lazy by default, except seq, IO, and their friends. The obvious solution would be to have available both a lazy and a strict version of each monad: State, State', StateT, and State'T (or some such), with functions to convert between them. It is trivial to implement that in the current library. If someone can come up with a more elegant solution right away, that would be great. (Iavor - do you have a solution?) Otherwise, I think we have waited long enough. Let's implement the simple fix. This bug is a major inconvenience to users of this library.
(try 1000000) overflows the stack.
In the current situation, you can use
where final = runIdentity $ execStateT prog (0::Int) ... tick :: (Num a, MonadState a m) => m a ...
Regards, Yitz

Hello Yitzchak, Wednesday, January 10, 2007, 12:02:25 PM, you wrote:
Unfortunately, the current situation is that State is only available as a lazy monad, and StateT is only available as a strict monad.
At the very least, the two should be consistent. I would much prefer for them both to be lazy.
imho, lazy monads (as any other lazy things) is a source of beginner's confusion. therefore it may be better to provide "default" monads as strict and lazy ones - for one who knows what he wants - with a Lazy prefix, e.g. LazyST, LazyState... -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hi Bulat, I wrote:
[State and StateT] should be consistent. I would much prefer for them both to be lazy.
Bulat Ziganshin wrote:
imho, lazy monads (as any other lazy things) is a source of beginner's confusion. therefore it may be better to provide "default" monads as strict and lazy ones - for one who knows what he wants - with a Lazy prefix, e.g. LazyST, LazyState...
Well, as long as both are provided, that is fine with me. But I do not think that laziness in monad methods is a reason for beginners' confusion. First of all, it is natural to get a little confused about strictness at the beginning. I'm not sure it happens more often with monads than anywhere else. If there is more confusion about strictness with monads, it is because of the fact that many introductions/tutorials confuse all monads with IO. They say something like: "So how do you create side effects in the real world? That is what monads are for." No, no, no! That is what ** IO ** is for. Most monads are pure! In fact, I think making the default strict will create more confusion. We should help beginners to understand right from the start that do-notation is not a "procedure" of commands for the computer to carry out. It is just a special syntax for defining functions. We use it when it is more natural to describe the effect of a function in a step-by-step style, just as happens sometimes in mathematics. But the compiler is under no obligation to follow our steps literally. Except with IO - when dealing with the real world, we need to be able to specify the exact order in which things happen. ST represents using physical memory as a fast storage device. So it is really IO in disguise. Regards, Yitz

Yitzchak,
I agree with you that both lazy and strict monads are important and
that we should have both options in a monad library.
But the fun doesn't end there. There are other strictness properties
to consider. Take the state monad for example. Should it be strict or
lazy in the state that it carries around? What about the value
component? I think the answer to these questions are the same as for
monadic strictness above: both strict and lazy variants are useful.
Now, the challenge here is to design a library which doesn't explode
in size from all the various possibilities for strictness or laziness.
In fact I did once bite the bullet and came up with a library that
does all this. Though I haven't released it publicly yet. I never took
the time to polish the code to the point where I wouldn't be
embarrassed about showing it to others.
If you kick me hard enough I might release the library.
Cheers,
Josef
On 1/10/07, Yitzchak Gale
Hi Bulat,
I wrote:
[State and StateT] should be consistent. I would much prefer for them both to be lazy.
Bulat Ziganshin wrote:
imho, lazy monads (as any other lazy things) is a source of beginner's confusion. therefore it may be better to provide "default" monads as strict and lazy ones - for one who knows what he wants - with a Lazy prefix, e.g. LazyST, LazyState...
Well, as long as both are provided, that is fine with me.
But I do not think that laziness in monad methods is a reason for beginners' confusion.
First of all, it is natural to get a little confused about strictness at the beginning. I'm not sure it happens more often with monads than anywhere else.
If there is more confusion about strictness with monads, it is because of the fact that many introductions/tutorials confuse all monads with IO. They say something like:
"So how do you create side effects in the real world? That is what monads are for."
No, no, no! That is what ** IO ** is for. Most monads are pure!
In fact, I think making the default strict will create more confusion.
We should help beginners to understand right from the start that do-notation is not a "procedure" of commands for the computer to carry out. It is just a special syntax for defining functions. We use it when it is more natural to describe the effect of a function in a step-by-step style, just as happens sometimes in mathematics. But the compiler is under no obligation to follow our steps literally.
Except with IO - when dealing with the real world, we need to be able to specify the exact order in which things happen.
ST represents using physical memory as a fast storage device. So it is really IO in disguise.
Regards, Yitz _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Josef, Josef Svenningsson wrote:
...the fun doesn't end there. There are other strictness properties to consider.
Could be. But after using mtl heavily for a few years now, I find that in practice the only one where have felt the need for control over strictness is >>=, like Dean's example.
Take the state monad for example. Should it be strict or lazy in the state that it carries around? What about the value component? I think the answer to these questions are the same as for monadic strictness above: both strict and lazy variants are useful.
Are those really needed? Can't the strictness of the state be fully controlled by seq with runState, get, and put, and by choosing lazy or strict >>=? And similarly with value? As opposed to >>=, where there is no way to control its strictness from outside the Monad instance declaration.
Now, the challenge here is to design a library which doesn't explode in size from all the various possibilities for strictness or laziness.
The same challenge exists in many of the Data.* libraries. I think this is very important.
In fact I did once bite the bullet and came up with a library that does all this. Though I haven't released it publicly yet. I never took the time to polish the code to the point where I wouldn't be embarrassed about showing it to others. If you kick me hard enough I might release the library.
My boot is not long enough :). But I would love to see what you did. Regards, Yitz

On 1/10/07, Yitzchak Gale
Hi Josef,
Josef Svenningsson wrote:
...the fun doesn't end there. There are other strictness properties to consider.
Could be. But after using mtl heavily for a few years now, I find that in practice the only one where have felt the need for control over strictness is >>=, like Dean's example.
Yes. For most uses this finer control of strictness is just overkill. But in the rare cases when you really need this tweakability then it's a royal pain if you don't have it.
Take the state monad for example. Should it be strict or lazy in the state that it carries around? What about the value component? I think the answer to these questions are the same as for monadic strictness above: both strict and lazy variants are useful.
Are those really needed? Can't the strictness of the state be fully controlled by seq with runState, get, and put, and by choosing lazy or strict >>=? And similarly with value?
Yes, you're right. But it wouldn't be very convenient, would it? Sometimes I find that I want strict state by default and then I don't want to sprinkle my code with seqs. Furthermore this extra level of control is not that difficult to implement in a library.
Now, the challenge here is to design a library which doesn't explode in size from all the various possibilities for strictness or laziness.
The same challenge exists in many of the Data.* libraries. I think this is very important.
Indeed.
In fact I did once bite the bullet and came up with a library that does all this. Though I haven't released it publicly yet. I never took the time to polish the code to the point where I wouldn't be embarrassed about showing it to others. If you kick me hard enough I might release the library.
My boot is not long enough :). But I would love to see what you did.
:-) Ok, I've put some files under the following url: http://www.cs.chalmers.se/~josefs/monadlib/ It might need some explanation since I use the module system quite heavily. For a monad such as the state monad the hierarchy looks like this: * Control.Monad.State.Base contains the type declaration and basic functionality, but NOT instances of the monad class. This module is not exposed. * Control.Monad.State.Lazy * Control.Monad.State.Strict Contains instances for monad classes. * Control.Monad.State is supposed to be the default and just reexports Control.Monad.State.Strict. Furthermore, again taking the state monad as example, the monad is parameterized on the type of pair used in the definition of the monad. So instead of: newtype State s a = State { runState :: (s -> (a, s)) } we have: newtype StateP p s a = StateP { runStateP :: (s -> p a s) } Now, instantiating this with different pair types with different strictness properties will give us total control over strictness for state and value. Data.Pair provides various pair for this purpose. Enjoy, Josef

Josef Svenningsson wrote:
Take the state monad for example. Should it be strict or lazy in the state that it carries around? What about the value component? ...both strict and lazy variants are useful.
I wrote:
Are those really needed?
...it wouldn't be very convenient, would it? Sometimes I find that I want strict state by default and then I don't want to sprinkle my code with seqs.
I don't think that is so inconvenient. Why do we need to define getStrict, putStrict, getsStrict, etc., when it is perhaps even more clear to write get $!, put $!., (gets . ($!)), etc.?. The same goes for Iavor's monad library.
Now, the challenge here is to design a library which doesn't explode in size from all the various possibilities for strictness or laziness.
I am now pretty convinced that the only thing we need is two versions of each monad, varying only the strictness of >>=. Then, of course, we will need runFoo for each, and evalFoo and execFoo for each state monad. And adaptors that allow you to run a lazy calculation inside a strict one and vice-versa. So we need an asStrict function and an asLazy function for each lazy/strict pair of monads. I think that is all we need. Not too bad. I am very impressed that we get most of that almost for free in Iavor's library.
The same challenge exists in many of the Data.* libraries. I think this is very important.
I am now a bit more optimistic. Has anyone looked through them?
http://www.cs.chalmers.se/~josefs/monadlib/ ...instantiating this with different pair types with different strictness properties will give us total control over strictness for state and value.
Hmm. Your current implementation doesn't seem to do it that way. You use tuples for both the lazy version and the strict version, and each defines its own Monad instance for all Pair types. So it is impossible to use both in the same module, even with hiding. I tried to work on this a little. I defined a strict Pair type and tried to find a single Monad instance that will give the right strictness for both if you just vary between lazy and strict pairs. We need that both of the following converge in constant stack space: take 100 $ evalState (repeatM $ modify (+1)) 0 execStateStrict (replicateM_ 100000 $ modify (+1)) 0 (You can verify that this is true if you use the standard evalState, and replace execStateStrict with runIdentity . execStateT.) I was unable to hit upon the right combination of seqs in the Monad instance. Is it really possible? Of course, you could use a newtype of tuples and define separate Monad instances. But then we are not gaining anything over just defining the lazy and strict monads directly. Regards, Yitz

On 1/11/07, Yitzchak Gale
Josef Svenningsson wrote:
Take the state monad for example. Should it be strict or lazy in the state that it carries around? What about the value component? ...both strict and lazy variants are useful.
I wrote:
Are those really needed?
...it wouldn't be very convenient, would it? Sometimes I find that I want strict state by default and then I don't want to sprinkle my code with seqs.
I don't think that is so inconvenient. Why do we need to define getStrict, putStrict, getsStrict, etc., when it is perhaps even more clear to write get $!, put $!., (gets . ($!)), etc.?.
The same goes for Iavor's monad library.
Indeed. I'm embarrassed that I've never realized this before. I suppose I though the tuple solution was so elegant that I never realized there was a simpler solution at hand.
Now, the challenge here is to design a library which doesn't explode in size from all the various possibilities for strictness or laziness.
I am now pretty convinced that the only thing we need is two versions of each monad, varying only the strictness of >>=.
Then, of course, we will need runFoo for each, and evalFoo and execFoo for each state monad.
And adaptors that allow you to run a lazy calculation inside a strict one and vice-versa. So we need an asStrict function and an asLazy function for each lazy/strict pair of monads.
I think that is all we need. Not too bad.
I am very impressed that we get most of that almost for free in Iavor's library.
Yes, it seems quite feasible.
http://www.cs.chalmers.se/~josefs/monadlib/ ...instantiating this with different pair types with different strictness properties will give us total control over strictness for state and value.
Hmm. Your current implementation doesn't seem to do it that way. You use tuples for both the lazy version and the strict version, and each defines its own Monad instance for all Pair types. So it is impossible to use both in the same module, even with hiding.
The way I enable laziness in a strict monad and vice versa is to use a non-standard bind operator, strictBind or lazyBind. But that's not really scalable. The whole architecture that I used in my library isn't really all that good. The reason I came up with it was to solve a completely different problem which doesn't really apply to this library anyway. The library design you outline above is indeed the way to go.
I tried to work on this a little. I defined a strict Pair type and tried to find a single Monad instance that will give the right strictness for both if you just vary between lazy and strict pairs.
We need that both of the following converge in constant stack space:
take 100 $ evalState (repeatM $ modify (+1)) 0 execStateStrict (replicateM_ 100000 $ modify (+1)) 0
(You can verify that this is true if you use the standard evalState, and replace execStateStrict with runIdentity . execStateT.)
I was unable to hit upon the right combination of seqs in the Monad instance. Is it really possible?
Of course, you could use a newtype of tuples and define separate Monad instances. But then we are not gaining anything over just defining the lazy and strict monads directly.
I'm not sure exactly what you're trying to achieve here. If the tuple type you have is strict in both components then you're never going to get these examples to work. However, if you choose the lazy state monad and choose tuples carefully then both example can be made to terminate. Here's an example: ex1 = take 100 $ evalState ((repeatM $ modify (+1))::StateP StrictLeft Int [()]) 0 ex2 = execStateStrict ((replicateM_ 100000 $ modify (+1)) :: StateTP StrictLeft Int Identity ()) 0 The first example also terminates with the all lazy pair (,), the importance is the laziness of the right component. Cheers, Josef

haskell is the standard lazy functional language, so strictness ought
to be called out. e.g. StateStrict rather than StateLazy.
The traction that haskell is starting to get (and why I'm spending
time learning it and following haskell-cafe) is not because its
semantics are unsurprising to newbies. They are surprising and
surprisingly powerful. A haskell that did no more than scheme would
not be as interesting.
I may be subject to selection bias, but I haven't seen so many
references to a language in unexpected contexts since smalltalk in the
mid 80's. I don't think that's because it's a language that behaves
the way someone coming from another language expects.
On 1/10/07, Bulat Ziganshin
Hello Yitzchak,
Wednesday, January 10, 2007, 12:02:25 PM, you wrote:
Unfortunately, the current situation is that State is only available as a lazy monad, and StateT is only available as a strict monad.
At the very least, the two should be consistent. I would much prefer for them both to be lazy.
imho, lazy monads (as any other lazy things) is a source of beginner's confusion. therefore it may be better to provide "default" monads as strict and lazy ones - for one who knows what he wants - with a Lazy prefix, e.g. LazyST, LazyState...
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hello,
Unfortunately, the current situation is that State is only available as a lazy monad, and StateT is only available as a strict monad.
There is no such distinction in monadLib. The state transformer inherits its behavior from the underlying monad. For example: StateT Int IO is strict, but StatT Int Id is lazy. One way to get a strict state monad with monadLib is like this: import MonadLib data Lift a = Lift { runLift :: a } instance Monad Lift where return x = Lift x Lift x >>= f = f x strict = runLift $ runStateT 2 $ do undefined return 5 lazy = runId $ runStateT 2 $ do undefined return 5 The difference between those two is that "strict == undefined", while "lazy = (5,undefined)". Unfortunately the monad "Lift" is not part of monadLib at the moment so you have to define it on your own, like I did above, but I think that this is a good example of when it is useful, so I will probably add it to the next release. -Iavor

Wow! Now we are talking! Josef Svenningsson wrote:
So instead of: newtype State s a = State { runState :: (s -> (a, s)) } we have: newtype StateP p s a = StateP { runStateP :: (s -> p a s) } Now, instantiating this with different pair types with different strictness properties will give us total control over strictness for state and value.
Beautiful! Iavor Diatchki wrote:
The state transformer inherits its behavior from the underlying monad. For example: StateT Int IO is strict, but StateT Int Id is lazy.
Fantastic! I'm drooling. When can we get stuff like this into MTL? And maybe it is finally time for me to bite the bullet and try out monadLib again (is it still CPS? gulp). Now let's attack Data.* libraries... -Yitzchak

hi,
I'm drooling. When can we get stuff like this into MTL? And maybe it is finally time for me to bite the bullet and try out monadLib again (is it still CPS? gulp).
version 3 (the current version) implements the transformers in the usual way (e.g., as in mtl) so no cps (except, of course, for the continuation transformer). as usual, feedback is welcome. -iavor

On Wed, Jan 10, 2007 at 10:02:36AM -0800, Iavor Diatchki wrote:
[Yitzchak Gale:]
Unfortunately, the current situation is that State is only available as a lazy monad, and StateT is only available as a strict monad.
There is no such distinction in monadLib. The state transformer inherits its behavior from the underlying monad. For example: StateT Int IO is strict, but StatT Int Id is lazy. One way to get a strict state monad with monadLib is like this: [strict pseudo-monad]
This (like StateT) gives you strictness in the pair, but doesn't give the strictness in the state that the original poster wanted.

Hello,
On 1/10/07, Ross Paterson
There is no such distinction in monadLib. The state transformer inherits its behavior from the underlying monad. For example: StateT Int IO is strict, but StatT Int Id is lazy. One way to get a strict state monad with monadLib is like this: [strict pseudo-monad]
This (like StateT) gives you strictness in the pair, but doesn't give the strictness in the state that the original poster wanted.
Once we have this kind of strictness, then the programmer has control over the state. For example, they can define: setStrict x = seq x (set x) ex3 = runLift $ runState 2 $ setStrict undefined >> return 5 ex4 = runId $ runState 2 $ setStrict undefined >> return 5 In these examples "ex3 == undefined" but "ex4 = (5,undefined)". -Iavor

Iavor Diatchki wrote:
The state transformer inherits its behavior from the underlying monad.
Ross Paterson wrote:
This (like StateT) gives you strictness in the pair, but doesn't give the strictness in the state that the original poster wanted.
I think it does - if you run his program with State Int replaced by StateT Int Identity, it now runs in constant memory.
Once we have this kind of strictness, then the programmer has control over the state.
That is true for MTL as well. Regards, Yitz

Ross Paterson wrote:
This (like StateT) gives you strictness in the pair, but doesn't give the strictness in the state that the original poster wanted.
I think the OP wanted both. If State is lazy in the pair, a long chain of the form (a >>= (b >>= (c >>= ... >>= z))) gets build up and blows the stack if it finally turns out that yes, all these steps are needed. Worse than that, there's no way to correct this without changing the definition of (>>=). Laziness in the state component is annoying at times, but not as bad. You can recover strictness by writing put $! x get >>= (put $!) . f instead of put x modify f provided that (>>=) is already strict in the pair. (It gets even more ugly if the state is a Data.Map that needs to be updated strictly, in which Data.Map.update also doesn't work, even combined with the above modifications.) -Udo -- The only problem with seeing too much is that it makes you insane. -- Phaedrus

Unfortunately, the current situation is that State is only available as a lazy monad, and StateT is only available as a strict monad.
I agree with you that both lazy and strict monads are important and that we should have both options in a monad library.
But the fun doesn't end there. There are other strictness properties to consider. Take the state monad for example. Should it be strict or lazy in the state that it carries around? What about the value component? I think the answer to these questions are the same as for monadic strictness above: both strict and lazy variants are useful.
Sorry guys, but it looks like there are monstrous misconceptions of strictness: there is no such thing as a "strict" or a "lazy" monad. There are only functions strict in arguments and thus one can only ask in which arguments (>>=) is strict or how the strictness properties of the result (x >>= y) are obtained from those of x and y. As it turns out, the details are subtle. Let's make an attempt to define "strict in the state". One might say that this refers to a monad (SState s a) with the property that for all (x :: State s a), the semantic function (runState x :: s -> (a,s)) is strict, i.e. runState x _|_ = _|_ Thus, (x) evaluates the state to WHNF (weak head normal form) before it returns a result. Note that this definition "strict in the state" *cannot* be applied to an arbitrary instance (m) of the class (MonadState) because the class does not offer any hints about the semantic function (runState). One cannot state this property in terms of (put),(get),(return) and (>>=) alone. The current implementation of (Control.Monad.State.State s a) is not "strict in the state". Here, we have for example modify f = get >>= put . f runState (modify (+1)) _|_ = ((\s -> (s,s)) >>= (\n -> \s -> ((),n+1))) _|_ = ((),_|_+1) = ((),_|_) which returns the value () but gives an undefined state. This is also the source of Dean's space leak (and stack overflow). Performing graph reduction to WHNF on flip runState undefined . sequence_ . replicate 1000000 $ modify (+1) yields the pair ((), (... (((undefined + 1) + 1) + 1) ... + 1)) Clearly, the second component needs much memory to hold the 1000000 numbers. Evaluating it to WHNF form will result in a stack overflow even before (undefined) raises an exception. But the first component is simply (). So far, so good. An implementation of "strict in the state" would be newtype SState s a = S { runSState :: s -> (a,s) } instance Monad (SState s) where return a = S $ \s -> s `seq` (a, s) m >>= k = S $ \s -> let (a, s') = runSState m s in runSState (k a) s' instance MonadState s (SState s) where get = \s -> s `seq` (s,s) put s = \s' -> s' `seq` ((),s) We assume that the constructor (S) is hidden to the user so that he can only build monadic actions from (return), (>>=), (get) and (put). Note that the (>>=) operation does not mention strictness at all. Given our assumption, we know by induction that (m) and (k a) are "strict in the state" and it follows that (>>=) must be "strict in the state", too. A quick check confirms runSState (modify (+1)) _|_ = _|_ Marvelous, let's try
flip runSState undefined . sequence_ . replicate 1000000 $ modify (+1) *** Exception: stack overflow
What happened? It's a very good exercise to perform graph reduction by hand on this expression to see what's going on. For simplicity, you may want to get your hands dirty on modify (+1) >> modify (+1) >> modify (+1) >> return () The result is in essence a concatenation of strict functions like in f = (+1) . (+1) . (+1) . (+1) ... (+1) While the entire function (f) is strict as well, the intermediate results are not evaluated eagerly enough, resulting in a stack overflow. A concatenation of strict functions is amenable to strictness analysis. So, I strongly suspect that Dean's tick' = get >>= (put $!) . (+1) will yield a favorable result with optimization turned on "-O". But a priori, the problem must be remedied by changing the definition of (>>=) to force the intermediate accumulating parameter, like in m >>= k = S $ \s -> s `seq` let (a, s') = runSState m s in runSState (k a) $! s' The point is that the previous definition of (>>=) could also be used to combine monadic action not "strict in the state" and must perform lazy evaluation to achieve the non-strict semantics in that case, too. In contrast, this definition of (m >>= k) will always return a monadic action "strict in the state", regardless of the strictness of (m) and (k). Accidentally, the definition of (>>=) for (StateT) forces the pair constructor: instance (Monad m) => Monad (StateT s m) where return a = StateT $ \s -> return (a, s) m >>= k = StateT $ \s -> do (a, s') <- runStateT m s runStateT (k a) s' In case (m) and (k) are "strict in the state", this will force the intermediate state (s) and Dean's (tick' :: StateT Int Identity ()) will actually work without a stack overflow. But this does *not* mean that (StateT s m a) is "strict in the state", it's more like making (uncurry k) strict in its argument. For instance, runIdentity $ runStateT (let x = put 0 in x) undefined = ((),0) But the strict match on (,) prevents infinite monadic actions like runIdentity $ runStateT (let x = x >> put 0 in x) 0 I consider this a bug in the definition of (StateT), the line should read ~(a, s') <- runStateT m s But simply saying that (StateT) is "strict" and that (State) is "lazy" does not represent the real situation.
There is no such distinction in monadLib. The state transformer inherits its behavior from the underlying monad. For example: StateT Int IO is strict, but StatT Int Id is lazy. One way to get a strict state monad with monadLib is like this:
import MonadLib
data Lift a = Lift { runLift :: a }
instance Monad Lift where return x = Lift x Lift x >>= f = f x
strict = runLift $ runStateT 2 $ undefined >> return 5 lazy = runId $ runStateT 2 $ undefined >> return 5
The difference between those two is that "strict == undefined", while "lazy = (5,undefined)".
This is a brilliant example of ill-defined notions of "strict" and "lazy". It only assures that (>>=) is strict in its first argument which can easily be circumvented by supplying (Lift undefined). It has nothing to do with "strict in the state" and behaves just like (StateT s Id a):
runLift $ runStateT (let x = put 0 in x) undefined ((),0) runLift $ flip runStateT undefined $ sequence_ . replicate 1000000 $ modify (+1) ((),*** Exception: stack overflow
In the end, there is still the problem of making these multiple forms of "strictness" available to the programmer. While I think that these things are best left to strictness analysis, it would be no good if the programmer loses control over these things. Josef's idea of parametrization on the pair type as in newtype StateP p s a = StateP { runStateP :: (s -> p a s) } is feasible. We have the choice between data PairLL a b = PairLL a b data PairSL a b = PairSL !a b -- and symmetrically PairLS of course data PairSS a b = PairSS !a !b which correspond to the following domains (x,y) (x,y) (x,y) / \ | | / \ | | (_|_,y) (x,_|_) (x,_|_) | \ / | | \ / | | (_|_,_|_) | | | | | _|_ _|_ _|_ But I think that one pair type is missing, namely the "unboxed pair" with the domain structure (x,y) / \ / \ (_|_,y) (x,_|_) \ / \ / (_|_,_|_) = _|_ and a pseudo-definition newtype UPair a b = UPair a b Given these pair types, all of the above variations of strictness (besides the harmless (Lift)) can be obtained via a case-expression in the definition of (>>=): instance Monad (StateP p s) where return a = S $ \s -> p a s m >>= k = S $ \s -> case (runState m s) of p a s' -> runSState (k a) s' With the unboxed pair, the case turns into a let expression (i.e. irrefutable pattern). Incidentally, the (curry) and (uncurry) functions for unboxed pairs are real isomorphisms of types and I think that it offers much more natural semantics than the standard lifted pair. Taking this further, I also think that strictness is best articulated in the place where it naturally belongs to: the type of a function. Types are propositions, functions are proofs and a function proves the propositions about its own strictness properties. The (almost) best solution would be if one could simply say type StateSL a = State !Int a type StateSS a = State !Int !a and get the corresponding behavior. Here, (!) is a type level function that returns a corresponding unboxed type. F.i., the domain for Ints is ... (Up -1) (Up 0) (Up 1) ... \ | / \ | / (Up _|_) | _|_ and the domain for !Int is that of the unboxed integers Int#: -1 0 1 \ | / _|_ (Up) does the boxing and should be the only non-strict constructor available. I don't know whether this has to be exported to user level Haskell, but it would be best if the core language has a type system with strictness annotations and infers the corresponding stuff from user-level Haskell (i.e. does strictness analysis). The difference between lazy and strict is a difference between boxed and unboxed. I even think that the new function "lazy" from GHC 6.6 really has type (Up a -> a). Perhaps it is also possible to make (seq) parametric once again by seq :: forall a,b . !a -> b -> b and the first argument will be forced at run-time simply because of its type it got during type inference. A last remark: strictness is not needed because it's good. Strictness is needed because it exerts control over memory (and time). That's something best left to the compiler. Of course, the compiler's job is not to turn a O(n^2) algorithm into one that runs in O(n) time, this is something only the programmer can do. But the compiler's job is to figure out the `seq`s, fusions and inline definitions because I am too lazy to mark them explicitly. Regards, apfelmus

At 11:02 AM +0200 1/10/07, Yitzchak Gale wrote:
Unfortunately, the current situation is that State is only available as a lazy monad, and StateT is only available as a strict monad.
[...]
The obvious solution would be to have available both a lazy and a strict version of each monad: State, State', StateT, and State'T (or some such), with functions to convert between them. It is trivial to implement that in the current library.
First, thanks for the very helpful reply explaining the situation. Second, how would one know that State is lazy and StateT is strict? I don't see that in the Haddock documentation. Third, isn't it a continuum rather than a binary choice between lazy and strict? In my example, I used ($!) in the definition of (>>=), but that's just one flavor of strictness that was appropriate to my example. Is there some way to parameterize this degree of strictness? Dean

Dean Herington wrote:
Third, isn't it a continuum rather than a binary choice between lazy and strict? In my example, I used ($!) in the definition of (>>=), but that's just one flavor of strictness that was appropriate to my example. Is there some way to parameterize this degree of strictness?
Dean
The r0 and rwhnf and rnf from http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Parallel-... parameterize strictness.
participants (10)
-
apfelmus@quantentunnel.de
-
Bulat Ziganshin
-
Chris Kuklewicz
-
Dean Herington
-
Iavor Diatchki
-
Josef Svenningsson
-
Ross Paterson
-
Steve Downey
-
Udo Stenzel
-
Yitzchak Gale