summaryrefslogtreecommitdiff
path: root/compiler/iface/LoadIface.hs
diff options
context:
space:
mode:
authorSimon Peyton Jones <simonpj@microsoft.com>2014-12-13 22:53:54 +0000
committerSimon Peyton Jones <simonpj@microsoft.com>2014-12-15 10:06:55 +0000
commitd59c59f4d106a5d0dff0ecb164f7a669bee03c13 (patch)
treef6c837d6b320275ad560fff6277e6e33d9d7ccb5 /compiler/iface/LoadIface.hs
parentfbb42b2ea42b6467135f26db47d9c296e7ad75a3 (diff)
downloadhaskell-d59c59f4d106a5d0dff0ecb164f7a669bee03c13.tar.gz
Make Core Lint check for locally-bound GlobalIds
There should be no bindings in this module for a GlobalId; except after CoreTidy, when top-level bindings are globalised. To check for this, I had to make the CoreToDo pass part of the environment that Core Lint caries. But CoreToDo is defined in CoreMonad, which (before this patch) called CoreLint. So I had to do quite a bit of refactoring, moving some lint-invoking code into CoreLint itself. Crucially, I also more tcLookupImported_maybe, importDecl, and checkwiredInTyCon from TcIface (which use CoreLint) to LoadIface (which doesn't). This is probably better structure anyway. So most of this patch is refactoring. The actual check for GlobalIds is in CoreLint.lintAndScopeId
Diffstat (limited to 'compiler/iface/LoadIface.hs')
-rw-r--r--compiler/iface/LoadIface.hs156
1 files changed, 156 insertions, 0 deletions
diff --git a/compiler/iface/LoadIface.hs b/compiler/iface/LoadIface.hs
index 34ae3d507f..6fe805dad6 100644
--- a/compiler/iface/LoadIface.hs
+++ b/compiler/iface/LoadIface.hs
@@ -9,6 +9,10 @@ Loading interface files
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module LoadIface (
+ -- Importing one thing
+ tcLookupImported_maybe, importDecl,
+ checkWiredInTyCon, ifCheckWiredInThing,
+
-- RnM/TcM functions
loadModuleInterface, loadModuleInterfaces,
loadSrcInterface, loadSrcInterface_maybe,
@@ -43,6 +47,7 @@ import PrelInfo
import PrimOp ( allThePrimOps, primOpFixity, primOpOcc )
import MkId ( seqId )
import Rules
+import TyCon
import Annotations
import InstEnv
import FamInstEnv
@@ -70,6 +75,157 @@ import System.FilePath
{-
************************************************************************
* *
+* tcImportDecl is the key function for "faulting in" *
+* imported things
+* *
+************************************************************************
+
+The main idea is this. We are chugging along type-checking source code, and
+find a reference to GHC.Base.map. We call tcLookupGlobal, which doesn't find
+it in the EPS type envt. So it
+ 1 loads GHC.Base.hi
+ 2 gets the decl for GHC.Base.map
+ 3 typechecks it via tcIfaceDecl
+ 4 and adds it to the type env in the EPS
+
+Note that DURING STEP 4, we may find that map's type mentions a type
+constructor that also
+
+Notice that for imported things we read the current version from the EPS
+mutable variable. This is important in situations like
+ ...$(e1)...$(e2)...
+where the code that e1 expands to might import some defns that
+also turn out to be needed by the code that e2 expands to.
+-}
+
+tcLookupImported_maybe :: Name -> TcM (MaybeErr MsgDoc TyThing)
+-- Returns (Failed err) if we can't find the interface file for the thing
+tcLookupImported_maybe name
+ = do { hsc_env <- getTopEnv
+ ; mb_thing <- liftIO (lookupTypeHscEnv hsc_env name)
+ ; case mb_thing of
+ Just thing -> return (Succeeded thing)
+ Nothing -> tcImportDecl_maybe name }
+
+tcImportDecl_maybe :: Name -> TcM (MaybeErr MsgDoc TyThing)
+-- Entry point for *source-code* uses of importDecl
+tcImportDecl_maybe name
+ | Just thing <- wiredInNameTyThing_maybe name
+ = do { when (needWiredInHomeIface thing)
+ (initIfaceTcRn (loadWiredInHomeIface name))
+ -- See Note [Loading instances for wired-in things]
+ ; return (Succeeded thing) }
+ | otherwise
+ = initIfaceTcRn (importDecl name)
+
+importDecl :: Name -> IfM lcl (MaybeErr MsgDoc TyThing)
+-- Get the TyThing for this Name from an interface file
+-- It's not a wired-in thing -- the caller caught that
+importDecl name
+ = ASSERT( not (isWiredInName name) )
+ do { traceIf nd_doc
+
+ -- Load the interface, which should populate the PTE
+ ; mb_iface <- ASSERT2( isExternalName name, ppr name )
+ loadInterface nd_doc (nameModule name) ImportBySystem
+ ; case mb_iface of {
+ Failed err_msg -> return (Failed err_msg) ;
+ Succeeded _ -> do
+
+ -- Now look it up again; this time we should find it
+ { eps <- getEps
+ ; case lookupTypeEnv (eps_PTE eps) name of
+ Just thing -> return (Succeeded thing)
+ Nothing -> return (Failed not_found_msg)
+ }}}
+ where
+ nd_doc = ptext (sLit "Need decl for") <+> ppr name
+ not_found_msg = hang (ptext (sLit "Can't find interface-file declaration for") <+>
+ pprNameSpace (occNameSpace (nameOccName name)) <+> ppr name)
+ 2 (vcat [ptext (sLit "Probable cause: bug in .hi-boot file, or inconsistent .hi file"),
+ ptext (sLit "Use -ddump-if-trace to get an idea of which file caused the error")])
+
+
+{-
+************************************************************************
+* *
+ Checks for wired-in things
+* *
+************************************************************************
+
+Note [Loading instances for wired-in things]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+We need to make sure that we have at least *read* the interface files
+for any module with an instance decl or RULE that we might want.
+
+* If the instance decl is an orphan, we have a whole separate mechanism
+ (loadOrphanModules)
+
+* If the instance decl is not an orphan, then the act of looking at the
+ TyCon or Class will force in the defining module for the
+ TyCon/Class, and hence the instance decl
+
+* BUT, if the TyCon is a wired-in TyCon, we don't really need its interface;
+ but we must make sure we read its interface in case it has instances or
+ rules. That is what LoadIface.loadWiredInHomeInterface does. It's called
+ from TcIface.{tcImportDecl, checkWiredInTyCon, ifCheckWiredInThing}
+
+* HOWEVER, only do this for TyCons. There are no wired-in Classes. There
+ are some wired-in Ids, but we don't want to load their interfaces. For
+ example, Control.Exception.Base.recSelError is wired in, but that module
+ is compiled late in the base library, and we don't want to force it to
+ load before it's been compiled!
+
+All of this is done by the type checker. The renamer plays no role.
+(It used to, but no longer.)
+-}
+
+checkWiredInTyCon :: TyCon -> TcM ()
+-- Ensure that the home module of the TyCon (and hence its instances)
+-- are loaded. See Note [Loading instances for wired-in things]
+-- It might not be a wired-in tycon (see the calls in TcUnify),
+-- in which case this is a no-op.
+checkWiredInTyCon tc
+ | not (isWiredInName tc_name)
+ = return ()
+ | otherwise
+ = do { mod <- getModule
+ ; ASSERT( isExternalName tc_name )
+ when (mod /= nameModule tc_name)
+ (initIfaceTcRn (loadWiredInHomeIface tc_name))
+ -- Don't look for (non-existent) Float.hi when
+ -- compiling Float.lhs, which mentions Float of course
+ -- A bit yukky to call initIfaceTcRn here
+ }
+ where
+ tc_name = tyConName tc
+
+ifCheckWiredInThing :: TyThing -> IfL ()
+-- Even though we are in an interface file, we want to make
+-- sure the instances of a wired-in thing are loaded (imagine f :: Double -> Double)
+-- Ditto want to ensure that RULES are loaded too
+-- See Note [Loading instances for wired-in things]
+ifCheckWiredInThing thing
+ = do { mod <- getIfModule
+ -- Check whether we are typechecking the interface for this
+ -- very module. E.g when compiling the base library in --make mode
+ -- we may typecheck GHC.Base.hi. At that point, GHC.Base is not in
+ -- the HPT, so without the test we'll demand-load it into the PIT!
+ -- C.f. the same test in checkWiredInTyCon above
+ ; let name = getName thing
+ ; ASSERT2( isExternalName name, ppr name )
+ when (needWiredInHomeIface thing && mod /= nameModule name)
+ (loadWiredInHomeIface name) }
+
+needWiredInHomeIface :: TyThing -> Bool
+-- Only for TyCons; see Note [Loading instances for wired-in things]
+needWiredInHomeIface (ATyCon {}) = True
+needWiredInHomeIface _ = False
+
+
+{-
+************************************************************************
+* *
loadSrcInterface, loadOrphanModules, loadInterfaceForName
These three are called from TcM-land