On Tue, Oct 02, 2007 at 04:08:01PM -0700, Anatoly Yakovenko wrote:
> i am getting some weird memory usage out of this program:
> 
> 
> module Main where
> 
> import Data.Binary
> import Data.List(foldl')
> 
> 
> main = do
>    let sum' = foldl' (+) 0
>    let list::[Int] = decode $ encode $ ([1..] :: [Int])
>    print $ sum' list
>    print "done"
> 
> it goes up to 500M and down to 17M on windows.  Its build with ghc
> 6.6.1 with the latest data.binary
> 
> Any ideas what could be causing the memory usage to jump around so much?

Only 500M?  encode for lists is strict, I would have expected around
80GB usage...  What does -ddump-simpl-stats say?

Stefan

Attachment: signature.asc
Description: Digital signature

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to