[commit: ghc] master: Use lookupIfaceTop for loading IfaceDecls. (dd365b1)
git at git.haskell.org
git at git.haskell.org
Wed Jul 22 20:03:38 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/dd365b1baab08b44e8feb1715ecacf7407628d5c/ghc
>---------------------------------------------------------------
commit dd365b1baab08b44e8feb1715ecacf7407628d5c
Author: Edward Z. Yang <ezyang at cs.stanford.edu>
Date: Tue Jul 21 17:16:52 2015 -0700
Use lookupIfaceTop for loading IfaceDecls.
Summary:
It's shorter! And then when Backpack overrides lookupIfaceTop
everyone will see the right information.
Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
Test Plan: validate
Reviewers: simonpj, austin, bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D1090
>---------------------------------------------------------------
dd365b1baab08b44e8feb1715ecacf7407628d5c
compiler/iface/IfaceEnv.hs | 5 ++++-
compiler/iface/LoadIface.hs | 10 ++++------
compiler/iface/TcIface.hs | 4 ++--
3 files changed, 10 insertions(+), 9 deletions(-)
diff --git a/compiler/iface/IfaceEnv.hs b/compiler/iface/IfaceEnv.hs
index 1bd9316..a822b10 100644
--- a/compiler/iface/IfaceEnv.hs
+++ b/compiler/iface/IfaceEnv.hs
@@ -151,7 +151,10 @@ newImplicitBinder base_name mk_sys_occ
ifaceExportNames :: [IfaceExport] -> TcRnIf gbl lcl [AvailInfo]
ifaceExportNames exports = return exports
-lookupOrig :: Module -> OccName -> TcRnIf a b Name
+-- | Look up the 'Name' for a given 'Module' and 'OccName'.
+-- Consider alternately using 'lookupIfaceTop' if you're in the 'IfL' monad
+-- and 'Module' is simply that of the 'ModIface' you are typechecking.
+lookupOrig :: Module -> OccName -> TcRnIf a b Name
lookupOrig mod occ
= do { -- First ensure that mod and occ are evaluated
-- If not, chaos can ensue:
diff --git a/compiler/iface/LoadIface.hs b/compiler/iface/LoadIface.hs
index ad81357..9da1175 100644
--- a/compiler/iface/LoadIface.hs
+++ b/compiler/iface/LoadIface.hs
@@ -585,20 +585,18 @@ loadDecls :: Bool
-> [(Fingerprint, IfaceDecl)]
-> IfL [(Name,TyThing)]
loadDecls ignore_prags ver_decls
- = do { mod <- getIfModule
- ; thingss <- mapM (loadDecl ignore_prags mod) ver_decls
+ = do { thingss <- mapM (loadDecl ignore_prags) ver_decls
; return (concat thingss)
}
loadDecl :: Bool -- Don't load pragmas into the decl pool
- -> Module
-> (Fingerprint, IfaceDecl)
-> IfL [(Name,TyThing)] -- The list can be poked eagerly, but the
-- TyThings are forkM'd thunks
-loadDecl ignore_prags mod (_version, decl)
+loadDecl ignore_prags (_version, decl)
= do { -- Populate the name cache with final versions of all
-- the names associated with the decl
- main_name <- lookupOrig mod (ifName decl)
+ main_name <- lookupIfaceTop (ifName decl)
-- Typecheck the thing, lazily
-- NB. Firstly, the laziness is there in case we never need the
@@ -671,7 +669,7 @@ loadDecl ignore_prags mod (_version, decl)
Nothing ->
pprPanic "loadDecl" (ppr main_name <+> ppr n $$ ppr (decl))
- ; implicit_names <- mapM (lookupOrig mod) (ifaceDeclImplicitBndrs decl)
+ ; implicit_names <- mapM lookupIfaceTop (ifaceDeclImplicitBndrs decl)
-- ; traceIf (text "Loading decl for " <> ppr main_name $$ ppr implicit_names)
; return $ (main_name, thing) :
diff --git a/compiler/iface/TcIface.hs b/compiler/iface/TcIface.hs
index 9480aec..a7c340f 100644
--- a/compiler/iface/TcIface.hs
+++ b/compiler/iface/TcIface.hs
@@ -736,7 +736,7 @@ tcIfaceVectInfo mod typeEnv (IfaceVectInfo
}
where
vectVarMapping name
- = do { vName <- lookupOrig mod (mkLocalisedOccName mod mkVectOcc name)
+ = do { vName <- lookupIfaceTop (mkLocalisedOccName mod mkVectOcc name)
; var <- forkM (ptext (sLit "vect var") <+> ppr name) $
tcIfaceExtId name
; vVar <- forkM (ptext (sLit "vect vVar [mod =") <+>
@@ -764,7 +764,7 @@ tcIfaceVectInfo mod typeEnv (IfaceVectInfo
tcIfaceExtId name
vectTyConVectMapping vars name
- = do { vName <- lookupOrig mod (mkLocalisedOccName mod mkVectTyConOcc name)
+ = do { vName <- lookupIfaceTop (mkLocalisedOccName mod mkVectTyConOcc name)
; vectTyConMapping vars name vName
}
More information about the ghc-commits
mailing list