[Haskell-cafe] Problems with strictness analysis?
Don Stewart
dons at galois.com
Mon Nov 3 16:35:24 EST 2008
frantisek.kocun:
> yet I need to add a $! to the recursive call of isum to get a truly
> iterative ???
>
> Wait a minute Patai. How would you do that? I'm only beginner I thought I
> can only add strict "!" to data parameters. But to make isum function
> strict would be helpful.
>
Consider this program,
isum 0 s = s
isum n s = isum (n-1) (s+n)
main = case isum 10000000 0 {- rsum 10000000 -} of
0 -> print 0
x -> print x
Now, isum is *not* strict in 's', so without some additional hints or analysis, this
won't be evaluated until the result of isum is required. It will build up a long change of (s + n)
on the stack.
-O0
$ time ./A
Stack space overflow: current size 8388608 bytes.
Of course, we make this strict in a number of ways:
* Turning on optimisations:
-O2
$ time ./A
50000005000000
./A 0.31s user 0.00s system 99% cpu 0.312 total
* Use an explict bang pattern on the 's' variable:
{-# LANGUAGE BangPatterns #-}
isum 0 s = s
isum n !s = isum (n-1) (s+n)
-O0
$ time ./A
50000005000000
./A 0.69s user 0.00s system 95% cpu 0.721 total
Note that by being explict about the strictness in 's' this program produces the desired result
even with all optimisations disabled.
We can then turn on other optimisations:
-O2 -fvia-C -optc-O2
$ time ./A
50000005000000
./A 0.31s user 0.00s system 101% cpu 0.313 total
And it just gets faster.
Now, we can also add an explicit type signature to constrain to a machine Int:
-O2 -fvia-C -optc-O2
$ time ./A
50000005000000
./A 0.03s user 0.00s system 100% cpu 0.033 total
Meaing the final version is:
isum :: Int -> Int -> Int
isum 0 s = s
isum n !s = isum (n-1) (s+n)
So: if you rely on tail recursion on a particular variable, make sure it is
enforced as strict. That's the simplest, most robust way to ensure the
reduction strategy you want is used.
-- Don
More information about the Haskell-Cafe
mailing list