
Hi all, I just noticed that a tiny change to the program which I posted recently in the "More idiomatic use of strictness" thread causes a space leak. The code is: {-# LANGUAGE BangPatterns, PatternGuards #-} import Data.List (foldl') import Data.Char split delim s | [] <- rest = [token] | otherwise = token : split delim (tail rest) where (token,rest) = span (/=delim) s main = do putStrLn =<< fmap (show . stats ["the","a","and"] . split "<DOC>" . words) getContents stats ws docs = foldl' f ((map (const 0) ws),0) docs where f (dfs,n) d = let dfs' = zipWith (\w df -> (df + fromEnum (w `elem` d))) ws dfs in sum dfs' `seq` (dfs',n+1) If I change this line: putStrLn =<< fmap (show . stats ["the","a","and"] . split "<DOC>" . words) getContents to this: putStrLn =<< fmap (show . stats ["the","a","and"] . split "<DOC>" . words . map toLower) getContents suddenly the programs starts using tons of memory instead of running in small constant space. What's going on? Best, -- Grzegorz -- View this message in context: http://www.nabble.com/Strange-space-leak-tp18439685p18439685.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.