
Dear Haskellers, Recently I have been looking for a programming language that would be suitable for small scientific and recreational projects and palatable to a picky person like me. (I do theoretical physics and some math; I do not program very often.) Haskell and Clean look attractive from a mathematician's point of view and allow for very elegant solutions in some cases. I tried Clean first because it has a more efficient implementation and better array support. However, I am leaning toward Haskell since it has more libraries, larger community, and some nice features (e.g., the "do" notation). I thought it would be easier to avoid errors when programming in a pure functional language. Indeed, the Haskell type system is great and catches many errors. But in practice, I found it very difficult to write correct programs in Haskell! This is because my definition of correctness includes asymptotic complexity (time and space). I have pondered why Haskell is so prone to space leaks and whether this can be fixed. I posted a related message (describing a space leak caused by inlining) to Glasgow-haskell-users, http://www.haskell.org/pipermail/glasgow-haskell-users/2009-November/018063.... but apparently the GHC developers were busy preparing a new release. Perhaps on Haskell-cafe there are more people with some spare time; I would really appreciate your comments. So, there seem to be several reasons why controlling space usage is difficult: 1) The operational semantics of Haskell is not specified. That said, it seems that unoptimized programs behave in a predictable way if you follow the execution step by step. The Clean report explicitly says that the execution model is graph reduction; I believe that Haskell uses the same model. However, there are some subtleties, e.g., the tail call and selector optimizations. (I read about the selector optimization in Wadler's paper, http://homepages.inf.ed.ac.uk/wadler/topics/garbage-collection.html and saw it mentioned on the GHC development page. It's really nice and indispensable, but it seems to be missing from the user documentation. Is this the following description accurate? After the rhs of a lazy pattern like (a,b) = expression has been evaluated, the pattern does not take up any space, and the space occupied by a and b can be reclaimed independently.) There must be more subtleties. I imagine that a rigorous definition of operational semantics would be too complicated and impractical. But maybe an informal specification is better than nothing? Why people have not attempted to write it? 2) While each step is predictable, the overall behavior of a lazy program can be rather surprising. So one must be very careful. GHC provides two ways to control the evaluation order, seq and bang patterns, but I am not sure which of these (if any) is the right tool. Consider the following example (from the Real World Haskell book): mean :: [Double] -> Double mean xs = sum / fromIntegral num where (num,sum) = foldl' f (0,0) xs :: (Int, Double) f (n,s) x = (n+1, s+x) Although it uses foldl', there is a space leak because Haskell tuples are not strict. There are two possible fixes: f (!n,!s) x = (n+1, s+x) or f (n,s) x = let n1=n+1; s1=s+x in n1 `seq` s1 `seq` (n1,s1) The first one is short, but less natural than the second one, where the offending thunks are suppressed on the spot. Unfortunately, the syntax is awkward; it would be nice to write something like f (n,s) x = (!n+1, !n+1) Well, I am becoming too grumpy, perhaps the bang patterns are fine. More important question: are there established practices to *avoid* space leaks rather than fixing them afterwards? 3) The standard library was not designed with space efficiency in mind; for example, there is sum but no sum'. 4) GHC does a pretty good job optimizing programs for speed, but compiling with the -O option can easily introduce a space leak. I have not encountered such problems with Clean, though my experience is very limited. Apparently, the Clean developers have disallowed some unsafe optimization, see e.g., this message: http://mailman.science.ru.nl/pipermail/clean-list/2009/004140.html I doubt that the Clean solution is 100% reliable because the compiler still uses strictness analysis, which can change the asymptotic space usage (usually for better, but sometimes for worse). So I wonder whether it would be feasible to identify a set of conservative optimizations that do not change the space or time usage more than by a constant factor. For example, the strictness analysis could be limited to fixed-size data. Or instead of strictness analysis, one could inline the top-level patterns of every function. Of course, that would make the optimization less efficient on the average, but predictability is more important. Best regards, Alexei

2) While each step is predictable, the overall behavior of a lazy program can be rather surprising. So one must be very careful. GHC provides two ways to control the evaluation order, seq and bang patterns, but I am not sure which of these (if any) is the right tool. Consider the following example (from the Real World Haskell book): mean :: [Double] -> Double mean xs = sum / fromIntegral num where (num,sum) = foldl' f (0,0) xs :: (Int, Double) f (n,s) x = (n+1, s+x) Although it uses foldl', there is a space leak because Haskell tuples are not strict. There are two possible fixes: f (!n,!s) x = (n+1, s+x) or f (n,s) x = let n1=n+1; s1=s+x in n1 `seq` s1 `seq` (n1,s1) The first one is short, but less natural than the second one, where the offending thunks are suppressed on the spot. Unfortunately, the syntax is awkward; it would be nice to write something like f (n,s) x = (!n+1, !n+1) Well, I am becoming too grumpy, perhaps the bang patterns are fine. More important question: are there established practices to *avoid* space leaks rather than fixing them afterwards?
I believe the expectation is to learn to not be surprised in the areas where lazy or non-strict evaluation can be overused, and to learn all the advantages of non-strict evaluation vs strict, and the power it gives, such that an imperative programmer doesn't feel surprised or angry when things go wrong. I blogged about writing a long running service in Haskell that ran into problems with the lazy State monad, and lazy Data.Map, and I discussed how I had to force evaluations of everything to get the program under control. This wasn't for a hobby, this was for a production system. I believe I've a much better handle on strict vs non-strict than when I started the project, but I felt pretty lost for a while in the process of doing it. I was even using the Maybe monad with it's MonadPlus implementation to avoid using case statements around deconstruction, which I'm sure exacerbated some of my problem. However, since Haskell will evaluate the outer-most stuff first, the trick seems to be to find the point at which you *really* need the values computed, then tell Haskell to get on with it. You kind of have to have an explicit sequence point where all things need to be resolved, and you have to be able to see those in your code. Sometimes you can get away with only doing small pieces at a time. I had about the worst situation I've ever seen for data growth in my code. I had a pile of non-strict expressions, that were all dependencies for the next, running forever, and never getting evaluated except at asynchronous and user-controlled moments. If these expressions had been evaluated strictly, they would have taken up constant space, but since they were all thunks, I got linear data growth over time, until I blew up. Some advice I've gotten since then was to think about using case for strictness rather than explicitly using seq. Turns out case's pattern matching is pretty strict, and that you can often get by with that. I haven't spent a lot of time with core output, but my understanding is that it's all let and case.
3) The standard library was not designed with space efficiency in mind; for example, there is sum but no sum'.
Actually I think that the standard library was designed to be consistent with the way the language is documented to behave. That is to say that it's non-strict by default everywhere it's possible to be so. Control.Monad.State selects Control.Monad.State.Lazy by default instead of Control.Monad.State.Strict, but both exist. Yes, in some cases there's no strict equivalent provided, but is writing a strict sum really a big problem? I think there's stricter folds included because they're not quite as trivial, but once you have a strict fold isn't strict sum pretty easy? I suppose the type of the contained element in the list could make a big difference in whether the strict fold is strict enough, but where do you stop providing strict versions of functions for people? It seems a line must be drawn somewhere, and the right solution is to properly educate Haskell programmer about both the power and drawbacks of non-strict evaluation, and when it's really necessary to turn things off. Giving examples is fine, but one must learn to see the patterns where there is a problem that could brew. Real World Haskell teaches us about the profiling tools that helped me uncover my problems.
Best regards, Alexei
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Dear David, Thank you for your comments. I understand your suggestion that a program should contain some "synchronization points" where the values are evaluated. But this is not easy. Maybe I should just practice more. I while ago I played with the strict and lazy ST monads and was able to achieve the desired behavior, though with difficulty. Unfortunately, there is no universal solution, and one cannot always use standard idioms. For example, the lazy version of ST (and State) has the problem you described, while the strict version exhibits a space leak when used with mapM or sequence. Simply put, one cannot construct a lazy producer out of a strict state. I wrote a special version of sequence, which uses ST.Lazy but forces the evaluation of the implicit state at each step: import Control.Monad import Control.Monad.ST import qualified Control.Monad.ST.Lazy as Lazy seqLST :: [Lazy.ST s a] -> Lazy.ST s [a] seqLST xs = syncLST (f xs) where f [] = return [] f (x:xs) = liftM2 (:) x (seqLST xs) syncLST :: Lazy.ST s a -> Lazy.ST s a syncLST = join . Lazy.strictToLazyST . Lazy.lazyToStrictST . return For the lazy State monad, syncLState m = State $ \s -> s `seq` runState m s I am not completely satisfied with this solution. For one thing, it's slow and can hardly be optimized. It's also not clear whether one should evaluate the input state as I did (there was some reason but I don't remember) or the output state. I think that a better idea would be to use strict (ST s) together with a lazy continuation, (STC s a). It's basically a function s -> a, but one has to wrap it with some GHC-specific types like State#. Mathematically, (STC s a) is an algebra over the (ST s) monad. I'll try that when I have time. More generally, I am looking for reliable and easy to use tools and idioms for space-conscious programming. I appreciate the design of the strict ST and State monads. In particular, ST has a nice invariant that, at any point, the implicit state is fully evaluated. However, I spend a lot of time figuring how the strict and lazy monads actually work. Is there any documentation? Reading the discussion related to your blog, I realized that strict State is different in that it does not actually force the state. But forcing can be achieved by wrapping all actions with the following function: sState :: (s -> (a,s)) -> State s a sState f = State $ \s -> case f s of (a,s') -> s' `seq` (a,s') I hope that somebody will answer my other questions about the operational semantics and optimizations. -Alexei David Leimbach wrote:
2) While each step is predictable, the overall behavior of a lazy program can be rather surprising. So one must be very careful. GHC provides two ways to control the evaluation order, seq and bang patterns, but I am not sure which of these (if any) is the right tool. Consider the following example (from the Real World Haskell book): mean :: [Double] -> Double mean xs = sum / fromIntegral num where (num,sum) = foldl' f (0,0) xs :: (Int, Double) f (n,s) x = (n+1, s+x) Although it uses foldl', there is a space leak because Haskell tuples are not strict. There are two possible fixes: f (!n,!s) x = (n+1, s+x) or f (n,s) x = let n1=n+1; s1=s+x in n1 `seq` s1 `seq` (n1,s1) The first one is short, but less natural than the second one, where the offending thunks are suppressed on the spot. Unfortunately, the syntax is awkward; it would be nice to write something like f (n,s) x = (!n+1, !n+1) Well, I am becoming too grumpy, perhaps the bang patterns are fine. More important question: are there established practices to *avoid* space leaks rather than fixing them afterwards?
I believe the expectation is to learn to not be surprised in the areas where lazy or non-strict evaluation can be overused, and to learn all the advantages of non-strict evaluation vs strict, and the power it gives, such that an imperative programmer doesn't feel surprised or angry when things go wrong.
I blogged about writing a long running service in Haskell that ran into problems with the lazy State monad, and lazy Data.Map, and I discussed how I had to force evaluations of everything to get the program under control. This wasn't for a hobby, this was for a production system. I believe I've a much better handle on strict vs non-strict than when I started the project, but I felt pretty lost for a while in the process of doing it.
I was even using the Maybe monad with it's MonadPlus implementation to avoid using case statements around deconstruction, which I'm sure exacerbated some of my problem. However, since Haskell will evaluate the outer-most stuff first, the trick seems to be to find the point at which you *really* need the values computed, then tell Haskell to get on with it. You kind of have to have an explicit sequence point where all things need to be resolved, and you have to be able to see those in your code. Sometimes you can get away with only doing small pieces at a time.
I had about the worst situation I've ever seen for data growth in my code. I had a pile of non-strict expressions, that were all dependencies for the next, running forever, and never getting evaluated except at asynchronous and user-controlled moments. If these expressions had been evaluated strictly, they would have taken up constant space, but since they were all thunks, I got linear data growth over time, until I blew up.
Some advice I've gotten since then was to think about using case for strictness rather than explicitly using seq. Turns out case's pattern matching is pretty strict, and that you can often get by with that. I haven't spent a lot of time with core output, but my understanding is that it's all let and case.
3) The standard library was not designed with space efficiency in mind; for example, there is sum but no sum'.
Actually I think that the standard library was designed to be consistent with the way the language is documented to behave. That is to say that it's non-strict by default everywhere it's possible to be so. Control.Monad.State selects Control.Monad.State.Lazy by default instead of Control.Monad.State.Strict, but both exist.
Yes, in some cases there's no strict equivalent provided, but is writing a strict sum really a big problem? I think there's stricter folds included because they're not quite as trivial, but once you have a strict fold isn't strict sum pretty easy? I suppose the type of the contained element in the list could make a big difference in whether the strict fold is strict enough, but where do you stop providing strict versions of functions for people? It seems a line must be drawn somewhere, and the right solution is to properly educate Haskell programmer about both the power and drawbacks of non-strict evaluation, and when it's really necessary to turn things off. Giving examples is fine, but one must learn to see the patterns where there is a problem that could brew.
Real World Haskell teaches us about the profiling tools that helped me uncover my problems.
Best regards, Alexei
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sat, Jan 9, 2010 at 2:23 AM, Alexei Kitaev
Reading the discussion related to your blog, I realized that strict State is different in that it does not actually force the state. But forcing can be achieved by wrapping all actions with the following function:
sState :: (s -> (a,s)) -> State s a sState f = State $ \s -> case f s of (a,s') -> s' `seq` (a,s')
I hope that somebody will answer my other questions about the operational semantics and optimizations.
Hi Alexei, you have a ton of great points but I wanted to discuss an issue with this one. It's unusual that this is what you want either; since it only reduces the state to WHNF. For example, if your state is a string, this only evaluates enough to know whether or not the string is empty at each step, and you can still get into trouble with code like this: put ("xxx" ++ some_bad_computation) which leave bottoms inside of your state which won't show up until later. Several attempts to solve this problem exist, but the most commonly used one is the "rnf" strategy from Control.Parallel.Strategies, which uses a typeclass to allow each type to specify how to evaluate itself completely. -- ryan

Ryan Ingram schrieb:
Hi Alexei, you have a ton of great points but I wanted to discuss an issue with this one.
It's unusual that this is what you want either; since it only reduces the state to WHNF. For example, if your state is a string, this only evaluates enough to know whether or not the string is empty at each step, and you can still get into trouble with code like this:
put ("xxx" ++ some_bad_computation)
which leave bottoms inside of your state which won't show up until later.
Several attempts to solve this problem exist, but the most commonly used one is the "rnf" strategy from Control.Parallel.Strategies, which uses a typeclass to allow each type to specify how to evaluate itself completely.
Now available without parallelism in http://hackage.haskell.org/packages/archive/deepseq/1.1.0.0/doc/html/Control... I think that one should generally think before using seq, because it is only strict in the top most constructor. If you know the type you 'seq' on, then you might use a 'case' on it instead and can precisely control the depth of the strictness. Otherwise you might use 'rnf'. I have also some problems with space leaks. Recently I found a space leak in my code, that was because a finalizer did not run as expected. Now I'm seeking more information on how to use finalizers correctly ...
participants (4)
-
Alexei Kitaev
-
David Leimbach
-
Henning Thielemann
-
Ryan Ingram