Make package ndp wired-in
[ghc-hetmet.git] / compiler / main / HscTypes.lhs
index 956d10d..b353caa 100644 (file)
@@ -78,8 +78,8 @@ import {-# SOURCE #-}  InteractiveEval ( Resume )
 #endif
 
 import RdrName         ( GlobalRdrEnv, emptyGlobalRdrEnv, GlobalRdrElt(..), 
-                          unQualOK, ImpDeclSpec(..), Provenance(..),
-                          ImportSpec(..), lookupGlobalRdrEnv )
+                          mkRdrUnqual, ImpDeclSpec(..), Provenance(..),
+                          ImportSpec(..), lookupGlobalRdrEnv, lookupGRE_RdrName )
 import Name            ( Name, NamedThing, getName, nameOccName, nameModule )
 import NameEnv
 import NameSet 
@@ -115,7 +115,6 @@ import SrcLoc               ( SrcSpan, Located )
 import UniqFM          ( lookupUFM, eltsUFM, emptyUFM )
 import UniqSupply      ( UniqSupply )
 import FastString      ( FastString )
-
 import StringBuffer    ( StringBuffer )
 
 import System.Time     ( ClockTime )
@@ -701,19 +700,28 @@ extendInteractiveContext ictxt ids tyvars
 mkPrintUnqualified :: GlobalRdrEnv -> PrintUnqualified
 mkPrintUnqualified env = (qual_name, qual_mod)
   where
-  qual_name mod occ
-        | null gres = Just (moduleName mod)
+  qual_name mod occ    -- The (mod,occ) pair is the original name of the thing
+        | [gre] <- unqual_gres, right_name gre = Nothing
+               -- If there's a unique entity that's in scope unqualified with 'occ'
+               -- AND that entity is the right one, then we can use the unqualified name
+
+        | [gre] <- qual_gres = Just (get_qual_mod (gre_prov gre))
+
+        | null qual_gres = Just (moduleName mod)
                 -- it isn't in scope at all, this probably shouldn't happen,
                 -- but we'll qualify it by the original module anyway.
-        | any unQualOK gres = Nothing
-        | (Imported is : _) <- map gre_prov gres, (idecl : _) <- is
-          = Just (is_as (is_decl idecl))
-        | otherwise = panic "mkPrintUnqualified" 
+
+       | otherwise = panic "mkPrintUnqualified"
       where
-        gres  = [ gre | gre <- lookupGlobalRdrEnv env occ,
-                       nameModule (gre_name gre) == mod ]
+       right_name gre = nameModule (gre_name gre) == mod
+
+        unqual_gres = lookupGRE_RdrName (mkRdrUnqual occ) env
+        qual_gres   = filter right_name (lookupGlobalRdrEnv env occ)
+
+       get_qual_mod LocalDef      = moduleName mod
+       get_qual_mod (Imported is) = ASSERT( not (null is) ) is_as (is_decl (head is))
 
-  qual_mod mod = Nothing       -- For now...
+  qual_mod mod = Nothing       -- For now, we never qualify module names with their packages
 \end{code}
 
 
@@ -1255,28 +1263,42 @@ on just the OccName easily in a Core pass.
 -- ModGuts/ModDetails/EPS version
 data VectInfo      
   = VectInfo {
-      vectInfoCCVar :: VarEnv (Var, Var)        -- (f, f_CC) keyed on f
-                                                -- always tidy, even in ModGuts
+      vectInfoCCVar     :: VarEnv  (Var    , Var  ),   -- (f, f_CC) keyed on f
+      vectInfoCCTyCon   :: NameEnv (TyCon  , TyCon),   -- (T, T_CC) keyed on T
+      vectInfoCCDataCon :: NameEnv (DataCon, DataCon), -- (C, C_CC) keyed on C
+      vectInfoCCIso     :: NameEnv (TyCon  , Var)      -- (T, isoT) keyed on T
     }
+    -- all of this is always tidy, even in ModGuts
 
 -- ModIface version
 data IfaceVectInfo 
   = IfaceVectInfo {
-      ifaceVectInfoCCVar :: [Name]              -- all variables in here have
-                                                -- a closure-converted variant
-                                                -- the name of the CC'ed variant
-                                                -- is determined by `mkCloOcc'
+      ifaceVectInfoCCVar        :: [Name],
+        -- all variables in here have a closure-converted variant;
+        -- the name of the CC'ed variant is determined by `mkCloOcc'
+      ifaceVectInfoCCTyCon      :: [Name],
+        -- all tycons in here have a closure-converted variant;
+        -- the name of the CC'ed variant and those of its data constructors are
+        -- determined by `mkCloTyConOcc' and `mkCloDataConOcc'; the names of
+        -- the isomorphisms is determined by `mkCloIsoOcc'
+      ifaceVectInfoCCTyConReuse :: [Name]              
+        -- the closure-converted form of all the tycons in here coincids with
+        -- the unconverted from; the names of the isomorphisms is determined
+        -- by `mkCloIsoOcc'
     }
 
 noVectInfo :: VectInfo
-noVectInfo = VectInfo emptyVarEnv
+noVectInfo = VectInfo emptyVarEnv emptyNameEnv emptyNameEnv emptyNameEnv
 
 plusVectInfo :: VectInfo -> VectInfo -> VectInfo
 plusVectInfo vi1 vi2 = 
-  VectInfo (vectInfoCCVar vi1 `plusVarEnv` vectInfoCCVar vi2)
+  VectInfo (vectInfoCCVar     vi1 `plusVarEnv`  vectInfoCCVar     vi2)
+           (vectInfoCCTyCon   vi1 `plusNameEnv` vectInfoCCTyCon   vi2)
+           (vectInfoCCDataCon vi1 `plusNameEnv` vectInfoCCDataCon vi2)
+           (vectInfoCCIso     vi1 `plusNameEnv` vectInfoCCIso     vi2)
 
 noIfaceVectInfo :: IfaceVectInfo
-noIfaceVectInfo = IfaceVectInfo []
+noIfaceVectInfo = IfaceVectInfo [] [] []
 \end{code}
 
 %************************************************************************