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