Huge space leak of GHC API 7.8.x?
Simon Peyton Jones
simonpj at microsoft.com
Mon Jul 14 07:39:53 UTC 2014
Would you like to create a Trac ticket?
Is anyone able to investigate?
Simon
| -----Original Message-----
| From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Kazu
| Yamamoto
| Sent: 14 July 2014 08:00
| To: ghc-devs at haskell.org
| Subject: Huge space leak of GHC API 7.8.x?
|
| Hi,
|
| Some guys reported to me that ghc-mod uses about 1G bytes on Mac and I
| can reproduce this. I tried to understand why ghc-mod uses such huge
| memory.
|
| I found that GHC API 7.8.x uses much more memory than GHC API 7.6.x.
| Attached two files demonstrate this:
|
| - A.hs -- Simple program using GHC API (copied from Wiki)
| - B.hs -- A target file, just hello world
|
| You can compile A.hs as follows:
|
| % ghc A.hs -package ghc -package ghc-paths
|
| The following is the result:
|
| Mac (64bit) Linux (64bit)
| GHC 7.6.3: 20MB 4MB
| GHC 7.8.3: 106MB 13MB
|
| So, I think GHC API 7.8.x has huge space leak. (And I'm wondering why
| Mac uses much more memory than Linux).
|
| I would like to hear opinions from you guys.
|
| --Kazu
|
| <A.hs>
| import Control.Concurrent
| import CoreMonad (liftIO)
| import DynFlags
| import GHC
| import GHC.Paths (libdir)
|
| main = defaultErrorHandler defaultFatalMessager defaultFlushOut $ do
| runGhc (Just libdir) $ do
| dflags <- getSessionDynFlags
| let dflags' = dflags {hscTarget = HscInterpreted
| ,ghcLink = LinkInMemory
| ,ghcMode = CompManager
| }
| setSessionDynFlags dflags'
| target <- guessTarget "B.hs" Nothing
| setTargets [target]
| load LoadAllTargets
| liftIO $ threadDelay 10000000
| </A.hs>
| <B.hs>
| module B where
|
| main = print "Hello, World!"
| </B.hs>
| _______________________________________________
| ghc-devs mailing list
| ghc-devs at haskell.org
| http://www.haskell.org/mailman/listinfo/ghc-devs
More information about the ghc-devs
mailing list