[Haskell-cafe] "Out of memory" if compiled with -O2, why?

Petr Prokhorenkov prokhorenkov at gmail.com
Wed Dec 1 18:15:30 CET 2010


Hi, Dmitry

I recently had the same problem:
http://www.haskell.org/pipermail/haskell-cafe/2010-November/086450.html

Memory is taken by the list returned by your lst function wich is
being shared across g,h,i,j,k,l,m,n.
Apparently there is no safe and easy way to overcome this yet :(

--
Regards,
Petr



On Wed, Dec 1, 2010 at 5:23 PM, Dmitry Kulagin <dmitry.kulagin at gmail.com> wrote:
> Hi,
>
> I have problems with memory leaks and can't find out how to avoid them.
> I tried to reduce sample to demonstrate the following problems:
> 1) when compiled without -O2 option, it iconsumes 1582MB (!) total memory
> 2) when compiled with -O2 option it terminates with "out of memory"
>
> Actually I don't understand the reasons, particulary why  GC can't
> collect already processed objects g,...,n (see code below)?
>
> I would appreciate very much any help with this situation.
> Thanks!
>
>
> module Main where
>
> import qualified Data.Map as M
>
> len = 15*1024*1024
> lst from = take len $ zip [from..] [0..]
>
> g = M.size $ M.fromList $ lst 0
> h = M.size $ M.fromList $ lst 0
> i = M.size $ M.fromList $ lst 0
> j = M.size $ M.fromList $ lst 0
> k = M.size $ M.fromList $ lst 0
> l = M.size $ M.fromList $ lst 0
> m = M.size $ M.fromList $ lst 0
> n = M.size $ M.fromList $ lst 0
>
> main = do
>    mapM_ print [g,h,i,j,k,l,m,n]
>
> _______________________________________________
> 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