[GHC] #10812: High memory usage

#10812: High memory usage -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- Hello, lets consider following program: {{{ {-# LANGUAGE NoMonomorphismRestriction #-} import System.Mem.Weak import Control.Concurrent import System.Mem data Tst a = Tst a deriving (Show, Eq) tst a = do let arr = [0 .. a*a*a] v = Tst (seq arr arr) ptr <- mkWeakPtr v Nothing return ptr main = do ptrs <- mapM tst [1..100000000] --performGC --performMajorGC --performMinorGC threadDelay 1000000 xr <- mapM deRefWeak ptrs print $ length $ filter (/= Nothing) xr threadDelay 5000000 return () }}} It simply creates 10 million of weak references to values of {{{Tst}}}. These weak pointers are returned in the main function. After that we sleep a second and ask how meany references are alive. I get the {{{0}}} as a result here - so everything seems ok - garbage collection worked. There is a problem though - somehow the memory was not released, because on the second 5-second sleep the program uses over 14 Gb of RAM on my computer. I'm compiling it simply with {{{ghc -O2 Main.hs}}}. I'm pretty sure this is a bug, because such behaviour is not expected I think. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10812 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10812: High memory usage ---------------------------------+----------------------------------------- Reporter: danilo2 | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ---------------------------------+----------------------------------------- Changes (by danilo2): * os: Unknown/Multiple => MacOS X * architecture: Unknown/Multiple => x86_64 (amd64) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10812#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10812: High memory usage ---------------------------------+----------------------------------------- Reporter: danilo2 | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ---------------------------------+----------------------------------------- Description changed by danilo2: Old description:
Hello, lets consider following program:
{{{ {-# LANGUAGE NoMonomorphismRestriction #-}
import System.Mem.Weak import Control.Concurrent import System.Mem
data Tst a = Tst a deriving (Show, Eq)
tst a = do let arr = [0 .. a*a*a] v = Tst (seq arr arr) ptr <- mkWeakPtr v Nothing return ptr
main = do ptrs <- mapM tst [1..100000000] --performGC --performMajorGC --performMinorGC threadDelay 1000000 xr <- mapM deRefWeak ptrs print $ length $ filter (/= Nothing) xr
threadDelay 5000000
return () }}}
It simply creates 10 million of weak references to values of {{{Tst}}}. These weak pointers are returned in the main function. After that we sleep a second and ask how meany references are alive. I get the {{{0}}} as a result here - so everything seems ok - garbage collection worked. There is a problem though - somehow the memory was not released, because on the second 5-second sleep the program uses over 14 Gb of RAM on my computer.
I'm compiling it simply with {{{ghc -O2 Main.hs}}}. I'm pretty sure this is a bug, because such behaviour is not expected I think.
New description: Hello, lets consider following program: {{{ {-# LANGUAGE NoMonomorphismRestriction #-} import System.Mem.Weak import Control.Concurrent import System.Mem data Tst a = Tst a deriving (Show, Eq) tst a = do let arr = [0 .. a*a*a] v = Tst (seq arr arr) ptr <- mkWeakPtr v Nothing return ptr main = do ptrs <- mapM tst [1..100000000] --performGC --performMajorGC --performMinorGC threadDelay 1000000 xr <- mapM deRefWeak ptrs print $ length $ filter (/= Nothing) xr threadDelay 5000000 return () }}} It simply creates 10 million of weak references to values of {{{Tst}}}. These weak pointers are returned in the main function. After that we sleep a second and ask how meany references are alive. I get the {{{0}}} as a result here - so everything seems ok - garbage collection worked. There is a problem though - somehow the memory was not released, because during the last 5-second sleep the program uses over 14 Gb of RAM on my computer. I'm compiling it simply with {{{ghc -O2 Main.hs}}}. I'm pretty sure this is a bug, because such behaviour is not expected I think. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10812#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10812: High memory usage ---------------------------------+----------------------------------------- Reporter: danilo2 | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ---------------------------------+----------------------------------------- Comment (by bgamari): The problem is that the GC isn't being performed after traversing `xr`; if you manually insert a `performGc` before the `threadDelay` then you will find things behave as you expect. For the record, the given test seems to behave as expected on my machine. My testing methodology was rather crude, {{{ $ ghc -O Test.hs; ./Test & pid=$!; while true; do cat /proc/$pid/stat >> stat; sleep 0.01; done $ ipython --pylab
a = genfromtxt('stat') vsize = a[:,22] # see proc(5) plot(vsize / 1024**2) ylabel('vsize / megabytes') xlabel('something approximating time') }}}
With `[1..10000000]` `vsize` peaked around 1.8GB around 3 seconds after starting the process. With the testcase provided above `vsize` remained at this peak for the remaining duration of the program. With a manual `performGC` after the traversal, however, it dropped to essentially zero around a second after plateauing. It stayed there for the rest of the execution. The moral of the story is if you want the runtime to GC at a given point, you must tell it. GC occurs due to allocation. Given that there is essentially no allocation after the traversal it isn't terribly surprising that no GC is occurring. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10812#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10812: High memory usage ---------------------------------+----------------------------------------- Reporter: danilo2 | Owner: Type: bug | Status: closed Priority: high | Milestone: Component: Compiler | Version: 7.10.2 Resolution: wontfix | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ---------------------------------+----------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => wontfix -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10812#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10812: High memory usage ---------------------------------+----------------------------------------- Reporter: danilo2 | Owner: Type: bug | Status: closed Priority: high | Milestone: Component: Compiler | Version: 7.10.2 Resolution: wontfix | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ---------------------------------+----------------------------------------- Comment (by danilo2): Hello @bgamari! Thank you for your response :) I've tried running {{{performGC}}} manually (please look again in my code - I've tried all the versions above). Unfortunately even running it, nothing happens, the program consumes the same amount of RAM unless it terminates. Additionally I've tried such variant: {{{ {-# LANGUAGE NoMonomorphismRestriction #-} import System.Mem.Weak import Control.Concurrent import System.Mem data Tst a = Tst a deriving (Show, Eq) tst a = do let arr = [0 .. a*a*a] v = Tst (seq arr arr) ptr <- mkWeakPtr v Nothing return ptr xmain = do ptrs <- mapM tst [1..100000000] performGC threadDelay 1000000 xr <- mapM deRefWeak ptrs print $ length $ filter (/= Nothing) xr threadDelay 10000000 return () main = do print "A" xmain print "B" xmain }}} I wanted to check how the program behaves when allocating again some resources, so I run {{{xmain}}} two times. What's interesting is that the memory is still not released and during second execution the amount of RAM used by it exceeds 21 Gb - so it allocates further resources. So I've got 2 questions: 1) Maybe it is Mac OS X related bug? 2) You've told me that GC is performed only when memory is allocated, so when we are performing {{{MapM}}} ten million times, allocating each time a small chunk of memory (and returning weak pointers only), shouldn't the GC be called at last several times then? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10812#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10812: High memory usage ---------------------------------+----------------------------------------- Reporter: danilo2 | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ---------------------------------+----------------------------------------- Changes (by danilo2): * status: closed => new * resolution: wontfix => -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10812#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10812: High memory usage after performing GC ---------------------------------+----------------------------------------- Reporter: danilo2 | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ---------------------------------+----------------------------------------- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10812#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10812: High memory usage after performing GC ---------------------------------+-------------------------------------- Reporter: danilo2 | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by kazu-yamamoto): Even on Linux, I saw: https://github.com/yesodweb/wai/issues/488 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10812#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10812: High memory usage after performing GC ---------------------------------+-------------------------------------- Reporter: danilo2 | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Changes (by bgamari): * cc: simonmar (added) Comment:
I've tried running performGC manually (please look again in my code - I've tried all the versions commented out above).
Ahh, sorry for the misunderstanding.
So I've got 2 questions: 1) Maybe it is Mac OS X related bug?
Given Kazu's observation I guess we can rule this out.
2) You've told me that GC is performed only when memory is allocated, so when we are performing MapM ten million times, allocating each time a small chunk of memory (and returning weak pointers only), shouldn't the GC be called at last several times then?
Ahh, yes, you are right; the `mapM` does need to build its result and will therefore allocate and therefore garbage collect. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10812#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10812: High memory usage after performing GC ---------------------------------+-------------------------------------- Reporter: danilo2 | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by simonmar): Firstly I think the huge list is being lifted out and shared between the two computations, which accounts for all the memory still live at the end of "A". Also, after all the weak pointers have died, it takes a little while for all the finalizers to complete, so the memory won't be free at the point where we do the `performGC`. If you compile with `-threaded` you'll get an idle GC during the waiting period which will release some memory. Overall I haven't seen anything going wrong here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10812#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10812: High memory usage after performing GC ---------------------------------+-------------------------------------- Reporter: danilo2 | Owner: Type: bug | Status: closed Priority: high | Milestone: Component: Compiler | Version: 7.10.2 Resolution: invalid | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Changes (by simonmar): * status: new => closed * resolution: => invalid -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10812#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC