ghc-7.0.3: The GHC API

TcRnTypes

Synopsis

Documentation

type TcRnIf a b c = IOEnv (Env a b) cSource

type TcM a = TcRn aSource

type RnM a = TcRn aSource

type IfM lcl a = TcRnIf IfGblEnv lcl aSource

type IfG a = IfM () aSource

type TcRef a = IORef aSource

data Env gbl lcl Source

Constructors

Env 

Fields

env_top :: HscEnv
 
env_us :: !(IORef UniqSupply)
 
env_gbl :: gbl
 
env_lcl :: lcl
 

Instances

data TcGblEnv Source

Constructors

TcGblEnv 

Fields

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

tcg_fix_env :: FixityEnv

Just for things in this module

tcg_field_env :: RecFieldEnv

Just for things in this module

tcg_type_env :: TypeEnv

Global type env for the module we are compiling now. All TyCons and Classes (for this module) end up in here right away, along with their derived constructors, selectors.

(Ids defined in this module start in the local envt, though they move to the global envt during zonking)

tcg_type_env_var :: TcRef TypeEnv
 
tcg_inst_env :: InstEnv

Instance envt for home-package modules; Includes the dfuns in tcg_insts

tcg_fam_inst_env :: FamInstEnv

Ditto for family instances

tcg_exports :: [AvailInfo]

What is exported

tcg_imports :: ImportAvails

Information about what was imported from where, including things bound in this module.

tcg_dus :: DefUses

What is defined in this module and what is used. The latter is used to generate

(a) version tracking; no need to recompile if these things have not changed version stamp

(b) unused-import info

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_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. The reference is implicit rather than explicit, so we have to zap a mutable variable.

tcg_dfun_n :: TcRef OccSet

Allows us to choose unique DFun names.

tcg_rn_exports :: Maybe [Located (IE Name)]
 
tcg_rn_imports :: [LImportDecl Name]
 
tcg_used_rdrnames :: TcRef (Set RdrName)
 
tcg_rn_decls :: Maybe (HsGroup Name)

Renamed decls, maybe. Nothing = Don't retain renamed decls.

tcg_ev_binds :: Bag EvBind
 
tcg_binds :: LHsBinds Id
 
tcg_sigs :: NameSet
 
tcg_imp_specs :: [LTcSpecPrag]
 
tcg_warns :: Warnings
 
tcg_anns :: [Annotation]
 
tcg_insts :: [Instance]
 
tcg_fam_insts :: [FamInst]
 
tcg_rules :: [LRuleDecl Id]
 
tcg_fords :: [LForeignDecl Id]
 
tcg_doc_hdr :: Maybe LHsDocString

Maybe Haddock header docs

tcg_hpc :: AnyHpcUsage

True if any part of the prog uses hpc instrumentation.

tcg_main :: Maybe Name

The Name of the main function, if this module is the main module.

data IfGblEnv Source

Constructors

IfGblEnv 

data ImportAvails Source

ImportAvails summarises what was imported from where, irrespective of whether the imported things are actually used or not. It is used:

  • when processing the export list,
  • when constructing usage info for the interface file,
  • to identify the list of directly imported modules for initialisation purposes and for optimised overlap checking of family instances,
  • when figuring out what things are really unused

Constructors

ImportAvails 

Fields

imp_mods :: ModuleEnv [(ModuleName, Bool, SrcSpan)]

Domain is all directly-imported modules The ModuleName is what the module was imported as, e.g. in import Foo as Bar it is Bar.

The Bool means:

  • True => import was import Foo ()
  • False => import was some other form

Used

(a) to help construct the usage information in the interface file; if we import somethign we need to recompile if the export version changes

(b) to specify what child modules to initialise

We need a full ModuleEnv rather than a ModuleNameEnv here, because we might be importing modules of the same name from different packages. (currently not the case, but might be in the future).

imp_dep_mods :: ModuleNameEnv (ModuleName, 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 :: [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 :: [Module]

Orphan modules below us in the import tree (and maybe including us for imported modules)

imp_finsts :: [Module]

Family instance modules below us in the import tree (and maybe including us for imported modules)

data ArrowCtxt Source

Constructors

NoArrowCtxt 

data EvVarX a Source

Constructors

EvVarX EvVar a 

Instances

data CtLoc orig Source

Constructors

CtLoc orig SrcSpan [ErrCtxt] 

data EqOrigin Source

Constructors

UnifyOrigin 

Instances

pushErrCtxt :: orig -> ErrCtxt -> CtLoc orig -> CtLoc origSource

type TcId = IdSource