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

Anatoly Yakovenko aeyakovenko at gmail.com
Tue Oct 2 20:35:59 EDT 2007


servers never terminate, pretend that i have a server that reads a
list encoded with data.binary from a socket, and sums it up and
returns the current sum.  i would expect it to run in constant memory,
never terminate, and do useful work.

which is basically the problem that I am facing right now.  my program
seems to grow randomly in memory use when marshaling large data types
encoded using data.binary.

On 10/2/07, Dan Weston <westondan at imageworks.com> wrote:
> Maybe what you are observing is that the operational semantics of
> undefined is undefined. The program can halt, run forever, use no
> memory, use all the memory.
>
> Although I doubt what GHC does with this code is a random process, I
> don't think it's too meaningful to ask what are the space usage patterns
> of a program returning bottom.
>
> Anatoly Yakovenko wrote:
> > 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
> >>
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> >
>
>
>


More information about the Haskell-Cafe mailing list