-- 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

Reply via email to