
In the following thread, I reported a problem I was having with programs diverging when they use infinite lists with StateT: http://www.haskell.org//pipermail/haskell-cafe/2005-November/012253.html Roberto Zunino and Wolfgang Jeltsch pointed out that this is a bug in Control.Monad.State: (>>=) is lazy in State, but strict in StateT. The source of the problem is that the pattern match in the definition of (>>=) is inside a let expression in State - so it is lazy - but inside a do expression inside StateT - so it strict. Roberto suggests a one-byte patch to fix this problem: add '~' to make the pattern match in StateT irrefutable. (Note that this has already been done for the MonadFix instance of StateT.) The same fix should be applied to evalStateT and execStateT. They are also stricter than their non-transformer counterparts, for the same reason. -Yitz

Hello,
It is not clear to me what is the right thing to do here (although I
agree that the transformer and the monad should be consistent). In
'monadLib' at first I was very careful to make things as lazy as
possible, but then I noticed that this was a source of memory leaks,
that a user of the library could not really avoid. So now I have
started making things stricter, not in the state itself, but rather
the pair (result,state). One always has to watch out for mfix, of
course, but things appear to be working at the moment.
-Iavor
On 11/21/05, Yitzchak Gale
In the following thread, I reported a problem I was having with programs diverging when they use infinite lists with StateT:
http://www.haskell.org//pipermail/haskell-cafe/2005-November/012253.html
Roberto Zunino and Wolfgang Jeltsch pointed out that this is a bug in Control.Monad.State: (>>=) is lazy in State, but strict in StateT.
The source of the problem is that the pattern match in the definition of (>>=) is inside a let expression in State - so it is lazy - but inside a do expression inside StateT - so it strict.
Roberto suggests a one-byte patch to fix this problem: add '~' to make the pattern match in StateT irrefutable.
(Note that this has already been done for the MonadFix instance of StateT.)
The same fix should be applied to evalStateT and execStateT. They are also stricter than their non-transformer counterparts, for the same reason.
-Yitz _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Hi Iavor,
It is not clear to me what is the right thing to do here (although I agree that the transformer and the monad should be consistent). In 'monadLib' at first I was very careful to make things as lazy as possible, but then I noticed that this was a source of memory leaks, that a user of the library could not really avoid. So now I have started making things stricter,
Lack of laziness is also a serious problem that a user cannot avoid. In my case, I have to completely rewrite StateT, otherwise it is totally unusable. This is definitely a bug. If you make State strict, I am sure it would break many existing programs. (It would certainly break many of mine.) I doubt that very much existing code is relying on the accidental strictness in StateT. Strictness is a problem throughout the Haskell libraries. There was a recent discussion about Data.Map, for example. Right now, there seems to be a need for at least two different versions of every single container and monad in the library, depending on strictness. It would be great if someone could come up with a nicer and more general approach. (And if not - it would be nice of all of those different versions would be added already.) If we are forced to choose one or the other, I would definitely vote for the lazy version. Otherwise, what have we accomplished by using Haskell? Regards, Yitz

Yitzchak Gale wrote:
Lack of laziness is also a serious problem that a user cannot avoid. In my case, I have to completely rewrite StateT, otherwise it is totally unusable. This is definitely a bug.
I disagree. If an operation is lazy, there is absolutely nothing you as a user can to to change that. I've been bitten by that more than once. If an operation is too strict (which I have yet to encounter), you can always wrap the offending data in another constructor. Udo. -- I'm not prejudiced, I hate everyone equally.

Hello,
Just to clarify, I wasn't suggesting that the the monad is strict in
the state component, but rather that it is strict in the pair
containing the result and the state. This is a fine but important
distinction. I doubt it will break many programs, because the API to
the state monad always creates well formed pairs, even something like
'mfix return' is OK.
-Iavor
On 11/22/05, Udo Stenzel
Yitzchak Gale wrote:
Lack of laziness is also a serious problem that a user cannot avoid. In my case, I have to completely rewrite StateT, otherwise it is totally unusable. This is definitely a bug.
I disagree. If an operation is lazy, there is absolutely nothing you as a user can to to change that. I've been bitten by that more than once. If an operation is too strict (which I have yet to encounter), you can always wrap the offending data in another constructor.
Udo. -- I'm not prejudiced, I hate everyone equally.
-----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.1 (GNU/Linux)
iD8DBQFDgyPyc1ZCC9bsOpURApYGAKCWQGLinm2r2ex0aQS+t1bE9+wHDACZAWpI cozKJqXa1qGzTlUHsy1uHIw= =7qbK -----END PGP SIGNATURE-----

Hello,
I did not understand the example you posted, as it contains functions
that are not defined, but here is something you can do (this is using
monadLib, but something like that should probably work with the
libraries distributed with GHC). Let me know if this helps.
-Iavor
import Monad.StateT
import Monad.Id
import Random
type M = StateT (StdGen,[Int]) Id
randomItem :: M ()
randomItem = do (g,xs) <- peek
let (x,g') = random g
poke_ (g',mod x 5 : xs)
needMoreItems :: M Bool
needMoreItems = do (_,xs) <- peek
return (sum xs < 50)
whileM p b = do x <- p
if x then b >> whileM p b else return ()
test = do g <- newStdGen
print $ runId $ evalState (g,[])
$ do whileM needMoreItems randomItem
(_,xs) <- peek
return xs
On 11/22/05, Yitzchak Gale
Hi Iavor,
Just to clarify, I wasn't suggesting that the the monad is strict in the state component, but rather that it is strict in the pair containing the result and the state.
Does this help in the "createItems" examples I sent to Udo in the previous post?
Thanks, Yitz

Hello,
I did not understand the example you posted, as it contains functions
that are not defined, but here is something you can do (this is using
monadLib, but something like that should probably work with the
libraries distributed with GHC). Letme know if this helps.
-Iavor
import Monad.StateT
import Monad.Id
import Random
type M = StateT (StdGen,[Int]) Id
randomItem :: M ()
randomItem = do (g,xs) <- peek
let (x,g') = random g
poke_ (g',mod x 5 : xs)
needMoreItems :: M Bool
needMoreItems = do (_,xs) <- peek
return (sum xs < 50)
whileM p b = do x <- p
if x then b >> whileM p b else return ()
test = do g <- newStdGen
print $ runId $ evalState (g,[])
$ do whileM needMoreItems randomItem
(_,xs) <- peek
return xs
On 11/22/05, Yitzchak Gale
Hi Iavor,
Just to clarify, I wasn't suggesting that the the monad is strict in the state component, but rather that it is strict in the pair containing the result and the state.
Does this help in the "createItems" examples I sent to Udo in the previous post?
Thanks, Yitz

...I did not understand the example you posted, as it contains functions that are not defined...
Sorry. I actually think you understood it quite well, from what you wrote in reply. But OK, I will put in some more annotation below.
but here is something you can do (...using monadLib...). Letme know if this helps.
Well, I like using infinite lists - where a sequence is completely decoupled from its end conditions - as opposed to while-loop-like constructs. And other such lazy paradigms when appropriate. And I also like using monads when they make my code more clear - which is usually. And I like using these things together when they happen to coincide. I gave Udo an example of a common kind of situation in which that happens. You wrote that you introduced some limited kind of strictness in your state monad. My question was: Can I still use infinite lists and state monads together in monadLib? I think your answer is "No." Am I correct? Regards, Yitz Iavor's code:
import Monad.StateT import Monad.Id import Random
type M = StateT (StdGen,[Int]) Id
randomItem :: M () randomItem = do (g,xs) <- peek let (x,g') = random g poke_ (g',mod x 5 : xs)
needMoreItems :: M Bool needMoreItems = do (_,xs) <- peek return (sum xs < 50)
whileM p b = do x <- p if x then b >> whileM p b else return ()
test = do g <- newStdGen print $ runId $ evalState (g,[]) $ do whileM needMoreItems randomItem (_,xs) <- peek return xs
My code (that I wrote to Udo), with additional annotation: import System.Random import Control.Monad.State createItems :: RandomGen g => State g [Item] createItems = liftM catMaybes $ runListT $ flip evalStateT initialState $ runMaybeT $ do item <- liftRandom $ repeatM randomItem updateState item needMoreItems >>= guard return item where liftRandom = lift . lift . lift -- The type of the items we need to create. type Item = Int -- Create one random item. randomItem :: RandomGen g => State g Item randomItem = State $ randomR (1, 5) -- The type of the state we need to keep while -- computing whether we have enough items yet. type MyState = Int -- The initial state while computing whether we -- have enough items yet. initialState :: MyState initialState = 0 -- Update the state after creating an Item. updateState :: MonadState MyState m => Item -> m () updateState = modify . (+) --Do we need any more items? needMoreItems :: MonadState MyState m => m Bool needMoreItems = gets (< 50) -- repeatM is still missing from Control.Monad. -- I hope they will put it in soon. repeatM :: Monad m => m a -> m [a] repeatM = sequence . repeat -- MaybeT is still missing from mtl. -- I hope they will put it in soon. newtype MaybeT m a = MaybeT {runMaybeT :: m (Maybe a)} instance Monad m => Monad (MaybeT m) where ... instance Monad m => MonadPlus (MaybeT m) where ... instance MonadState s m => MonadState s (MaybeT m) where ...

Hello, I am still confused, sorry :-) It appears that the code has a type error: repeatM randomItem :: State g [Int] so, isn't 'item' of type '[Int]'. On the other hand, 'updateState' is expecting an 'Int' as an argument... -Iavor
createItems :: RandomGen g => State g [Item] createItems = liftM catMaybes $ runListT $ flip evalStateT initialState $ runMaybeT $ do item <- liftRandom $ repeatM randomItem updateState item needMoreItems >>= guard return item where liftRandom = lift . lift . lift
-- Create one random item. randomItem :: RandomGen g => State g Item randomItem = State $ randomR (1, 5)
-- repeatM is still missing from Control.Monad. -- I hope they will put it in soon. repeatM :: Monad m => m a -> m [a] repeatM = sequence . repeat

Hi Udo,
Lack of laziness is also a serious problem that a user cannot avoid. In my case, I have to completely rewrite StateT, otherwise it is totally unusable. This is definitely a bug.
I disagree. If an operation is lazy, there is absolutely nothing you as a user can to to change that.
Right. Well, you can rewrite the library, or you can restructure your entire app, but neither of those are very good options.
If an operation is too strict... you can always wrap the offending data in another constructor.
I have seen this claim several times, but I am not yet convinced. In my case, the unwanted strictness is coming from the bind method of a monad from the standard libraries. I don't see how to get rid of that strictness by wrapping something in a constructor. And even when it is possible to reduce strictness by wrapping something - it means changing the interface of existing functions. In a large application, that could be a major disaster. Here is an example. How would you fix this by wrapping something in a constructor? No restructuring is allowed (this is one function in a large application, so changing the interface of any function could have major consequences), and no rewriting libraries is allowed. You need to construct a random list of items. you do not know in advance how many I will need; that is determined by a stateful calculation as you construct the items. Here is the function; it diverges, unless you rewrite StateT with strictness removed: createItems :: RandomGen g => State g [Item] createItems = liftM catMaybes $ runListT $ flip evalStateT initialState $ runMaybeT $ do item <- liftRandom $ repeatM randomItem updateState item needMoreItems >>= guard return item where liftRandom = lift . lift . lift Regards, Yitz

Hello Yitzchak,
If an operation is too strict... you can always wrap the offending data in another constructor.
I have seen this claim several times, but I am not yet convinced.
In my case, the unwanted strictness is coming from the bind method of a monad from the standard libraries. I don't see how to get rid of that strictness by wrapping something in a constructor.
as Iavor already pointed out, theres the fine difference between being string in some implementation detail (the pair of state and result) or in the state itself, which I missed. I was thinking of the state component, and I maintain that it should be strict. Rationale: if the state is some primitive type, you want it strict anyway. If it isn't, the strictness doesn't cost much anyway. If it's still wrong, wrapping in a constructor helps. Your problem however is the strict match against a pair you don't even know is there. Indeed, a strict match against a single constructor datatype is probably always pointless. So it's really a bug in the library, after all.
Here is an example. How would you fix this by wrapping something in a constructor?
You can't, since you don't have access to the offending pair.
createItems :: RandomGen g => State g [Item] createItems = liftM catMaybes $ runListT $ flip evalStateT initialState $ runMaybeT $ do item <- liftRandom $ repeatM randomItem updateState item needMoreItems >>= guard return item where liftRandom = lift . lift . lift
...but this is probably broken anyway. After (repeatM randomItem) presumably the state (the RandomGen) is _|_, but the type of createItems would suggest it is still usable. I wouldn't do that. Other than that it's a bit hard to see what you're trying to accomplish here. Udo. -- "Gadgets are not necessarily an improvement, vide the succession: Blackboard -> Overhead Projector -> PowerPoint" -- E. W. Dijkstra

On Wed, Nov 23, 2005 at 10:58:55AM +0100, Udo Stenzel wrote:
I was thinking of the state component, and I maintain that it should be strict. Rationale: if the state is some primitive type, you want it strict anyway. If it isn't, the strictness doesn't cost much anyway. If it's still wrong, wrapping in a constructor helps.
I can see your point. But we have to be careful; this kind of thing adds complexity to the language, making Haskell harder to learn and programs harder to understand. My intuition tells me: - Things directly related to IO are strict. E.g., IO, ST, file operations, threads, etc. - Things marked explicitly as being strict are strict. E.g., seq, $!, StrictState, Data.Map.StrictMap, etc. - Everything else is lazy - because Haskell is lazy! I think that is pretty much the case today. That may not always be optimal, as you point out. But it sure makes it much easier for me do work in Haskell on a day to day basis. Regards, Yitz

Hi Udo, I am posting this response here on the libraries list, because it is relevant to the discussion about whether State should be lazy or strict by default. I am also cross-posting to the haskell list, because I think the topic may be of more general interest. I wrote:
createItems :: RandomGen g => State g [Item] createItems = liftM catMaybes $ runListT $ flip evalStateT initialState $ runMaybeT $ do item <- liftRandom $ repeatM randomItem updateState item needMoreItems >>= guard return item where liftRandom = lift . lift . lift
Udo Stenzel wrote:
...but this is probably broken anyway. After (repeatM randomItem) presumably the state (the RandomGen) is _|_, but the type of createItems would suggest it is still usable.
No, it works. MaybeT tells ListT when to stop its iteration. After that, the RandomGen can be used again elsewhere.
I wouldn't do that. Other than that it's a bit hard to see what you're trying to accomplish here.
Lazy monads are an important programming paradigm in practice. Laziness helps to completely decouple the various ingredients of the algorithm from each other. This helps in debugging, and in dividing tasks among different development teams. The monadic approach helps makes refactoring easy (a common complaint against Haskell). For example, it would be trivial to add exception handling, or logging. The algorithm is clearly specified as an iteration of a series of steps, the way most people would naturally think of it. Yet the calculation is completely pure. So a compiler is not required to follow the steps literally. It can split the calculation across different threads, processors, http connections, etc., if it is smart enough. This is the way industrial software development should be done. It is clearly far better than imperative OO. Regards, Yitz

= were strict and the lazy version usually gives problems. That is why, for instance, the ST monad is strict by default. The gist of the problem is
Yitzchak,
I think you raise some very relevant questions about the design of Haskell
libraries and how to deal with strictness/laziness. In my experience very
few Haskell programmers have a feel for the strictness/laziness of a
program. Even seasoned Haskell programmers have a hard time with this.
Therefore I think that often the strictness/laziness of a function can be
accidental rather than well thought through, even in libraries. However,
this makes it even more important to think these issues through when
designing a Haskell library. It's an issue which hasn't got by far the
attention that it should have recieved.
About your request regarding the state monad. I think it is the wrong thing
to make >>= strict. Experience tells us that most programmers program as if
that when you make >>= lazy it does not perform a tail call anymore. This
means that everytime you run >>= some piece of memory will be allocated. As
an example, consider a server of some sort with an inner loop using a state
monad. Making >>= lazy will mean that the server will inevitably run out of
memory. But I very much agree with you that the library should provide a
lazy state monad for those moments when the programmer knows what he is
doing and he really wants laziness.
Incidentally I started working on a new monad library some time ago. The
library was designed with the explicit goal of giving the programmer options
about the strictness of functions and data structures while at the same time
being convenient to use. I think I managaged pretty well to accomodate those
goals. However, I never got around to finish it. Some day perhaps....
All the best,
/Josef
On 11/22/05, Yitzchak Gale
Hi Iavor,
It is not clear to me what is the right thing to do here (although I agree that the transformer and the monad should be consistent). In 'monadLib' at first I was very careful to make things as lazy as possible, but then I noticed that this was a source of memory leaks, that a user of the library could not really avoid. So now I have started making things stricter,
Lack of laziness is also a serious problem that a user cannot avoid. In my case, I have to completely rewrite StateT, otherwise it is totally unusable. This is definitely a bug.
If you make State strict, I am sure it would break many existing programs. (It would certainly break many of mine.) I doubt that very much existing code is relying on the accidental strictness in StateT.
Strictness is a problem throughout the Haskell libraries. There was a recent discussion about Data.Map, for example. Right now, there seems to be a need for at least two different versions of every single container and monad in the library, depending on strictness. It would be great if someone could come up with a nicer and more general approach.
(And if not - it would be nice of all of those different versions would be added already.)
If we are forced to choose one or the other, I would definitely vote for the lazy version. Otherwise, what have we accomplished by using Haskell?
Regards, Yitz _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Hi Josef, You wrote:
...Experience tells us that most programmers program as if >>= were strict and the lazy version usually gives problems. That is why, for instance, the ST monad is strict by default.
That is only true for IO. And for ST, which is really just IO restricted to IORefs. In these unusual monads that interact with the Real World, one expects strictness. The monads of the mtl library - and most others - are meant for pure programs that lend themselves to monadic paradigms. Here one expects laziness, as usual in Haskell. Many monad beginners do seem to make the mistake you are referring to. The reason is that they start by using only the IO monad before learning much else about what monads are for. I think that will improve once we begin to see more introductions to Haskell geared to practical programmers.
As an example, consider a server of some sort with an inner loop using a state monad. Making
= lazy will mean that the server will inevitably run out of memory.
Servers interact with the Real World, so you would use IO and ST. But you are right, it would be great to have special strict versions of various monads (and containers like Data.Map) for these situations. Regards, Yitz
participants (4)
-
Iavor Diatchki
-
Josef Svenningsson
-
Udo Stenzel
-
Yitzchak Gale