[Haskell-cafe] More idiomatic use of strictness
Grzegorz Chrupala
grzegorz.chrupala at computing.dcu.ie
Thu Jul 10 06:16:25 EDT 2008
Hi all,
Is there a less ugly way of avoiding laziness in the code pasted below then
the use of seq in the last line?
The program is supposed to split a large input file into chunks and check in
how many of those chunks each of a list of words appear, as well as the
total number of chunks. Without the seq it consumes huge amounts of memory.
Thanks!
Grzegorz
{-# LANGUAGE BangPatterns, PatternGuards #-}
import Data.List (foldl')
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)
--
View this message in context: http://www.nabble.com/More-idiomatic-use-of-strictness-tp18379800p18379800.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
More information about the Haskell-Cafe
mailing list