[commit: ghc] master: Suppress AMP warnings with -XNoImplicitPrelude (fixed Trac #8320) (c027092)

git at git.haskell.org git at git.haskell.org
Thu Oct 24 08:31:52 UTC 2013


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/c0270922e0ddd3de549ba7c99244faf431d0740f/ghc

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

commit c0270922e0ddd3de549ba7c99244faf431d0740f
Author: Simon Peyton Jones <simonpj at static.144-76-175-55.clients.your-server.de>
Date:   Thu Oct 24 03:07:26 2013 -0500

    Suppress AMP warnings with -XNoImplicitPrelude (fixed Trac #8320)
    
    The AMP warnings caused 'base' to be loaded even when we were
    compiling 'ghc-prim'.  That is bad, bad, bad.  We got a very
    obscure message
       attempting to use module ‛ghc-prim:GHC.Types’
         (libraries/ghc-prim/./GHC/Types.hs) which is not loaded
    
    See Note [Home module load error] in LoadIface


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

c0270922e0ddd3de549ba7c99244faf431d0740f
 compiler/iface/LoadIface.lhs      |   25 +++++++++++++++++++++----
 compiler/typecheck/TcRnDriver.lhs |   18 ++++++++++++++++--
 2 files changed, 37 insertions(+), 6 deletions(-)

diff --git a/compiler/iface/LoadIface.lhs b/compiler/iface/LoadIface.lhs
index 0fc8e68..ab522db 100644
--- a/compiler/iface/LoadIface.lhs
+++ b/compiler/iface/LoadIface.lhs
@@ -495,6 +495,25 @@ bumpDeclStats name
 %*                                                      *
 %*********************************************************
 
+Note [Home module load error]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+If the sought-for interface is in the current package (as determined
+by -package-name flag) then it jolly well should already be in the HPT
+because we process home-package modules in dependency order.  (Except
+in one-shot mode; see notes with hsc_HPT decl in HscTypes).
+
+It is possible (though hard) to get this error through user behaviour.
+  * Suppose package P (modules P1, P2) depends on package Q (modules Q1,
+    Q2, with Q2 importing Q1)
+  * We compile both packages.  
+  * Now we edit package Q so that it somehow depends on P
+  * Now recompile Q with --make (without recompiling P).  
+  * Then Q1 imports, say, P1, which in turn depends on Q2. So Q2
+    is a home-package module which is not yet in the HPT!  Disaster.
+
+This actually happened with P=base, Q=ghc-prim, via the AMP warnings.
+See Trac #8320.
+
 \begin{code}
 findAndReadIface :: SDoc -> Module
                  -> IsBootInterface     -- True  <=> Look for a .hi-boot file
@@ -533,10 +552,7 @@ findAndReadIface doc_str mod hi_boot_file
                        let file_path = addBootSuffix_maybe hi_boot_file
                                                            (ml_hi_file loc)
 
-                       -- If the interface is in the current package
-                       -- then if we could load it would already be in
-                       -- the HPT and we assume that our callers checked
-                       -- that.
+                       -- See Note [Home module load error]
                        if thisPackage dflags == modulePackageId mod &&
                           not (isOneShot (ghcMode dflags))
                            then return (Failed (homeModError mod loc))
@@ -866,6 +882,7 @@ wrongIfaceModErr iface mod_name file_path
   where iface_file = doubleQuotes (text file_path)
 
 homeModError :: Module -> ModLocation -> SDoc
+-- See Note [Home module load error]
 homeModError mod location
   = ptext (sLit "attempting to use module ") <> quotes (ppr mod)
     <> (case ml_hs_file location of
diff --git a/compiler/typecheck/TcRnDriver.lhs b/compiler/typecheck/TcRnDriver.lhs
index 247998a..594d7fd 100644
--- a/compiler/typecheck/TcRnDriver.lhs
+++ b/compiler/typecheck/TcRnDriver.lhs
@@ -947,12 +947,26 @@ rnTopSrcDecls extra_deps group
 %*                                                                      *
 %************************************************************************
 
+Note [No AMP warning with NoImplicitPrelude]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+If you have -XNoImplicitPrelude, then we suppress the AMP warnings.
+The AMP warnings need access to Monad, Applicative, etc, and they
+are defined in 'base'. If, when compiling package 'ghc-prim' (say),
+you try to load Monad (from 'base'), chaos results because 'base'
+depends on 'ghc-prim'.  See Note [Home module load error] in LoadIface,
+and Trac #8320.
+
+Using -XNoImplicitPrelude is a proxy for ensuring that all the
+'base' modules are below the home module in the dependency tree.
+
 \begin{code}
 -- | Main entry point for generating AMP warnings
 tcAmpWarn :: TcM ()
 tcAmpWarn =
-    do { warnFlag <- woptM Opt_WarnAMP
-       ; when warnFlag $ do {
+    do { implicit_prel <- xoptM Opt_ImplicitPrelude
+       ; warnFlag <- woptM Opt_WarnAMP
+       ; when (warnFlag && implicit_prel) $ do {
+              -- See Note [No AMP warning with NoImplicitPrelude]
 
          -- Monad without Applicative
        ; tcAmpMissingParentClassWarn monadClassName



More information about the ghc-commits mailing list