[Haskell-cafe] Re: bizarre memory usage with data.binary

Anatoly Yakovenko aeyakovenko at gmail.com
Tue Oct 2 20:01:31 EDT 2007


Program1:

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"

vs

Program2:

module Main where

import Data.Binary
import Data.List(foldl')


main = do
  let sum' = foldl' (+) 0
  let list::[Int] = [1..]
  print $ sum' list
  print "done"

neither program is expected to terminate.  The point of these examples
is to demonstrate that Data.Binary encode and decode have some strange
memory allocation patters.

If you run Program1, it will run forever, but its memory usage on my
machine goes to 500M then back down to 17M then back up to 500M then
back down to 17M... repeatedly.  I don't think this has anything to do
with running out of space in a 32 bit integer.

Program2 on the other hand runs at constant memory at around 2M.

Anatoly

On 10/2/07, Anatoly Yakovenko <aeyakovenko at gmail.com> 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?
>
>
> Thanks,
> Anatoly
>


More information about the Haskell-Cafe mailing list