diff options
author | Edward Z. Yang <ezyang@cs.stanford.edu> | 2016-05-12 12:47:16 -0700 |
---|---|---|
committer | Edward Z. Yang <ezyang@cs.stanford.edu> | 2016-08-21 00:53:21 -0700 |
commit | 1f1bd920047fa083de29eba7cedafbe37d350b73 (patch) | |
tree | e774ab9ecba610ab537265bc622d93e2df3145ec /compiler | |
parent | 704913cf79c7dbf9bf622fb3cfe476edd478b5a2 (diff) | |
download | haskell-1f1bd920047fa083de29eba7cedafbe37d350b73.tar.gz |
Introduce BootUnfolding, set when unfolding is absent due to hs-boot file.
Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu>
Test Plan: validate
Reviewers: simonpj, austin, bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D2246
Diffstat (limited to 'compiler')
-rw-r--r-- | compiler/coreSyn/CoreSyn.hs | 22 | ||||
-rw-r--r-- | compiler/coreSyn/CoreUnfold.hs | 1 | ||||
-rw-r--r-- | compiler/coreSyn/CoreUtils.hs | 1 | ||||
-rw-r--r-- | compiler/coreSyn/PprCore.hs | 1 | ||||
-rw-r--r-- | compiler/deSugar/DsMonad.hs | 1 | ||||
-rw-r--r-- | compiler/iface/LoadIface.hs | 2 | ||||
-rw-r--r-- | compiler/iface/TcIface.hs | 20 | ||||
-rw-r--r-- | compiler/main/TidyPgm.hs | 5 | ||||
-rw-r--r-- | compiler/simplCore/Simplify.hs | 1 | ||||
-rw-r--r-- | compiler/specialise/Specialise.hs | 1 | ||||
-rw-r--r-- | compiler/typecheck/TcRnMonad.hs | 12 | ||||
-rw-r--r-- | compiler/typecheck/TcRnTypes.hs | 5 | ||||
-rw-r--r-- | compiler/vectorise/Vectorise/Exp.hs | 1 |
13 files changed, 52 insertions, 21 deletions
diff --git a/compiler/coreSyn/CoreSyn.hs b/compiler/coreSyn/CoreSyn.hs index a6f8f82ec8..183495f7b5 100644 --- a/compiler/coreSyn/CoreSyn.hs +++ b/compiler/coreSyn/CoreSyn.hs @@ -49,7 +49,7 @@ module CoreSyn ( Unfolding(..), UnfoldingGuidance(..), UnfoldingSource(..), -- ** Constructing 'Unfolding's - noUnfolding, evaldUnfolding, mkOtherCon, + noUnfolding, bootUnfolding, evaldUnfolding, mkOtherCon, unSaturatedOk, needSaturated, boringCxtOk, boringCxtNotOk, -- ** Predicates and deconstruction on 'Unfolding' @@ -59,6 +59,7 @@ module CoreSyn ( isExpandableUnfolding, isConLikeUnfolding, isCompulsoryUnfolding, isStableUnfolding, hasStableCoreUnfolding_maybe, isClosedUnfolding, hasSomeUnfolding, + isBootUnfolding, canUnfold, neverUnfoldGuidance, isStableSource, -- * Annotated expression data types @@ -975,7 +976,10 @@ The @Unfolding@ type is declared here to avoid numerous loops -- identifier would have if we substituted its definition in for the identifier. -- This type should be treated as abstract everywhere except in "CoreUnfold" data Unfolding - = NoUnfolding -- ^ We have no information about the unfolding + = NoUnfolding -- ^ We have no information about the unfolding. + + | BootUnfolding -- ^ We have no information about the unfolding, because + -- this 'Id' came from an @hi-boot@ file. | OtherCon [AltCon] -- ^ It ain't one of these constructors. -- @OtherCon xs@ also indicates that something has been evaluated @@ -1160,6 +1164,11 @@ evaldUnfolding :: Unfolding noUnfolding = NoUnfolding evaldUnfolding = OtherCon [] +-- | There is no known 'Unfolding', because this came from an +-- hi-boot file. +bootUnfolding :: Unfolding +bootUnfolding = BootUnfolding + mkOtherCon :: [AltCon] -> Unfolding mkOtherCon = OtherCon @@ -1260,8 +1269,13 @@ isClosedUnfolding _ = True -- | Only returns False if there is no unfolding information available at all hasSomeUnfolding :: Unfolding -> Bool -hasSomeUnfolding NoUnfolding = False -hasSomeUnfolding _ = True +hasSomeUnfolding NoUnfolding = False +hasSomeUnfolding BootUnfolding = False +hasSomeUnfolding _ = True + +isBootUnfolding :: Unfolding -> Bool +isBootUnfolding BootUnfolding = True +isBootUnfolding _ = False neverUnfoldGuidance :: UnfoldingGuidance -> Bool neverUnfoldGuidance UnfNever = True diff --git a/compiler/coreSyn/CoreUnfold.hs b/compiler/coreSyn/CoreUnfold.hs index 885e965fe0..c613ceb20c 100644 --- a/compiler/coreSyn/CoreUnfold.hs +++ b/compiler/coreSyn/CoreUnfold.hs @@ -1065,6 +1065,7 @@ callSiteInline dflags id active_unfolding lone_variable arg_infos cont_info is_wf is_exp guidance | otherwise -> traceInline dflags "Inactive unfolding:" (ppr id) Nothing NoUnfolding -> Nothing + BootUnfolding -> Nothing OtherCon {} -> Nothing DFunUnfolding {} -> Nothing -- Never unfold a DFun diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index f11c6bef04..6a28b9f14c 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -1836,6 +1836,7 @@ diffIdInfo env bndr1 bndr2 -- redundant, and can lead to an exponential blow-up in complexity. diffUnfold :: RnEnv2 -> Unfolding -> Unfolding -> [SDoc] diffUnfold _ NoUnfolding NoUnfolding = [] +diffUnfold _ BootUnfolding BootUnfolding = [] diffUnfold _ (OtherCon cs1) (OtherCon cs2) | cs1 == cs2 = [] diffUnfold env (DFunUnfolding bs1 c1 a1) (DFunUnfolding bs2 c2 a2) diff --git a/compiler/coreSyn/PprCore.hs b/compiler/coreSyn/PprCore.hs index 75e91a4408..ce8a68b032 100644 --- a/compiler/coreSyn/PprCore.hs +++ b/compiler/coreSyn/PprCore.hs @@ -484,6 +484,7 @@ instance Outputable UnfoldingSource where instance Outputable Unfolding where ppr NoUnfolding = text "No unfolding" + ppr BootUnfolding = text "No unfolding (from boot)" ppr (OtherCon cs) = text "OtherCon" <+> ppr cs ppr (DFunUnfolding { df_bndrs = bndrs, df_con = con, df_args = args }) = hang (text "DFun:" <+> ptext (sLit "\\") diff --git a/compiler/deSugar/DsMonad.hs b/compiler/deSugar/DsMonad.hs index 0320cdf3a2..6713aa9663 100644 --- a/compiler/deSugar/DsMonad.hs +++ b/compiler/deSugar/DsMonad.hs @@ -263,6 +263,7 @@ mkDsEnvs dflags mod rdr_env type_env fam_inst_env msg_var pmvar = let if_genv = IfGblEnv { if_doc = text "mkDsEnvs", if_rec_types = Just (mod, return type_env) } if_lenv = mkIfLclEnv mod (text "GHC error in desugarer lookup in" <+> ppr mod) + False -- not boot! real_span = realSrcLocSpan (mkRealSrcLoc (moduleNameFS (moduleName mod)) 1 1) gbl_env = DsGblEnv { ds_mod = mod , ds_fam_inst_env = fam_inst_env diff --git a/compiler/iface/LoadIface.hs b/compiler/iface/LoadIface.hs index ba58c9e456..ad5f7d3dbb 100644 --- a/compiler/iface/LoadIface.hs +++ b/compiler/iface/LoadIface.hs @@ -423,7 +423,7 @@ loadInterface doc_str mod from let loc_doc = text file_path in - initIfaceLcl mod loc_doc $ do + initIfaceLcl mod loc_doc (mi_boot iface) $ do -- Load the new ModIface into the External Package State -- Even home-package interfaces loaded by loadInterface diff --git a/compiler/iface/TcIface.hs b/compiler/iface/TcIface.hs index 527fe71ce1..fa8e26ae5e 100644 --- a/compiler/iface/TcIface.hs +++ b/compiler/iface/TcIface.hs @@ -146,7 +146,7 @@ knots are tied through the EPS. No problem! typecheckIface :: ModIface -- Get the decls from here -> IfG ModDetails typecheckIface iface - = initIfaceLcl (mi_module iface) (text "typecheckIface") $ do + = initIfaceLcl (mi_module iface) (text "typecheckIface") (mi_boot iface) $ do { -- Get the right set of decls and rules. If we are compiling without -O -- we discard pragmas before typechecking, so that we don't "see" -- information that we shouldn't. From a versioning point of view @@ -1241,16 +1241,18 @@ tcIdDetails _ (IfRecSelId tc naughty) tyThingPatSyn _ = panic "tcIdDetails: expecting patsyn" tcIdInfo :: Bool -> Name -> Type -> IfaceIdInfo -> IfL IdInfo -tcIdInfo ignore_prags name ty info - | ignore_prags = return vanillaIdInfo - | otherwise = case info of - NoInfo -> return vanillaIdInfo - HasInfo info -> foldlM tcPrag init_info info - where +tcIdInfo ignore_prags name ty info = do + lcl_env <- getLclEnv -- Set the CgInfo to something sensible but uninformative before -- we start; default assumption is that it has CAFs - init_info = vanillaIdInfo - + let init_info | if_boot lcl_env = vanillaIdInfo `setUnfoldingInfo` BootUnfolding + | otherwise = vanillaIdInfo + if ignore_prags + then return init_info + else case info of + NoInfo -> return init_info + HasInfo info -> foldlM tcPrag init_info info + where tcPrag :: IdInfo -> IfaceInfoItem -> IfL IdInfo tcPrag info HsNoCafRefs = return (info `setCafInfo` NoCafRefs) tcPrag info (HsArity arity) = return (info `setArityInfo` arity) diff --git a/compiler/main/TidyPgm.hs b/compiler/main/TidyPgm.hs index 6ec1e0234e..5bd94e3cae 100644 --- a/compiler/main/TidyPgm.hs +++ b/compiler/main/TidyPgm.hs @@ -183,8 +183,9 @@ mkBootTypeEnv exports ids tcs fam_insts -- Do make sure that we keep Ids that are already Global. -- When typechecking an .hs-boot file, the Ids come through as -- GlobalIds. - final_ids = [ if isLocalId id then globaliseAndTidyId id - else id + final_ids = [ (if isLocalId id then globaliseAndTidyId id + else id) + `setIdUnfolding` BootUnfolding | id <- ids , keep_it id ] diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs index 8bc5dc4c58..47c9323ce1 100644 --- a/compiler/simplCore/Simplify.hs +++ b/compiler/simplCore/Simplify.hs @@ -2911,6 +2911,7 @@ simplUnfolding :: SimplEnv-> TopLevelFlag -> InId -> Unfolding -> SimplM Unfoldi simplUnfolding env top_lvl id unf = case unf of NoUnfolding -> return unf + BootUnfolding -> return unf OtherCon {} -> return unf DFunUnfolding { df_bndrs = bndrs, df_con = con, df_args = args } diff --git a/compiler/specialise/Specialise.hs b/compiler/specialise/Specialise.hs index 72118aa171..e90ea129cd 100644 --- a/compiler/specialise/Specialise.hs +++ b/compiler/specialise/Specialise.hs @@ -748,6 +748,7 @@ wantSpecImport :: DynFlags -> Unfolding -> Bool wantSpecImport dflags unf = case unf of NoUnfolding -> False + BootUnfolding -> False OtherCon {} -> False DFunUnfolding {} -> True CoreUnfolding { uf_src = src, uf_guidance = _guidance } diff --git a/compiler/typecheck/TcRnMonad.hs b/compiler/typecheck/TcRnMonad.hs index 5c2c1e41bb..a83fbf26bd 100644 --- a/compiler/typecheck/TcRnMonad.hs +++ b/compiler/typecheck/TcRnMonad.hs @@ -1600,9 +1600,11 @@ setLocalRdrEnv rdr_env thing_inside ************************************************************************ -} -mkIfLclEnv :: Module -> SDoc -> IfLclEnv -mkIfLclEnv mod loc = IfLclEnv { if_mod = mod, +mkIfLclEnv :: Module -> SDoc -> Bool -> IfLclEnv +mkIfLclEnv mod loc boot + = IfLclEnv { if_mod = mod, if_loc = loc, + if_boot = boot, if_tv_env = emptyFsEnv, if_id_env = emptyFsEnv } @@ -1644,9 +1646,9 @@ initIfaceCheck doc hsc_env do_this } initTcRnIf 'i' hsc_env gbl_env () do_this -initIfaceLcl :: Module -> SDoc -> IfL a -> IfM lcl a -initIfaceLcl mod loc_doc thing_inside - = setLclEnv (mkIfLclEnv mod loc_doc) thing_inside +initIfaceLcl :: Module -> SDoc -> Bool -> IfL a -> IfM lcl a +initIfaceLcl mod loc_doc hi_boot_file thing_inside + = setLclEnv (mkIfLclEnv mod loc_doc hi_boot_file) thing_inside getIfModule :: IfL Module getIfModule = do { env <- getLclEnv; return (if_mod env) } diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index be2c741964..61b00f3727 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -276,6 +276,11 @@ data IfLclEnv -- it means M.f = \x -> x, where M is the if_mod if_mod :: Module, + -- Whether or not the IfaceDecl came from a boot + -- file or not; we'll use this to choose between + -- NoUnfolding and BootUnfolding + if_boot :: Bool, + -- The field is used only for error reporting -- if (say) there's a Lint error in it if_loc :: SDoc, diff --git a/compiler/vectorise/Vectorise/Exp.hs b/compiler/vectorise/Vectorise/Exp.hs index 770adb77de..5ca77b8ffe 100644 --- a/compiler/vectorise/Vectorise/Exp.hs +++ b/compiler/vectorise/Vectorise/Exp.hs @@ -323,6 +323,7 @@ liftSimple aexpr isToplevel :: Var -> Bool isToplevel v | isId v = case realIdUnfolding v of NoUnfolding -> False + BootUnfolding -> False OtherCon {} -> True DFunUnfolding {} -> True CoreUnfolding {uf_is_top = top} -> top |