[project @ 1999-04-27 17:33:49 by sof]
[ghc-hetmet.git] / ghc / compiler / rename / RnIfaces.lhs
index 0407764..eebe37e 100644 (file)
@@ -11,7 +11,7 @@ module RnIfaces (
        importDecl, recordSlurp,
        getImportVersions, getSlurpedNames, getRnStats, getImportedFixities,
 
-       checkUpToDate, loadHomeInterface,
+       checkUpToDate,
 
        getDeclBinders,
        mkSearchPath
@@ -25,7 +25,7 @@ import CmdLineOpts    ( opt_PruneTyDecls,  opt_PruneInstDecls,
 import HsSyn           ( HsDecl(..), TyClDecl(..), InstDecl(..), IfaceSig(..), 
                          HsType(..), ConDecl(..), IE(..), ConDetails(..), Sig(..),
                          FixitySig(..),
-                         hsDeclName, countTyClDecls, isDataDecl, nonFixitySigs
+                         hsDeclName, countTyClDecls, isDataDecl, isClassOpSig
                        )
 import BasicTypes      ( Version, NewOrData(..) )
 import RdrHsSyn                ( RdrNameHsDecl, RdrNameInstDecl, RdrNameTyClDecl,
@@ -44,12 +44,14 @@ import FiniteMap    ( FiniteMap, sizeFM, emptyFM, delFromFM,
                          fmToList
                        )
 import Name            ( Name {-instance NamedThing-},
-                         nameModule, moduleString, pprModule, isLocallyDefined,
-                         isWiredInName, maybeWiredInTyConName,  pprModule,
-                         maybeWiredInIdName, nameUnique, NamedThing(..)
+                         nameModule, isLocallyDefined,
+                         isWiredInName, maybeWiredInTyConName,
+                         maybeWiredInIdName, nameUnique, NamedThing(..),
+                         pprEncodedFS
                         )
-import OccName         ( Module, mkBootModule, 
-                         moduleIfaceFlavour, bootFlavour, hiFile
+import Module          ( Module, mkBootModule, moduleString, pprModule, 
+                         mkDynamicModule, moduleIfaceFlavour, bootFlavour, hiFile,
+                         moduleUserString, moduleFS, setModuleFlavour
                        )
 import RdrName         ( RdrName, rdrNameOcc )
 import NameSet
@@ -72,7 +74,6 @@ import Outputable
 
 import IO      ( isDoesNotExistError )
 import List    ( nub )
-
 \end{code}
 
 
@@ -163,84 +164,124 @@ count_decls decls
 %*********************************************************
 
 \begin{code}
-loadHomeInterface :: SDoc -> Name -> RnMG Ifaces
+loadHomeInterface :: SDoc -> Name -> RnMG (Module, Ifaces)
 loadHomeInterface doc_str name
   = loadInterface doc_str (nameModule name)
 
-loadInterface :: SDoc -> Module -> RnMG Ifaces
+loadInterface :: SDoc -> Module -> RnMG (Module, Ifaces)
 loadInterface doc_str load_mod
  = getIfacesRn                 `thenRn` \ ifaces ->
    let
-       new_hif              = moduleIfaceFlavour load_mod
-       this_mod             = iMod ifaces
+       hi_boot_wanted       = bootFlavour (moduleIfaceFlavour load_mod)
        mod_map              = iModMap ifaces
        (insts, tycls_names) = iDefInsts ifaces
+       
    in
        -- CHECK WHETHER WE HAVE IT ALREADY
    case lookupFM mod_map load_mod of {
        Just (existing_hif, _, _) 
-               | bootFlavour new_hif || not (bootFlavour existing_hif)
+               | hi_boot_wanted || not (bootFlavour existing_hif)
                ->      -- Already in the cache, and new version is no better than old,
                        -- so don't re-read it
-                   returnRn ifaces ;
+                   returnRn (setModuleFlavour existing_hif load_mod, ifaces) ;
        other ->
 
        -- READ THE MODULE IN
    findAndReadIface doc_str load_mod           `thenRn` \ read_result ->
    case read_result of {
-       -- Check for not found
-       Nothing ->      -- Not found, so add an empty export env to the Ifaces map
+       Nothing | not hi_boot_wanted && load_mod `elem` thinAirModules
+               -> -- Hack alert!  When compiling PrelBase we have to load the
+                  -- decls for packCString# and friends; they are 'thin-air' Ids
+                  -- (see PrelInfo.lhs).  So if we don't find the HiFile we quietly
+                  -- look for a .hi-boot file instead, and use that
+                  --
+                  -- NB this causes multiple "failed" attempts to read PrelPack,
+                  --    which makes curious reading with -dshow-rn-trace, but
+                  --    there's no harm done
+                  loadInterface doc_str (mkBootModule load_mod)
+
+              
+               | otherwise
+               ->      -- Not found, so add an empty export env to the Ifaces map
                        -- so that we don't look again
                   let
                        new_mod_map = addToFM mod_map load_mod (hiFile, 0, [])
                        new_ifaces = ifaces { iModMap = new_mod_map }
                   in
                   setIfacesRn new_ifaces               `thenRn_`
-                  failWithRn new_ifaces (noIfaceErr load_mod) ;
+                  failWithRn (load_mod, new_ifaces) (noIfaceErr load_mod) ;
 
        -- Found and parsed!
-       Just (ParsedIface _ mod_vers usages exports rd_inst_mods rd_decls rd_insts) ->
+       Just (the_mod, ParsedIface mod_vers usages exports rd_inst_mods rd_decls rd_insts) ->
+
 
        -- LOAD IT INTO Ifaces
        -- First set the module
-    setModuleRn load_mod       $
 
        -- NB: *first* we do loadDecl, so that the provenance of all the locally-defined
        ---    names is done correctly (notably, whether this is an .hi file or .hi-boot file).
        --     If we do loadExport first the wrong info gets into the cache (unless we
        --      explicitly tag each export which seems a bit of a bore)
+
+    getModuleRn                `thenRn` \ this_mod ->
+    setModuleRn the_mod  $     -- First set the module name of the module being loaded,
+                               -- so that unqualified occurrences in the interface file
+                               -- get the right qualifer
     foldlRn loadDecl (iDecls ifaces) rd_decls          `thenRn` \ new_decls ->
     foldlRn loadFixDecl (iFixes ifaces) rd_decls       `thenRn` \ new_fixities ->
-    mapRn   loadExport exports                         `thenRn` \ avails_s ->
     foldlRn loadInstDecl insts rd_insts                        `thenRn` \ new_insts ->
+
+    mapRn (loadExport this_mod) exports                        `thenRn` \ avails_s ->
     let
-        mod_details = (new_hif, mod_vers, concat avails_s)
+         -- Notice: the 'flavour' of the loaded Module does not have to 
+         --  be the same as the requested Module.
+        the_mod_hif = moduleIfaceFlavour the_mod
+        mod_details = (the_mod_hif, mod_vers, concat avails_s)
 
                        -- Exclude this module from the "special-inst" modules
         new_inst_mods = iInstMods ifaces `unionLists` (filter (/= this_mod) rd_inst_mods)
 
-        new_ifaces = ifaces { iModMap   = addToFM mod_map load_mod mod_details,
+        new_ifaces = ifaces { iModMap   = addToFM mod_map the_mod mod_details,
                               iDecls    = new_decls,
                               iFixes    = new_fixities,
                               iDefInsts = (new_insts, tycls_names),
                               iInstMods = new_inst_mods  }
     in
     setIfacesRn new_ifaces             `thenRn_`
-    returnRn new_ifaces
+    returnRn (the_mod, new_ifaces)
     }}
 
-loadExport :: ExportItem -> RnMG [AvailInfo]
-loadExport (mod, entities)
-  = mapRn load_entity entities
+loadExport :: Module -> ExportItem -> RnMG [AvailInfo]
+loadExport this_mod (mod, entities)
+  | mod == this_mod = returnRn []
+       -- If the module exports anything defined in this module, just ignore it.
+       -- Reason: otherwise it looks as if there are two local definition sites
+       -- for the thing, and an error gets reported.  Easiest thing is just to
+       -- filter them out up front. This situation only arises if a module
+       -- imports itself, or another module that imported it.  (Necessarily,
+       -- this invoves a loop.)  Consequence: if you say
+       --      module A where
+       --         import B( AType )
+       --         type AType = ...
+       --
+       --      module B( AType ) where
+       --         import {-# SOURCE #-} A( AType )
+       --
+       -- then you'll get a 'B does not export AType' message.  A bit bogus
+       -- but it's a bogus thing to do!
+
+  | otherwise
+  = setModuleFlavourRn mod `thenRn` \ mod' ->
+    mapRn (load_entity mod') entities
   where
-    new_name occ = newImportedGlobalName mod occ
+    new_name mod occ = newImportedGlobalName mod occ
 
-    load_entity (Avail occ)
-      =        new_name occ            `thenRn` \ name ->
+    load_entity mod (Avail occ)
+      =        new_name mod occ        `thenRn` \ name ->
        returnRn (Avail name)
-    load_entity (AvailTC occ occs)
-      =        new_name occ            `thenRn` \ name ->
-        mapRn new_name occs    `thenRn` \ names ->
+    load_entity mod (AvailTC occ occs)
+      =        new_name mod occ              `thenRn` \ name ->
+        mapRn (new_name mod) occs     `thenRn` \ names ->
         returnRn (AvailTC name names)
 
 
@@ -355,7 +396,7 @@ checkUpToDate mod_name
                                    pprModule mod_name])        `thenRn_`
                    returnRn False
 
-       Just (ParsedIface _ _ usages _ _ _ _) 
+       Just (_, ParsedIface _ usages _ _ _ _) 
                ->      -- Found it, so now check it
                    checkModUsage usages
   where
@@ -365,7 +406,7 @@ checkUpToDate mod_name
 checkModUsage [] = returnRn True               -- Yes!  Everything is up to date!
 
 checkModUsage ((mod, old_mod_vers, whats_imported) : rest)
-  = loadInterface doc_str mod          `thenRn` \ ifaces ->
+  = loadInterface doc_str mod          `thenRn` \ (mod, ifaces) ->
     let
        maybe_new_mod_vers        = lookupFM (iModMap ifaces) mod
        Just (_, new_mod_vers, _) = maybe_new_mod_vers
@@ -466,7 +507,7 @@ importDecl (name, loc) mode
 getNonWiredInDecl :: Name -> SrcLoc -> RnMode -> RnMG (Maybe RdrNameHsDecl)
 getNonWiredInDecl needed_name loc mode
   = traceRn doc_str                            `thenRn_`
-    loadHomeInterface doc_str needed_name      `thenRn` \ ifaces ->
+    loadHomeInterface doc_str needed_name      `thenRn` \ (_, ifaces) ->
     case lookupNameEnv (iDecls ifaces) needed_name of
 
        -- Special case for data/newtype type declarations
@@ -608,17 +649,17 @@ get_wired_tycon tycon
 %*********************************************************
 
 \begin{code}
-getInterfaceExports :: Module -> RnMG Avails
+getInterfaceExports :: Module -> RnMG (Module, Avails)
 getInterfaceExports mod
-  = loadInterface doc_str mod  `thenRn` \ ifaces ->
+  = loadInterface doc_str mod  `thenRn` \ (mod, ifaces) ->
     case lookupFM (iModMap ifaces) mod of
        Nothing ->      -- Not there; it must be that the interface file wasn't found;
                        -- the error will have been reported already.
                        -- (Actually loadInterface should put the empty export env in there
                        --  anyway, but this does no harm.)
-                     returnRn []
+                     returnRn (mod, [])
 
-       Just (_, _, avails) -> returnRn avails
+       Just (_, _, avails) -> returnRn (mod, avails)
   where
     doc_str = sep [pprModule mod, ptext SLIT("is directly imported")]
 \end{code}
@@ -650,13 +691,20 @@ getNonWiredDataDecl needed_name
                    version
                    avail@(AvailTC tycon_name _) 
                    ty_decl@(TyData new_or_data context tycon tyvars condecls derivings pragmas src_loc)
-  |  needed_name == tycon_name
-  && opt_PruneTyDecls
+  |  null condecls ||
+       -- HACK ALERT!  If the data type is abstract then it must from a 
+       -- hand-written hi-boot file.  We put it in the deferred pile unconditionally,
+       -- because we don't want to read it in, and then later find a decl for a constructor
+       -- from that type, read the real interface file, and read in the full data type
+       -- decl again!!!  
+
+     (needed_name == tycon_name
+     && opt_PruneTyDecls
         -- don't prune newtypes, as the code generator may
        -- want to peer inside a newtype type constructor
        -- (ClosureInfo.fun_result_ty is the culprit.)
-  && not (new_or_data == NewType)
-  && not (nameUnique needed_name `elem` cCallishTyKeys)                
+     && not (new_or_data == NewType)
+     && not (nameUnique needed_name `elem` cCallishTyKeys))
        -- Hack!  Don't prune these tycons whose constructors
        -- the desugarer must be able to see when desugaring
        -- a CCall.  Ugh!
@@ -717,7 +765,7 @@ getImportedInstDecls :: RnMG [(Module,RdrNameInstDecl)]
 getImportedInstDecls
   =    -- First load any special-instance modules that aren't aready loaded
     getSpecialInstModules                      `thenRn` \ inst_mods ->
-    mapRn load_it inst_mods                    `thenRn_`
+    mapRn_ load_it inst_mods                   `thenRn_`
 
        -- Now we're ready to grab the instance declarations
        -- Find the un-gated ones and return them, 
@@ -761,10 +809,26 @@ getSpecialInstModules
   = getIfacesRn                                                `thenRn` \ ifaces ->
     returnRn (iInstMods ifaces)
 
-getImportedFixities :: RnMG FixityEnv
-getImportedFixities
-  = getIfacesRn                                                `thenRn` \ ifaces ->
+getImportedFixities :: GlobalRdrEnv -> RnMG FixityEnv
+       -- Get all imported fixities
+       -- We first make sure that all the home modules
+       -- of all in-scope variables are loaded.
+getImportedFixities gbl_env
+  = let
+       home_modules = [ nameModule name | names <- rdrEnvElts gbl_env,
+                                          name <- names,
+                                          not (isLocallyDefined name)
+                      ]
+    in
+    mapRn_ load (nub home_modules)     `thenRn_`
+
+       -- Now we can snaffle the fixity env
+    getIfacesRn                                                `thenRn` \ ifaces ->
     returnRn (iFixes ifaces)
+  where
+    load mod = loadInterface doc_str mod
+            where
+              doc_str = ptext SLIT("Need fixities from") <+> ppr mod
 \end{code}
 
 
@@ -932,10 +996,10 @@ getDeclBinders new_name (TyClD (ClassDecl _ cname _ sigs _ _ tname dname src_loc
 
        -- Record the names for the class ops
     let
-       -- ignoring fixity declarations
-       nonfix_sigs = nonFixitySigs sigs
+       -- just want class-op sigs
+       op_sigs = filter isClassOpSig sigs
     in
-    mapRn (getClassOpNames new_name) nonfix_sigs       `thenRn` \ sub_names ->
+    mapRn (getClassOpNames new_name) op_sigs   `thenRn` \ sub_names ->
 
     returnRn (Just (AvailTC class_name (class_name : sub_names)))
 
@@ -993,7 +1057,7 @@ getDeclSysBinders new_name other_decl
 %*********************************************************
 
 \begin{code}
-findAndReadIface :: SDoc -> Module -> RnMG (Maybe ParsedIface)
+findAndReadIface :: SDoc -> Module -> RnMG (Maybe (Module, ParsedIface))
        -- Nothing <=> file not found, or unreadable, or illegible
        -- Just x  <=> successfully found and parsed 
 
@@ -1003,18 +1067,11 @@ findAndReadIface doc_str mod_name
       -- one for 'normal' ones, the other for .hi-boot files,
       -- hence the need to signal which kind we're interested.
     getModuleHiMap from_hi_boot                `thenRn` \ himap ->
-    case (lookupFM himap (moduleString mod_name)) of
+    case (lookupFM himap (moduleUserString mod_name)) of
          -- Found the file
-       Just fpath -> readIface fpath
-        -- Hack alert!  When compiling PrelBase we have to load the
-        -- decls for packCString# and friends; they are 'thin-air' Ids
-        -- (see PrelInfo.lhs).  So if we don't find the HiFile we quietly
-        -- look for a .hi-boot file instead, and use that
-       Nothing |  not from_hi_boot && mod_name `elem` thinAirModules
-              -> findAndReadIface doc_str (mkBootModule mod_name)
-               | otherwise              
-              -> traceRn (ptext SLIT("...failed"))     `thenRn_`
-                 returnRn Nothing
+       Just fpath -> readIface mod_name fpath
+       Nothing    -> traceRn (ptext SLIT("...failed")) `thenRn_`
+                    returnRn Nothing
   where
     hif                 = moduleIfaceFlavour mod_name
     from_hi_boot = bootFlavour hif
@@ -1029,27 +1086,40 @@ findAndReadIface doc_str mod_name
 @readIface@ tries just the one file.
 
 \begin{code}
-readIface :: String -> RnMG (Maybe ParsedIface)        
+readIface :: Module -> (String, Bool) -> RnMG (Maybe (Module, ParsedIface))
        -- Nothing <=> file not found, or unreadable, or illegible
        -- Just x  <=> successfully found and parsed 
-readIface file_path
+readIface requested_mod (file_path, is_dll)
   = ioToRnMG (hGetStringBuffer file_path)       `thenRn` \ read_result ->
     case read_result of
        Right contents    -> 
              case parseIface contents (mkSrcLoc (mkFastString file_path) 1) of
-                 Failed err      -> failWithRn Nothing err 
-                 Succeeded (PIface iface) -> 
-                       if opt_D_show_rn_imports then
-                          putDocRn (hcat[ptext SLIT("Read "), text file_path]) `thenRn_`
-                          returnRn (Just iface)
-                       else
-                          returnRn (Just iface)
-
-        Left err ->
-         if isDoesNotExistError err then
-            returnRn Nothing
-         else
-            failWithRn Nothing (cannaeReadFile file_path err)
+                 Failed err                    -> failWithRn Nothing err 
+                 Succeeded (PIface mod_nm iface) ->
+                           (if mod_nm /=  moduleFS requested_mod then
+                               addWarnRn (hsep [ ptext SLIT("Something is amiss; requested module name")
+                                               , pprModule requested_mod
+                                               , ptext SLIT("differs from name found in the interface file ")
+                                               , pprEncodedFS mod_nm
+                                               ])
+                            else
+                               returnRn ())        `thenRn_`
+                           let
+                            the_mod 
+                              | is_dll    = mkDynamicModule requested_mod
+                              | otherwise = requested_mod
+                           in
+                           if opt_D_show_rn_imports then
+                              putDocRn (hcat[ptext SLIT("Read module "), pprEncodedFS mod_nm,
+                                             ptext SLIT(" from "), text file_path]) `thenRn_`
+                              returnRn (Just (the_mod, iface))
+                           else
+                              returnRn (Just (the_mod, iface))
+
+        Left err
+         | isDoesNotExistError err -> returnRn Nothing
+         | otherwise               -> failWithRn Nothing (cannaeReadFile file_path err)
+
 \end{code}
 
 %*********************************************************
@@ -1069,9 +1139,10 @@ of (directory, suffix) pairs.  For example:
 
 \begin{code}
 mkSearchPath :: Maybe String -> SearchPath
-mkSearchPath Nothing = [(".",".hi")]
-mkSearchPath (Just s)
-  = go s
+mkSearchPath Nothing = [(".",".hi")]  -- ToDo: default should be to look in
+                                     -- the directory the module we're compiling
+                                     -- lives.
+mkSearchPath (Just s) = go s
   where
     go "" = []
     go s  =