X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Fmain%2FHscTypes.lhs;h=a40b0065972a82e18179d4c0e82e3a950883c2da;hb=8f624641f3eb421154ab170ce5aeaca75b90d2f0;hp=7cb86bfb42be033fbb0e930febac267a98f57222;hpb=98688c6e8fd33f31c51218cf93cbf03fe3a5e73d;p=ghc-hetmet.git diff --git a/ghc/compiler/main/HscTypes.lhs b/ghc/compiler/main/HscTypes.lhs index 7cb86bf..a40b006 100644 --- a/ghc/compiler/main/HscTypes.lhs +++ b/ghc/compiler/main/HscTypes.lhs @@ -28,7 +28,7 @@ module HscTypes ( FixityEnv, FixItem(..), lookupFixity, emptyFixityEnv, - implicitTyThings, isImplicitTyThing, + implicitTyThings, TyThing(..), tyThingClass, tyThingTyCon, tyThingDataCon, tyThingId, TypeEnv, lookupType, mkTypeEnv, emptyTypeEnv, @@ -39,7 +39,7 @@ module HscTypes ( Dependencies(..), noDependencies, Pool(..), emptyPool, DeclPool, InstPool, Gated, - RulePool, addRuleToPool, + RulePool, RulePoolContents, addRuleToPool, NameCache(..), OrigNameCache, OrigIParamCache, Avails, availsToNameSet, availName, availNames, GenAvailInfo(..), AvailInfo, RdrAvailInfo, @@ -74,7 +74,7 @@ import Module import InstEnv ( InstEnv, DFunId ) import Rules ( RuleBase ) import CoreSyn ( CoreBind ) -import Id ( Id, isImplicitId ) +import Id ( Id ) import Type ( TyThing(..) ) import Class ( Class, classSelIds, classTyCon ) @@ -93,7 +93,7 @@ import CoreSyn ( IdCoreRule ) import PrelNames ( isBuiltInSyntaxName ) import Maybes ( orElse ) import Outputable -import SrcLoc ( SrcLoc ) +import SrcLoc ( SrcSpan ) import UniqSupply ( UniqSupply ) import Maybe ( fromJust ) import FastString ( FastString ) @@ -139,7 +139,7 @@ hscEPS hsc_env = readIORef (hsc_EPS hsc_env) The GhciMode is self-explanatory: \begin{code} -data GhciMode = Batch | Interactive | OneShot +data GhciMode = Batch | Interactive | OneShot | IDE deriving Eq \end{code} @@ -275,7 +275,7 @@ data ModDetails data ModGuts = ModGuts { mg_module :: !Module, - mg_exports :: !Avails, -- What it exports + mg_exports :: !NameSet, -- What it exports mg_deps :: !Dependencies, -- What is below it, directly or otherwise mg_dir_imps :: ![Module], -- Directly-imported modules; used to -- generate initialisation code @@ -431,12 +431,6 @@ unQualInScope env %************************************************************************ \begin{code} -isImplicitTyThing :: TyThing -> Bool -isImplicitTyThing (ADataCon dc) = True -isImplicitTyThing (AnId id) = isImplicitId id -isImplicitTyThing (ATyCon tc) = isClassTyCon tc -isImplicitTyThing other = False - implicitTyThings :: TyThing -> [TyThing] implicitTyThings (AnId id) = [] @@ -629,7 +623,7 @@ emptyIfaceFixCache n = defaultFixity type FixityEnv = NameEnv FixItem -- We keep the OccName in the range so that we can generate an interface from it -data FixItem = FixItem OccName Fixity SrcLoc +data FixItem = FixItem OccName Fixity SrcSpan instance Outputable FixItem where ppr (FixItem occ fix loc) = ppr fix <+> ppr occ <+> parens (ppr loc) @@ -664,6 +658,7 @@ type IsBootInterface = Bool -- in the import hierarchy. See TcRnTypes.ImportAvails for details. -- -- Invariant: the dependencies of a module M never includes M +-- Invariant: the lists are unordered, with no duplicates data Dependencies = Deps { dep_mods :: [(ModuleName,IsBootInterface)], -- Home-package module dependencies dep_pkgs :: [PackageName], -- External package dependencies @@ -739,14 +734,7 @@ data ExternalPackageState -- available before this instance decl is needed. eps_rules :: !RulePool - -- Rules move from here to eps_rule_base when - -- all their LHS free vars are in the eps_PTE - -- To maintain this invariant, we need to check the pool - -- a) when adding to the rule pool by loading an interface - -- (some of the new rules may alrady have all their - -- gates in the eps_PTE) - -- b) when extending the eps_PTE when we load a decl - -- from the eps_decls pool + -- The as-yet un-slurped rules } \end{code} @@ -777,36 +765,35 @@ type OrigIParamCache = FiniteMap (IPName OccName) (IPName Name) \end{code} \begin{code} -data Pool p = Pool (NameEnv p) -- The pool itself, indexed by some primary key +data Pool p = Pool p -- The pool itself Int -- Number of decls slurped into the map Int -- Number of decls slurped out of the map -emptyPool = Pool emptyNameEnv 0 0 +emptyPool p = Pool p 0 0 instance Outputable p => Outputable (Pool p) where ppr (Pool p n_in n_out) -- Debug printing only = vcat [ptext SLIT("Pool") <+> int n_in <+> int n_out, nest 2 (ppr p)] -type DeclPool = Pool IfaceDecl +type DeclPool = Pool (NameEnv IfaceDecl) -- Keyed by the "main thing" of the decl ------------------------- type Gated d = ([Name], (ModuleName, d)) -- The [Name] 'gate' the declaration -- ModuleName records which iface file this -- decl came from -type RulePool = Pool [Gated IfaceRule] +type RulePool = Pool RulePoolContents +type RulePoolContents = [Gated IfaceRule] -addRuleToPool :: NameEnv [Gated IfaceRule] +addRuleToPool :: RulePoolContents -> (ModuleName, IfaceRule) -> [Name] -- Free vars of rule; always non-empty - -> NameEnv [Gated IfaceRule] -addRuleToPool rules rule (fv:fvs) = extendNameEnv_C combine rules fv [(fvs,rule)] - where - combine old _ = (fvs,rule) : old + -> RulePoolContents +addRuleToPool rules rule fvs = (fvs,rule) : rules ------------------------- -type InstPool = Pool [Gated IfaceInst] +type InstPool = Pool (NameEnv [Gated IfaceInst]) -- The key of the Pool is the Class -- The Names are the TyCons in the instance head -- For example, suppose this is in an interface file