[commit: ghc] wip/lazy-interface-unfoldings: Hi (3a1210f)

git at git.haskell.org git at git.haskell.org
Tue Mar 5 21:44:08 UTC 2019


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/lazy-interface-unfoldings
Link       : http://ghc.haskell.org/trac/ghc/changeset/3a1210f20915702983e4750a280daf8892e51c31/ghc

>---------------------------------------------------------------

commit 3a1210f20915702983e4750a280daf8892e51c31
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Mon Mar 4 23:19:42 2019 -0500

    Hi


>---------------------------------------------------------------

3a1210f20915702983e4750a280daf8892e51c31
 compiler/deSugar/Desugar.hs    | 10 +++++-----
 compiler/iface/TcIface.hs      |  8 ++++----
 compiler/iface/TcIface.hs-boot |  1 -
 3 files changed, 9 insertions(+), 10 deletions(-)

diff --git a/compiler/deSugar/Desugar.hs b/compiler/deSugar/Desugar.hs
index 5bec60e..1e1aa92 100644
--- a/compiler/deSugar/Desugar.hs
+++ b/compiler/deSugar/Desugar.hs
@@ -418,14 +418,14 @@ dsRule _ = panic "dsRule: Impossible Match" -- due to #15884
 warnRuleShadowing :: RuleName -> Activation -> Id -> [Id] -> DsM ()
 -- See Note [Rules and inlining/other rules]
 warnRuleShadowing rule_name rule_act fn_id arg_ids
-  = do { check False fn_id    -- We often have multiple rules for the same Id in a
-                              -- module. Maybe we should check that they don't overlap
-                              -- but currently we don't
-       ; dflags <- getDynFlags
+  = do { dflags <- getDynFlags
+       ; check dflags False fn_id  -- We often have multiple rules for the same Id in a
+                                   -- module. Maybe we should check that they don't overlap
+                                   -- but currently we don't
        ; mapM_ (check dflags True) arg_ids }
   where
     check dflags check_rules_too lhs_id
-      | isLocalId lhs_id || (canUnfold (idOptUnfolding dflags lhs_id)
+      | isLocalId lhs_id || (canUnfold (idOptUnfolding dflags lhs_id))
                        -- If imported with no unfolding, no worries
       , idInlineActivation lhs_id `competesWith` rule_act
       = warnDs (Reason Opt_WarnInlineRuleShadowing)
diff --git a/compiler/iface/TcIface.hs b/compiler/iface/TcIface.hs
index 9fce8aa..afb306d 100644
--- a/compiler/iface/TcIface.hs
+++ b/compiler/iface/TcIface.hs
@@ -370,7 +370,7 @@ typecheckIfacesForMerging mod ifaces tc_env_var =
         -- See Note [Resolving never-exported Names in TcIface]
         type_env <- fixM $ \type_env -> do
             setImplicitEnvM type_env $ do
-                decls <- loadDecls ignore_prags (mi_decls iface)
+                decls <- loadDecls (mi_decls iface)
                 return (mkNameEnv decls)
         -- But note that we use this type_env to typecheck references to DFun
         -- in 'IfaceInst'
@@ -415,6 +415,7 @@ typecheckIfaceForInstantiate nsubst iface =
     setImplicitEnvM type_env $ do
     insts     <- mapM tcIfaceInst (mi_insts iface)
     fam_insts <- mapM tcIfaceFamInst (mi_fam_insts iface)
+    rules     <- tcIfaceRules (mi_rules iface)
     anns      <- tcIfaceAnnotations (mi_anns iface)
     exports   <- ifaceExportNames (mi_exports iface)
     complete_sigs <- tcIfaceCompleteSigs (mi_complete_sigs iface)
@@ -619,7 +620,6 @@ tcIfaceDecl :: IfaceDecl
 tcIfaceDecl = tc_iface_decl Nothing
 
 tc_iface_decl :: Maybe Class  -- ^ For associated type/data family declarations
-              -> Bool         -- ^ True <=> discard IdInfo on IfaceId bindings
               -> IfaceDecl
               -> IfL TyThing
 tc_iface_decl _ (IfaceId {ifName = name, ifType = iface_type,
@@ -715,7 +715,7 @@ tc_iface_decl _parent
     ; cls  <- buildClass tc_name binders' roles fds Nothing
     ; return (ATyCon (classTyCon cls)) }
 
-tc_iface_decl _parent ignore_prags
+tc_iface_decl _parent
             (IfaceClass {ifName = tc_name,
                          ifRoles = roles,
                          ifBinders = binders,
@@ -1431,7 +1431,7 @@ tcIdDetails ty IfDFunId
 
 tcIdDetails _ (IfRecSelId tc naughty)
   = do { tc' <- either (fmap RecSelData . tcIfaceTyCon)
-                       (fmap (RecSelPatSyn . tyThingPatSyn) . tcIfaceDecl False)
+                       (fmap (RecSelPatSyn . tyThingPatSyn) . tcIfaceDecl)
                        tc
        ; return (RecSelId { sel_tycon = tc', sel_naughty = naughty }) }
   where
diff --git a/compiler/iface/TcIface.hs-boot b/compiler/iface/TcIface.hs-boot
index f1e7dd7..ddf0455 100644
--- a/compiler/iface/TcIface.hs-boot
+++ b/compiler/iface/TcIface.hs-boot
@@ -1,6 +1,5 @@
 module TcIface where
 
-import GhcPrelude
 import IfaceSyn    ( IfaceDecl, IfaceClsInst, IfaceFamInst, IfaceRule,
                      IfaceAnnotation, IfaceCompleteMatch )
 import TyCoRep     ( TyThing )



More information about the ghc-commits mailing list