stack overflow

Simon Peyton-Jones simonpj@microsoft.com
Mon, 26 Feb 2001 01:26:53 -0800


Consider=20
	foldl (+) 0 [x1,x2,x3,x4,...

This rewrites to

	foldl (+) (0 + x1) [x2,x3,x4,...]
=3D=3D>	foldl (+) (0 + x1 + x2) [x3,x4,...]
=3D=3D>	foldl (+) (0 + x1 + x2 +x3) [x4,...]

And so on.  So we build up a giant chain of thunks.
Finally we evaluate the giant chain, and that builds up
a giant stack.

Why can't GHC evaluate as it goes?  Because it's only
correct to do so if the function is strict in its second argument,
which (+) is, and so is addToFM.

If GHC were to inline foldl more vigorously, this would happen.
Maybe we should make it do so, to avoid gratuitous leaks.

Simon

| -----Original Message-----
| From: Julian Assange [mailto:proff@iq.org]
| Sent: 24 February 2001 10:50
| To: haskell@haskell.org
| Cc: proff@iq.org
| Subject: stack overflow
|=20
|=20
| -- compile with:
| -- ghc -i/usr/lib/ghc-4.08.1/imports/data -lHSdata=20
| -fglasgow-exts -O -fglasgow-exts wordfreq.hs -o wordfreq
| module Main where
| import List
| import Char(toLower)
| import FiniteMap(fmToList,emptyFM,addToFM,lookupWithDefaultFM)
|=20
| main =3D interact (unlines . pretty . sort . fmToList .
|                  makemap . words  . lower)
|        where
|        pretty l  =3D [w ++ " " ++ show n | (w,n) <- l]
|        sort      =3D sortBy (\(_,n0) (_,n1) -> compare n0 n1)
|        makemap   =3D foldl f emptyFM
| 	           where
| 	           f fm word  =3D addToFM fm word (n+1)
| 	                        where
|                                 n =3D lookupWithDefaultFM fm 0 word
|        lower     =3D map toLower
|=20
|=20
|=20
| When used with a 170k input file, makemap suffers from a stack
| overflow. foldl should be tail recursive. What's the score?
|=20
| Julian
|=20
| _______________________________________________
| Haskell mailing list
| Haskell@haskell.org
| http://www.haskell.org/mailman/listinfo/haskell
|=20