[GHC] #10812: High memory usage

GHC ghc-devs at haskell.org
Sat Aug 29 15:22:22 UTC 2015


#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


More information about the ghc-tickets mailing list