X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Ftypecheck%2FTcRnTypes.lhs;h=33190e798768fc0c01be73acdc82ae3135a8ef79;hb=ff818166a0a06e77becad9e28ed116f3b7f5cc8b;hp=d30a6d6dd7729a1de34e6ca11f752e33de1ed09d;hpb=32836fa7556e79a6f1f98c4019f7daf0400ad4fd;p=ghc-hetmet.git diff --git a/ghc/compiler/typecheck/TcRnTypes.lhs b/ghc/compiler/typecheck/TcRnTypes.lhs index d30a6d6..33190e7 100644 --- a/ghc/compiler/typecheck/TcRnTypes.lhs +++ b/ghc/compiler/typecheck/TcRnTypes.lhs @@ -9,10 +9,10 @@ module TcRnTypes( -- The environment types Env(..), TcGblEnv(..), TcLclEnv(..), - IfGblEnv(..), IfLclEnv(..), + IfGblEnv(..), IfLclEnv(..), -- Ranamer types - EntityUsage, emptyUsages, ErrCtxt, + ErrCtxt, ImportAvails(..), emptyImportAvails, plusImportAvails, plusAvail, pruneAvails, AvailEnv, emptyAvailEnv, unitAvailEnv, plusAvailEnv, @@ -20,7 +20,7 @@ module TcRnTypes( WhereFrom(..), mkModDeps, -- Typechecker types - TcTyThing(..), GadtRefinement, + TcTyThing(..), pprTcTyThingCategory, GadtRefinement, -- Template Haskell ThStage(..), topStage, topSpliceStage, @@ -45,18 +45,18 @@ import HsSyn ( PendingSplice, HsOverLit, LRuleDecl, LForeignDecl, ArithSeqInfo, DictBinds, LHsBinds ) import HscTypes ( FixityEnv, HscEnv, TypeEnv, TyThing, - GenAvailInfo(..), AvailInfo, + GenAvailInfo(..), AvailInfo, HscSource(..), availName, IsBootInterface, Deprecations ) -import Packages ( PackageName ) -import Type ( Type, TvSubstEnv ) +import Packages ( PackageId ) +import Type ( Type, TvSubstEnv, pprParendType, pprTyThingCategory ) import TcType ( TcTyVarSet, TcType, TcTauType, TcThetaType, SkolemInfo, - TcPredType, TcKind, tcCmpPred, tcCmpType, tcCmpTypes ) + TcPredType, TcKind, tcCmpPred, tcCmpType, tcCmpTypes, pprSkolInfo ) import InstEnv ( DFunId, InstEnv ) import IOEnv import RdrName ( GlobalRdrEnv, LocalRdrEnv ) import Name ( Name ) import NameEnv -import NameSet ( NameSet, emptyNameSet, DefUses ) +import NameSet ( NameSet, unionNameSets, DefUses ) import OccName ( OccEnv ) import Var ( Id, TyVar ) import VarEnv ( TidyEnv ) @@ -129,6 +129,9 @@ data Env gbl lcl -- Changes as we move into an expression data TcGblEnv = TcGblEnv { tcg_mod :: Module, -- Module being compiled + tcg_src :: HscSource, -- What kind of module + -- (regular Haskell, hs-boot, ext-core) + tcg_rdr_env :: GlobalRdrEnv, -- Top level envt; used during renaming tcg_default :: Maybe [Type], -- Types used for defaulting -- Nothing => no 'default' decl @@ -150,21 +153,6 @@ data TcGblEnv tcg_inst_env :: InstEnv, -- Instance envt for *home-package* modules -- Includes the dfuns in tcg_insts - tcg_inst_uses :: TcRef NameSet, -- Home-package Dfuns actually used - -- Used to generate version dependencies - -- This records usages, rather like tcg_dus, but it has to - -- be a mutable variable so it can be augmented - -- when we look up an instance. These uses of dfuns are - -- rather like the free variables of the program, but - -- are implicit instead of explicit. - - tcg_th_used :: TcRef Bool, -- True <=> Template Haskell syntax used - -- We need this so that we can generate a dependency on the - -- Template Haskell package, becuase the desugarer is going to - -- emit loads of references to TH symbols. It's rather like - -- tcg_inst_uses; the reference is implicit rather than explicit, - -- so we have to zap a mutable variable. - -- Now a bunch of things about this module that are simply -- accumulated, but never consulted until the end. -- Nevertheless, it's convenient to accumulate them along @@ -180,11 +168,33 @@ data TcGblEnv -- things have not changed version stamp -- (b) unused-import info - tcg_keep :: NameSet, -- Set of names to keep alive, and to expose in the - -- interface file (but not to export to the user). - -- These are typically extra definitions generated from - -- data type declarations which would otherwise be - -- dropped as dead code. + tcg_keep :: TcRef NameSet, -- Locally-defined top-level names to keep alive + -- "Keep alive" means give them an Exported flag, so + -- that the simplifier does not discard them as dead + -- code, and so that they are exposed in the interface file + -- (but not to export to the user). + -- + -- Some things, like dict-fun Ids and default-method Ids are + -- "born" with the Exported flag on, for exactly the above reason, + -- but some we only discover as we go. Specifically: + -- * The to/from functions for generic data types + -- * Top-level variables appearing free in the RHS of an orphan rule + -- * Top-level variables appearing free in a TH bracket + + tcg_inst_uses :: TcRef NameSet, -- Home-package Dfuns actually used + -- Used to generate version dependencies + -- This records usages, rather like tcg_dus, but it has to + -- be a mutable variable so it can be augmented + -- when we look up an instance. These uses of dfuns are + -- rather like the free variables of the program, but + -- are implicit instead of explicit. + + tcg_th_used :: TcRef Bool, -- True <=> Template Haskell syntax used + -- We need this so that we can generate a dependency on the + -- Template Haskell package, becuase the desugarer is going to + -- emit loads of references to TH symbols. It's rather like + -- tcg_inst_uses; the reference is implicit rather than explicit, + -- so we have to zap a mutable variable. -- The next fields accumulate the payload of the module -- The binds, rules and foreign-decl fiels are collected @@ -223,7 +233,14 @@ data IfLclEnv -- The module for the current IfaceDecl -- So if we see f = \x -> x -- it means M.f = \x -> x, where M is the if_mod - if_mod :: ModuleName, + if_mod :: Module, + + -- The field is used only for error reporting + -- if (say) there's a Lint error in it + if_loc :: SDoc, + -- Where the interface came from: + -- .hi file, or GHCi state, or ext core + -- plus which bit is currently being examined if_tv_env :: OccEnv TyVar, -- Nested tyvar bindings if_id_env :: OccEnv Id -- Nested id binding @@ -312,7 +329,21 @@ pass it inwards. -- Template Haskell levels --------------------------- -type ThLevel = Int -- Always >= 0 +type ThLevel = Int + -- Indicates how many levels of brackets we are inside + -- (always >= 0) + -- Incremented when going inside a bracket, + -- decremented when going inside a splice + +impLevel, topLevel :: ThLevel +topLevel = 1 -- Things defined at top level of this module +impLevel = 0 -- Imported things; they can be used inside a top level splice +-- +-- For example: +-- f = ... +-- g1 = $(map ...) is OK +-- g2 = $(f ...) is not OK; because we havn't compiled f yet + data ThStage = Comp -- Ordinary compiling, at level topLevel @@ -325,16 +356,6 @@ topStage = Comp topSpliceStage = Splice (topLevel - 1) -- Stage for the body of a top-level splice -impLevel, topLevel :: ThLevel -topLevel = 1 -- Things defined at top level of this module -impLevel = 0 -- Imported things; they can be used inside a top level splice --- --- For example: --- f = ... --- g1 = $(map ...) is OK --- g2 = $(f ...) is not OK; because we havn't compiled f yet - - --------------------------- -- Arrow-notation stages --------------------------- @@ -375,16 +396,30 @@ topArrowCtxt = ArrCtxt { proc_level = topProcLevel, proc_banned = [] } data TcTyThing = AGlobal TyThing -- Used only in the return type of a lookup + | ATcId TcId ThLevel ProcLevel -- Ids defined in this module; may not be fully zonked - | ATyVar TyVar -- Type variables + + | ATyVar Name TcType -- Type variables; tv -> type. It can't just be a TyVar + -- that is mutated to point to the type it is bound to, + -- because that would make it a wobbly type, and we + -- want pattern-bound lexically-scoped type variables to + -- be able to stand for rigid types + | AThing TcKind -- Used temporarily, during kind checking, for the -- tycons and clases in this recursive group instance Outputable TcTyThing where -- Debugging only - ppr (AGlobal g) = text "AGlobal" <+> ppr g - ppr (ATcId g tl pl) = text "ATcId" <+> ppr g <+> ppr tl <+> ppr pl - ppr (ATyVar t) = text "ATyVar" <+> ppr t + ppr (AGlobal g) = ppr g + ppr (ATcId g tl pl) = text "Identifier" <> + ifPprDebug (brackets (ppr g <> comma <> ppr tl <> comma <> ppr pl)) + ppr (ATyVar tv ty) = text "Type variable" <+> quotes (ppr tv) <+> pprParendType ty ppr (AThing k) = text "AThing" <+> ppr k + +pprTcTyThingCategory :: TcTyThing -> SDoc +pprTcTyThingCategory (AGlobal thing) = pprTyThingCategory thing +pprTcTyThingCategory (ATyVar _ _) = ptext SLIT("Type variable") +pprTcTyThingCategory (ATcId _ _ _) = ptext SLIT("Local identifier") +pprTcTyThingCategory (AThing _) = ptext SLIT("Kinded thing") \end{code} \begin{code} @@ -397,32 +432,6 @@ type ErrCtxt = [TidyEnv -> TcM (TidyEnv, Message)] %************************************************************************ %* * - EntityUsage -%* * -%************************************************************************ - -EntityUsage tells what things are actually need in order to compile this -module. It is used for generating the usage-version field of the ModIface. - -Note that we do not record version info for entities from -other (non-home) packages. If the package changes, GHC doesn't help. - -\begin{code} -type EntityUsage = NameSet - -- The Names are all the (a) home-package - -- (b) "big" (i.e. no data cons, class ops) - -- (c) non-locally-defined - -- (d) non-wired-in - -- names that have been slurped in so far. - -- This is used to generate the "usage" information for this module. - -emptyUsages :: EntityUsage -emptyUsages = emptyNameSet -\end{code} - - -%************************************************************************ -%* * Operations over ImportAvails %* * %************************************************************************ @@ -438,27 +447,20 @@ It is used * when processing the export list \begin{code} data ImportAvails = ImportAvails { - imp_env :: AvailEnv, - -- All the things that are available from the import - -- Its domain is all the "main" things; - -- i.e. *excluding* class ops and constructors - -- (which appear inside their parent AvailTC) - - imp_qual :: ModuleEnv AvailEnv, - -- Used to figure out "module M" export specifiers + imp_env :: ModuleEnv NameSet, + -- All the things imported, classified by + -- the *module qualifier* for its import + -- e.g. import List as Foo + -- would add a binding Foo |-> ...stuff from List... + -- to imp_env. + -- + -- We need to classify them like this so that we can figure out + -- "module M" export specifiers in an export list -- (see 1.4 Report Section 5.1.1). Ultimately, we want to find -- everything that is unambiguously in scope as 'M.x' -- and where plain 'x' is (perhaps ambiguously) in scope. -- So the starting point is all things that are in scope as 'M.x', -- which is what this field tells us. - -- - -- Domain is the *module qualifier* for imports. - -- e.g. import List as Foo - -- would add a binding Foo |-> ...stuff from List... - -- to imp_qual. - -- We keep the stuff as an AvailEnv so that it's easy to - -- combine stuff coming from different (unqualified) - -- imports of the same module imp_mods :: ModuleEnv (Module, Maybe Bool, SrcSpan), -- Domain is all directly-imported modules @@ -478,33 +480,33 @@ data ImportAvails -- need to recompile if the module version changes -- (b) to specify what child modules to initialise - imp_dep_mods :: ModuleEnv (ModuleName, IsBootInterface), + imp_dep_mods :: ModuleEnv (Module, IsBootInterface), -- Home-package modules needed by the module being compiled -- - -- It doesn't matter whether any of these dependencies are actually - -- *used* when compiling the module; they are listed if they are below - -- it at all. For example, suppose M imports A which imports X. Then - -- compiling M might not need to consult X.hi, but X is still listed - -- in M's dependencies. - - imp_dep_pkgs :: [PackageName], + -- It doesn't matter whether any of these dependencies + -- are actually *used* when compiling the module; they + -- are listed if they are below it at all. For + -- example, suppose M imports A which imports X. Then + -- compiling M might not need to consult X.hi, but X + -- is still listed in M's dependencies. + + imp_dep_pkgs :: [PackageId], -- Packages needed by the module being compiled, whether -- directly, or via other modules in this package, or via -- modules imported from other packages. - imp_orphs :: [ModuleName] + imp_orphs :: [Module] -- Orphan modules below us in the import tree } -mkModDeps :: [(ModuleName, IsBootInterface)] - -> ModuleEnv (ModuleName, IsBootInterface) +mkModDeps :: [(Module, IsBootInterface)] + -> ModuleEnv (Module, IsBootInterface) mkModDeps deps = foldl add emptyModuleEnv deps where - add env elt@(m,_) = extendModuleEnvByName env m elt + add env elt@(m,_) = extendModuleEnv env m elt emptyImportAvails :: ImportAvails -emptyImportAvails = ImportAvails { imp_env = emptyAvailEnv, - imp_qual = emptyModuleEnv, +emptyImportAvails = ImportAvails { imp_env = emptyModuleEnv, imp_mods = emptyModuleEnv, imp_dep_mods = emptyModuleEnv, imp_dep_pkgs = [], @@ -512,12 +514,11 @@ emptyImportAvails = ImportAvails { imp_env = emptyAvailEnv, plusImportAvails :: ImportAvails -> ImportAvails -> ImportAvails plusImportAvails - (ImportAvails { imp_env = env1, imp_qual = unqual1, imp_mods = mods1, + (ImportAvails { imp_env = env1, imp_mods = mods1, imp_dep_mods = dmods1, imp_dep_pkgs = dpkgs1, imp_orphs = orphs1 }) - (ImportAvails { imp_env = env2, imp_qual = unqual2, imp_mods = mods2, + (ImportAvails { imp_env = env2, imp_mods = mods2, imp_dep_mods = dmods2, imp_dep_pkgs = dpkgs2, imp_orphs = orphs2 }) - = ImportAvails { imp_env = env1 `plusAvailEnv` env2, - imp_qual = plusModuleEnv_C plusAvailEnv unqual1 unqual2, + = ImportAvails { imp_env = plusModuleEnv_C unionNameSets env1 env2, imp_mods = mods1 `plusModuleEnv` mods2, imp_dep_mods = plusModuleEnv_C plus_mod_dep dmods1 dmods2, imp_dep_pkgs = dpkgs1 `unionLists` dpkgs2, @@ -778,8 +779,6 @@ data InstOrigin \begin{code} pprInstLoc :: InstLoc -> SDoc -pprInstLoc (InstLoc (SigOrigin info) locn _) - = text "arising from" <+> ppr info -- I don't think this happens much, if at all pprInstLoc (InstLoc orig locn _) = hsep [text "arising from", pp_orig orig, text "at", ppr locn] where @@ -790,11 +789,11 @@ pprInstLoc (InstLoc orig locn _) pp_orig (LiteralOrigin lit) = hsep [ptext SLIT("the literal"), quotes (ppr lit)] pp_orig (ArithSeqOrigin seq) = hsep [ptext SLIT("the arithmetic sequence"), quotes (ppr seq)] pp_orig (PArrSeqOrigin seq) = hsep [ptext SLIT("the parallel array sequence"), quotes (ppr seq)] - pp_orig InstSigOrigin = ptext SLIT("instantiating a type signature") - pp_orig InstScOrigin = ptext SLIT("the superclasses of an instance declaration") + pp_orig InstSigOrigin = ptext SLIT("instantiating a type signature") + pp_orig InstScOrigin = ptext SLIT("the superclasses of an instance declaration") pp_orig DerivOrigin = ptext SLIT("the 'deriving' clause of a data type declaration") pp_orig DefaultOrigin = ptext SLIT("a 'default' declaration") - pp_orig DoOrigin = ptext SLIT("a do statement") - pp_orig ProcOrigin = ptext SLIT("a proc expression") - pp_orig (SigOrigin info) = ppr info + pp_orig DoOrigin = ptext SLIT("a do statement") + pp_orig ProcOrigin = ptext SLIT("a proc expression") + pp_orig (SigOrigin info) = pprSkolInfo info \end{code}