On Wed, Dec 1, 2010 at 6:23 AM, Dmitry Kulagin
<dmitry.kulagin@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]
I'm using ghc7 here. If I run your program with -O2, it takes 1943 MB of memory max.
If I comment out everything except g and h then with -O2 it takes 1521 MB.
If I comment out everything except g then with -O2 it takes 1521 MB.
I'm not sure where the extra 400 MB of memory are going.
When I compile with: -fno-cse -fno-full-laziness and -O2, the memory usage (with g though n) is 1585 MB.
Jason