X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;ds=sidebyside;f=compiler%2Fmain%2FHscTypes.lhs;h=bc9c9eef8ffeeeb8e44456bb7e027791418ec884;hb=e95ee1f718c6915c478005aad8af81705357d6ab;hp=6b59a5915deed4bb786707579a18790f3ff898c8;hpb=7f1db085b2256e3372feca52d493ca7577413cbe;p=ghc-hetmet.git diff --git a/compiler/main/HscTypes.lhs b/compiler/main/HscTypes.lhs index 6b59a59..bc9c9ee 100644 --- a/compiler/main/HscTypes.lhs +++ b/compiler/main/HscTypes.lhs @@ -54,8 +54,9 @@ module HscTypes ( -- * Interactive context InteractiveContext(..), emptyInteractiveContext, - icPrintUnqual, mkPrintUnqualified, extendInteractiveContext, + icPrintUnqual, extendInteractiveContext, substInteractiveContext, + mkPrintUnqualified, pprModulePrefix, -- * Interfaces ModIface(..), mkIfaceWarnCache, mkIfaceHashCache, mkIfaceFixCache, @@ -116,8 +117,6 @@ import RdrName import Name import NameEnv import NameSet -import OccName ( OccName, OccEnv, lookupOccEnv, mkOccEnv, emptyOccEnv, - extendOccEnv ) import Module import InstEnv ( InstEnv, Instance ) import FamInstEnv ( FamInstEnv, FamInst ) @@ -130,7 +129,7 @@ import Id import Type import Annotations -import Class ( Class, classSelIds, classATs, classTyCon ) +import Class ( Class, classAllSelIds, classATs, classTyCon ) import TyCon import DataCon ( DataCon, dataConImplicitIds, dataConWrapId ) import PrelNames ( gHC_PRIM ) @@ -138,16 +137,15 @@ import Packages hiding ( Version(..) ) import DynFlags ( DynFlags(..), isOneShot, HscTarget (..), dopt, DynFlag(..) ) import DriverPhases ( HscSource(..), isHsBoot, hscSourceString, Phase ) -import BasicTypes ( IPName, Fixity, defaultFixity, WarningTxt(..) ) +import BasicTypes ( IPName, defaultFixity, WarningTxt(..) ) import OptimizationFuel ( OptFuelState ) import IfaceSyn -import FiniteMap ( FiniteMap ) import CoreSyn ( CoreRule ) import Maybes ( orElse, expectJust, catMaybes ) import Outputable import BreakArray import SrcLoc ( SrcSpan, Located(..) ) -import LazyUniqFM ( lookupUFM, eltsUFM, emptyUFM ) +import UniqFM ( lookupUFM, eltsUFM, emptyUFM ) import UniqSupply ( UniqSupply ) import FastString import StringBuffer ( StringBuffer ) @@ -163,6 +161,7 @@ import System.Time ( ClockTime ) import Data.IORef import Data.Array ( Array, array ) import Data.List +import Data.Map (Map) import Control.Monad ( mplus, guard, liftM, when ) import Exception \end{code} @@ -326,6 +325,12 @@ instance ExceptionMonad Ghc where Ghc $ \s -> unGhc act s `gcatch` \e -> unGhc (handle e) s gblock (Ghc m) = Ghc $ \s -> gblock (m s) gunblock (Ghc m) = Ghc $ \s -> gunblock (m s) + gmask f = + Ghc $ \s -> gmask $ \io_restore -> + let + g_restore (Ghc m) = Ghc $ \s -> io_restore (m s) + in + unGhc (f g_restore) s instance WarnLogMonad Ghc where setWarnings warns = Ghc $ \(Session _ wref) -> writeIORef wref warns @@ -358,6 +363,12 @@ instance ExceptionMonad m => ExceptionMonad (GhcT m) where GhcT $ \s -> unGhcT act s `gcatch` \e -> unGhcT (handle e) s gblock (GhcT m) = GhcT $ \s -> gblock (m s) gunblock (GhcT m) = GhcT $ \s -> gunblock (m s) + gmask f = + GhcT $ \s -> gmask $ \io_restore -> + let + g_restore (GhcT m) = GhcT $ \s -> io_restore (m s) + in + unGhcT (f g_restore) s instance MonadIO m => WarnLogMonad (GhcT m) where setWarnings warns = GhcT $ \(Session _ wref) -> liftIO $ writeIORef wref warns @@ -800,14 +811,12 @@ data FindResult -- ^ The requested package was not found | FoundMultiple [PackageId] -- ^ _Error_: both in multiple packages - | PackageHidden PackageId - -- ^ For an explicit source import, the package containing the module is - -- not exposed. - | ModuleHidden PackageId - -- ^ For an explicit source import, the package containing the module is - -- exposed, but the module itself is hidden. - | NotFound [FilePath] (Maybe PackageId) - -- ^ The module was not found, the specified places were searched + | NotFound [FilePath] (Maybe PackageId) [PackageId] [PackageId] + -- ^ The module was not found, including either + -- * the specified places were searched + -- * the package that this module should have been in + -- * list of packages in which the module was hidden, + -- * list of hidden packages containing this module | NotFoundInPackage PackageId -- ^ The module was not found in this package @@ -844,11 +853,10 @@ data ModIface mi_boot :: !IsBootInterface, -- ^ Read from an hi-boot file? mi_deps :: Dependencies, - -- ^ The dependencies of the module, consulted for directly - -- imported modules only - - -- This is consulted for directly-imported modules, - -- but not for anything else (hence lazy) + -- ^ The dependencies of the module. This is + -- consulted for directly-imported modules, but not + -- for anything else (hence lazy) + mi_usages :: [Usage], -- ^ Usages; kept sorted so that it's easy to decide -- whether to write a new iface file (changing usages @@ -982,9 +990,7 @@ data ModGuts mg_insts :: ![Instance], -- ^ Class instances declared in this module mg_fam_insts :: ![FamInst], -- ^ Family instances declared in this module mg_rules :: ![CoreRule], -- ^ Before the core pipeline starts, contains - -- rules declared in this module. After the core - -- pipeline starts, it is changed to contain all - -- known rules for those things imported + -- See Note [Overall plumbing for rules] in Rules.lhs mg_binds :: ![CoreBind], -- ^ Bindings for this module mg_foreign :: !ForeignStubs, -- ^ Foreign exports declared in this module mg_warns :: !Warnings, -- ^ Warnings declared in the module @@ -1131,7 +1137,7 @@ data InteractiveContext ic_toplev_scope :: [Module], -- ^ The context includes the "top-level" scope of -- these modules - ic_exports :: [Module], -- ^ The context includes just the exports of these + ic_exports :: [(Module, Maybe (ImportDecl RdrName))], -- ^ The context includes just the exported parts of these -- modules ic_rn_gbl_env :: GlobalRdrEnv, -- ^ The contexts' cached 'GlobalRdrEnv', built from @@ -1205,6 +1211,8 @@ substInteractiveContext ictxt@InteractiveContext{ic_tmp_ids=ids} subst = %* * %************************************************************************ +Note [Printing original names] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Deciding how to print names is pretty tricky. We are given a name P:M.T, where P is the package name, M is the defining module, and T is the occurrence name, and we have to decide in which form to display @@ -1214,19 +1222,24 @@ Ideally we want to display the name in the form in which it is in scope. However, the name might not be in scope at all, and that's where it gets tricky. Here are the cases: - 1. T uniquely maps to P:M.T ---> "T" - 2. there is an X for which X.T uniquely maps to P:M.T ---> "X.T" - 3. there is no binding for "M.T" ---> "M.T" - 4. otherwise ---> "P:M.T" - -3 and 4 apply when P:M.T is not in scope. In these cases we want to -refer to the name as "M.T", but "M.T" might mean something else in the -current scope (e.g. if there's an "import X as M"), so to avoid -confusion we avoid using "M.T" if there's already a binding for it. - -There's one further subtlety: if the module M cannot be imported -because it is not exposed by any package, then we must refer to it as -"P:M". This is handled by the qual_mod component of PrintUnqualified. + 1. T uniquely maps to P:M.T ---> "T" NameUnqual + 2. There is an X for which X.T + uniquely maps to P:M.T ---> "X.T" NameQual X + 3. There is no binding for "M.T" ---> "M.T" NameNotInScope1 + 4. Otherwise ---> "P:M.T" NameNotInScope2 + +(3) and (4) apply when the entity P:M.T is not in the GlobalRdrEnv at +all. In these cases we still want to refer to the name as "M.T", *but* +"M.T" might mean something else in the current scope (e.g. if there's +an "import X as M"), so to avoid confusion we avoid using "M.T" if +there's already a binding for it. Instead we write P:M.T. + +There's one further subtlety: in case (3), what if there are two +things around, P1:M.T and P2:M.T? Then we don't want to print both of +them as M.T! However only one of the modules P1:M and P2:M can be +exposed (say P2), so we use M.T for that, and P1:M.T for the other one. +This is handled by the qual_mod component of PrintUnqualified, inside +the (ppr mod) of case (3), in Name.pprModulePrefix \begin{code} -- | Creates some functions that work out the best ways to format @@ -1320,7 +1333,7 @@ implicitTyThings (AClass cl) -- are only the family decls; they have no implicit things map ATyCon (classATs cl) ++ -- superclass and operation selectors - map AnId (classSelIds cl) + map AnId (classAllSelIds cl) implicitTyThings (ADataCon dc) = -- For data cons add the worker and (possibly) wrapper @@ -1838,7 +1851,7 @@ data NameCache type OrigNameCache = ModuleEnv (OccEnv Name) -- | Module-local cache of implicit parameter 'OccName's given 'Name's -type OrigIParamCache = FiniteMap (IPName OccName) (IPName Name) +type OrigIParamCache = Map (IPName OccName) (IPName Name) \end{code} @@ -1983,7 +1996,6 @@ on just the OccName easily in a Core pass. \begin{code} -- | Vectorisation information for 'ModGuts', 'ModDetails' and 'ExternalPackageState'. --- All of this information is always tidy, even in ModGuts. data VectInfo = VectInfo { vectInfoVar :: VarEnv (Var , Var ), -- ^ @(f, f_v)@ keyed on @f@