"Out of memory" if compiled with -O2, why?

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]

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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Thank you, it is indeed very similar problem.
Nevertheless it seems that the lst function is not the direct reason, because:
1) if I inline lst (by hands), the problem is still there
2) size of the list is actially not so large - just 15 millions elements
I am almost sure that the reason is Map.fromList - result of the
function perhaps somehow memoized and not released by GC.
Dmitry.
On Wed, Dec 1, 2010 at 8:15 PM, Petr Prokhorenkov
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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I've tried it out with and without -O2 and with and without manual
inlining. I also used len=1024*1024.
Just in case, the system is Linux x86-64, GHC 6.12.3.
You can find output of memory profiler attached.
It seems that list of pairs is shared only when lst is not manually
inlined and -O2 is enabled.
And the GC certainly cannot collect any of map nodes until M.size has returned.
So, at the same time list [(Integer, Integer)] of length len and Map
Integer Integer of size len are in memory, which
means that an (Integer, Integer) and s single node of this map are
taking together 100 bytes of memory, which I find plausible.
Bottom line --- I see nothing strange about it, except for
unnecessary sharing of lst and M.Map being quite memory-costy.
--
Regards,
Petr
On Thu, Dec 2, 2010 at 1:27 PM, Dmitry Kulagin
Thank you, it is indeed very similar problem. Nevertheless it seems that the lst function is not the direct reason, because: 1) if I inline lst (by hands), the problem is still there 2) size of the list is actially not so large - just 15 millions elements
I am almost sure that the reason is Map.fromList - result of the function perhaps somehow memoized and not released by GC.
Dmitry.
On Wed, Dec 1, 2010 at 8:15 PM, Petr Prokhorenkov
wrote: 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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Wed, Dec 1, 2010 at 6:23 AM, Dmitry Kulagin
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

Hello Jason, Wednesday, December 1, 2010, 8:54:58 PM, you wrote:
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 then with -O2 it takes 1521 MB.
I'm not sure where the extra 400 MB of memory are going.
i think, it's because memory isn't collected immediately, so in first case you just have more garbage hanging around. if you need to measure real workset of your program, you should apply very aggressive (and slow) garbage collection settings -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
participants (4)
-
Bulat Ziganshin
-
Dmitry Kulagin
-
Jason Dagit
-
Petr Prokhorenkov