
#14052: Significant GHCi speed regression with :module and `let` in GHC 8.2.1 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: GHCi | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by phadej): when module is loaded into context with `:m` we `InteractiveEval.setContext` which builds `ic_rn_gbl_env` with {{{ !final_rdr_env = all_env `icExtendGblRdrEnv` ic_tythings old_ic }}} Because there aren't shadowing cleanup anymore, `ic_tythings` grows, `icExtendGblRdrEnv` is linear in ic_tythings size, which causes the quadratic behaviour when we repeadetly `:m` modules. So `it` isn't related to this bug. E.g. the `GenExample.hs` version below has similar slowdown: {{{ module Main where import Control.Monad import System.Environment import System.Exit import System.IO main :: IO () main = do args <- getArgs case args of n:_ -> genExamples (read n) _ -> do hPutStrLn stderr "usage: runghc GenExamples.hs <num-examples>" exitWith $ ExitFailure 1 genExamples :: Int -> IO () genExamples nExamples = do putStrLn ":set +s" putStrLn ":l Foo" putStrLn "let bar = ()" -- first one sequence_ [genExample i | i <- [1..nExamples] ] genExample :: Int -> IO () genExample i = putStr $ unlines [ "" , ":m *Foo" , "let foo = bar" -- ask old , "let bar = ()" -- reset, if `let bar = foo` is even slower ] }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14052#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler