summaryrefslogtreecommitdiff
path: root/compiler/typecheck
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/typecheck')
-rw-r--r--compiler/typecheck/TcRnDriver.hs7
-rw-r--r--compiler/typecheck/TcRnTypes.hs12
2 files changed, 13 insertions, 6 deletions
diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs
index 81cba29040..63fe36d2c8 100644
--- a/compiler/typecheck/TcRnDriver.hs
+++ b/compiler/typecheck/TcRnDriver.hs
@@ -8,6 +8,7 @@ https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/TypeChecker
-}
{-# LANGUAGE CPP #-}
+{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NondecreasingIndentation #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
@@ -132,6 +133,7 @@ import Data.Data ( Data )
import HsDumpAst
import qualified Data.Set as S
+import Control.DeepSeq
import Control.Monad
#include "HsVersions.h"
@@ -1788,8 +1790,8 @@ runTcInteractive hsc_env thing_inside
(loadSrcInterface (text "runTcInteractive") m
False mb_pkg)
- ; orphs <- fmap concat . forM (ic_imports icxt) $ \i ->
- case i of
+ ; !orphs <- fmap (force . concat) . forM (ic_imports icxt) $ \i ->
+ case i of -- force above: see #15111
IIModule n -> getOrphans n Nothing
IIDecl i ->
let mb_pkg = sl_fs <$> ideclPkgQual i in
@@ -1798,6 +1800,7 @@ runTcInteractive hsc_env thing_inside
; let imports = emptyImportAvails {
imp_orphs = orphs
}
+
; (gbl_env, lcl_env) <- getEnvs
; let gbl_env' = gbl_env {
tcg_rdr_env = ic_rn_gbl_env icxt
diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs
index 781c6bada4..968330da8b 100644
--- a/compiler/typecheck/TcRnTypes.hs
+++ b/compiler/typecheck/TcRnTypes.hs
@@ -270,8 +270,9 @@ type TcM = TcRn
-- the lcl type).
data Env gbl lcl
= Env {
- env_top :: HscEnv, -- Top-level stuff that never changes
+ env_top :: !HscEnv, -- Top-level stuff that never changes
-- Includes all info about imported things
+ -- BangPattern is to fix leak, see #15111
env_us :: {-# UNPACK #-} !(IORef UniqSupply),
-- Unique supply for local variables
@@ -526,10 +527,12 @@ data TcGblEnv
-- bound in this module when dealing with hi-boot recursions
-- Updated at intervals (e.g. after dealing with types and classes)
- tcg_inst_env :: InstEnv,
+ tcg_inst_env :: !InstEnv,
-- ^ Instance envt for all /home-package/ modules;
-- Includes the dfuns in tcg_insts
- tcg_fam_inst_env :: FamInstEnv, -- ^ Ditto for family instances
+ -- NB. BangPattern is to fix a leak, see #15111
+ tcg_fam_inst_env :: !FamInstEnv, -- ^ Ditto for family instances
+ -- NB. BangPattern is to fix a leak, see #15111
tcg_ann_env :: AnnEnv, -- ^ And for annotations
-- Now a bunch of things about this module that are simply
@@ -679,8 +682,9 @@ data TcGblEnv
tcg_patsyns :: [PatSyn], -- ...Pattern synonyms
tcg_doc_hdr :: Maybe LHsDocString, -- ^ Maybe Haddock header docs
- tcg_hpc :: AnyHpcUsage, -- ^ @True@ if any part of the
+ tcg_hpc :: !AnyHpcUsage, -- ^ @True@ if any part of the
-- prog uses hpc instrumentation.
+ -- NB. BangPattern is to fix a leak, see #15111
tcg_self_boot :: SelfBootInfo, -- ^ Whether this module has a
-- corresponding hi-boot file