Don't import FastString in HsVersions.h
[ghc-hetmet.git] / compiler / iface / LoadIface.lhs
index 34026a6..feb51d1 100644 (file)
@@ -52,12 +52,15 @@ import SrcLoc
 import Maybes
 import ErrUtils
 import Finder
-import UniqFM
+import LazyUniqFM
 import StaticFlags
 import Outputable
 import BinIface
 import Panic
+import Util
+import FastString
 
+import Control.Monad
 import Data.List
 import Data.Maybe
 import Data.IORef
@@ -83,7 +86,7 @@ loadSrcInterface doc mod want_boot  = do
   -- interface; it will call the Finder again, but the ModLocation will be
   -- cached from the first search.
   hsc_env <- getTopEnv
-  res <- ioToIOEnv $ findImportedModule hsc_env mod Nothing
+  res <- liftIO $ findImportedModule hsc_env mod Nothing
   case res of
     Found _ mod -> do
       mb_iface <- initIfaceTcRn $ loadInterface doc mod (ImportByUser want_boot)
@@ -99,12 +102,12 @@ loadOrphanModules :: [Module]            -- the modules
                  -> Bool             -- these are family instance-modules
                  -> TcM ()
 loadOrphanModules mods isFamInstMod
-  | null mods = returnM ()
+  | null mods = return ()
   | otherwise = initIfaceTcRn $
                do { traceIf (text "Loading orphan modules:" <+> 
                                 fsep (map ppr mods))
-                  ; mappM_ load mods
-                  ; returnM () }
+                  ; mapM_ load mods
+                  ; return () }
   where
     load mod   = loadSysInterface (mk_doc mod) mod
     mk_doc mod 
@@ -114,14 +117,14 @@ loadOrphanModules mods isFamInstMod
 -- | Loads the interface for a given Name.
 loadInterfaceForName :: SDoc -> Name -> TcRn ModIface
 loadInterfaceForName doc name
-  = do { 
-#ifdef DEBUG
-               -- Should not be called with a name from the module being compiled
-         this_mod <- getModule
-       ; ASSERT2( not (nameIsLocalOrFrom this_mod name), ppr name <+> parens doc )
-#endif
-         initIfaceTcRn $ loadSysInterface doc (nameModule name)
-    }
+  = do { 
+    when debugIsOn $ do
+        -- Should not be called with a name from the module being compiled
+        { this_mod <- getModule
+        ; MASSERT2( not (nameIsLocalOrFrom this_mod name), ppr name <+> parens doc )
+        }
+  ; initIfaceTcRn $ loadSysInterface doc (nameModule name)
+  }
 
 -- | An 'IfM' function to load the home interface for a wired-in thing,
 -- so that we're sure that we see its instance declarations and rules
@@ -200,7 +203,7 @@ loadInterface doc_str mod from
        ; dflags <- getDOpts
        ; case lookupIfaceByModule dflags hpt (eps_PIT eps) mod of {
            Just iface 
-               -> returnM (Succeeded iface) ;  -- Already loaded
+               -> return (Succeeded iface) ;   -- Already loaded
                        -- The (src_imp == mi_boot iface) test checks that the already-loaded
                        -- interface isn't a boot iface.  This can conceivably happen,
                        -- if an earlier import had a before we got to real imports.   I think.
@@ -228,7 +231,7 @@ loadInterface doc_str mod from
                        -- Not found, so add an empty iface to 
                        -- the EPS map so that we don't look again
                                
-               ; returnM (Failed err) } ;
+               ; return (Failed err) } ;
 
        -- Found and parsed!
            Succeeded (iface, file_path)        -- Sanity check:
@@ -236,7 +239,7 @@ loadInterface doc_str mod from
                  modulePackageId (mi_module iface) == thisPackage dflags,
                                                --   a home-package module...
                  Nothing <- mb_dep             --   that we know nothing about
-               -> returnM (Failed (badDepMsg mod))
+               -> return (Failed (badDepMsg mod))
 
                | otherwise ->
 
@@ -300,7 +303,8 @@ loadInterface doc_str mod from
                                                 fam_inst_env,
              eps_stats        = addEpsInStats (eps_stats eps) 
                                               (length new_eps_decls)
-             (length new_eps_insts) (length new_eps_rules) }
+                                              (length new_eps_insts)
+                                              (length new_eps_rules) }
 
        ; return (Succeeded final_iface)
     }}}}
@@ -418,7 +422,7 @@ loadDecl ignore_prags mod (_version, decl)
                           Nothing    -> 
                             pprPanic "loadDecl" (ppr main_name <+> ppr n $$ ppr (decl))
 
-       ; returnM $ (main_name, thing) : 
+       ; return $ (main_name, thing) :
                       -- uses the invariant that implicit_names and
                       -- implictTyThings are bijective
                       [(n, lookup n) | n <- implicit_names]
@@ -464,19 +468,19 @@ findAndReadIface doc_str mod hi_boot_file
        -- Check for GHC.Prim, and return its static interface
        ; dflags <- getDOpts
        ; if mod == gHC_PRIM
-         then returnM (Succeeded (ghcPrimIface, 
+         then return (Succeeded (ghcPrimIface,
                                   "<built in interface for GHC.Prim>"))
          else do
 
        -- Look for the file
        ; hsc_env <- getTopEnv
-       ; mb_found <- ioToIOEnv (findExactModule hsc_env mod)
+       ; mb_found <- liftIO (findExactModule hsc_env mod)
        ; case mb_found of {
               
              err | notFound err -> do
                { traceIf (ptext SLIT("...not found"))
                ; dflags <- getDOpts
-               ; returnM (Failed (cannotFindInterface dflags 
+               ; return (Failed (cannotFindInterface dflags 
                                        (moduleName mod) err)) } ;
              Found loc mod -> do 
 
@@ -485,18 +489,18 @@ findAndReadIface doc_str mod hi_boot_file
 
         ; if thisPackage dflags == modulePackageId mod
                 && not (isOneShot (ghcMode dflags))
-            then returnM (Failed (homeModError mod loc))
+            then return (Failed (homeModError mod loc))
             else do {
 
         ; traceIf (ptext SLIT("readIFace") <+> text file_path)
        ; read_result <- readIface mod file_path hi_boot_file
        ; case read_result of
-           Failed err -> returnM (Failed (badIfaceFile file_path err))
+           Failed err -> return (Failed (badIfaceFile file_path err))
            Succeeded iface 
                | mi_module iface /= mod ->
                  return (Failed (wrongIfaceModErr iface mod file_path))
                | otherwise ->
-                 returnM (Succeeded (iface, file_path))
+                 return (Succeeded (iface, file_path))
                        -- Don't forget to fill in the package name...
        }}}}
 
@@ -514,7 +518,8 @@ readIface :: Module -> FilePath -> IsBootInterface
 
 readIface wanted_mod file_path is_hi_boot_file
   = do { dflags <- getDOpts
-        ; res <- tryMostM $ readBinIface file_path
+        ; res <- tryMostM $
+                 readBinIface CheckHiWay QuietBinIFaceReading file_path
        ; case res of
            Right iface 
                | wanted_mod == actual_mod -> return (Succeeded iface)
@@ -609,10 +614,10 @@ ifaceStats eps
 -- | Read binary interface, and print it out
 showIface :: HscEnv -> FilePath -> IO ()
 showIface hsc_env filename = do
-   -- skip the version check; we don't want to worry about profiled vs.
+   -- skip the hi way check; we don't want to worry about profiled vs.
    -- non-profiled interfaces, for example.
-   writeIORef v_IgnoreHiWay True
-   iface <- initTcRnIf 's' hsc_env () () $ readBinIface  filename
+   iface <- initTcRnIf 's' hsc_env () () $
+       readBinIface IgnoreHiWay TraceBinIFaceReading filename
    printDump (pprModIface iface)
 \end{code}