#4208: ghci/Linker.lhs space leaks
---------------------------------+------------------------------------------
Reporter: TristanAllwood | Owner:
Type: bug | Status: new
Priority: normal | Component: GHC API
Version: 6.12.3 | Keywords:
Os: Unknown/Multiple | Testcase:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
Comment(by TristanAllwood):
Small example to replicate, (uses ghc-paths from hackage)
{{{
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE MagicHash #-}
module Main where
import GHC.Paths
import GHC
import Control.Monad
import PrelNames
import Linker
import GHC.Prim
import MonadUtils
main :: IO ()
main = runGhc (Just libdir) $ do
dflags' <- getSessionDynFlags
primPackages <- setSessionDynFlags dflags'
dflags <- getSessionDynFlags
defaultCleanupHandler dflags $ do
liftIO $ initDynLinker dflags
liftIO $ linkPackages dflags primPackages
replicateM_ 1000000 $ do
!printVal <- getSession >>= (liftIO . flip getHValue printName)
return ()
}}}
run with
{{{
ghc --make -package ghc X.hs
./X +RTS -hT -RTS
}}}
hp2ps graph output attached
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4208#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs