ghc-7.10.3: The GHC API

Safe HaskellNone
LanguageHaskell2010

TcRnTypes

Synopsis

Documentation

type TcRnIf a b = IOEnv (Env a b) Source

type TcM = TcRn Source

Historical "type-checking monad" (now it's just TcRn).

type RnM = TcRn Source

Historical "renaming monad" (now it's just TcRn).

type IfM lcl = TcRnIf IfGblEnv lcl Source

type IfG = IfM () Source

type TcRef a = IORef a Source

Type alias for IORef; the convention is we'll use this for mutable bits of data in TcGblEnv which are updated during typechecking and returned at the end.

data Env gbl lcl Source

Constructors

Env 

Fields

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

Instances

ContainsModule gbl => ContainsModule (Env gbl lcl) 
ContainsDynFlags (Env gbl lcl) 

data TcGblEnv Source

TcGblEnv describes the top-level of the module at the point at which the typechecker is finished work. It is this structure that is handed on to the desugarer For state that needs to be updated during the typechecking phase and returned at end, use a TcRef (= IORef).

Constructors

TcGblEnv 

Fields

tcg_mod :: Module

Module being compiled

tcg_src :: HscSource

What kind of module (regular Haskell, hs-boot, ext-core)

tcg_sig_of :: Maybe Module

Are we being compiled as a signature of an implementation?

tcg_impl_rdr_env :: Maybe GlobalRdrEnv

Environment used only during -sig-of for resolving top level bindings. See Note [Signature parameters in TcGblEnv and DynFlags]

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 See Note [The interactive package] in HscTypes

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)

NB: for what "things in this module" means, see Note [The interactive package] in HscTypes

tcg_type_env_var :: TcRef TypeEnv
 
tcg_inst_env :: InstEnv

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

tcg_fam_inst_env :: FamInstEnv

Ditto for family instances

tcg_ann_env :: AnnEnv

And for annotations

tcg_visible_orphan_mods :: ModuleSet

The set of orphan modules which transitively reachable from direct imports. We use this to figure out if an orphan instance in the global InstEnv should be considered visible. See Note [Instance lookup and orphan instances] in InstEnv

tcg_exports :: [AvailInfo]

What is exported

tcg_imports :: ImportAvails

Information about what was imported from where, including things bound in this module. Also store Safe Haskell info here about transative trusted packaage requirements.

tcg_dus :: DefUses

What is defined in this module and what is used.

tcg_used_rdrnames :: TcRef (Set RdrName)
 
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, because 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_th_splice_used :: TcRef Bool

True = A Template Haskell splice was used.

Splices disable recompilation avoidance (see #481)

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_rn_decls :: Maybe (HsGroup Name)

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

tcg_dependent_files :: TcRef [FilePath]

dependencies from addDependentFile

tcg_th_topdecls :: TcRef [LHsDecl RdrName]

Top-level declarations from addTopDecls

tcg_th_topnames :: TcRef NameSet

Exact names bound in top-level declarations in tcg_th_topdecls

tcg_th_modfinalizers :: TcRef [Q ()]

Template Haskell module finalizers

tcg_th_state :: TcRef (Map TypeRep Dynamic)

Template Haskell state

tcg_ev_binds :: Bag EvBind
 
tcg_binds :: LHsBinds Id
 
tcg_sigs :: NameSet
 
tcg_imp_specs :: [LTcSpecPrag]
 
tcg_warns :: Warnings
 
tcg_anns :: [Annotation]
 
tcg_tcs :: [TyCon]
 
tcg_insts :: [ClsInst]
 
tcg_fam_insts :: [FamInst]
 
tcg_rules :: [LRuleDecl Id]
 
tcg_fords :: [LForeignDecl Id]
 
tcg_vects :: [LVectDecl Id]
 
tcg_patsyns :: [PatSyn]
 
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.

tcg_safeInfer :: TcRef Bool
 
tcg_tc_plugins :: [TcPluginSolver]

A list of user-defined plugins for the constraint solver.

tcg_static_wc :: TcRef WantedConstraints

Wanted constraints of static forms.

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 :: ImportedMods

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 something 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 :: [PackageKey]

Packages needed by the module being compiled, whether directly, or via other modules in this package, or via modules imported from other packages.

imp_trust_pkgs :: [PackageKey]

This is strictly a subset of imp_dep_pkgs and records the packages the current module needs to trust for Safe Haskell compilation to succeed. A package is required to be trusted if we are dependent on a trustworthy module in that package. While perhaps making imp_dep_pkgs a tuple of (PackageKey, Bool) where True for the bool indicates the package is required to be trusted is the more logical design, doing so complicates a lot of code not concerned with Safe Haskell. See Note [RnNames . Tracking Trust Transitively]

imp_trust_own_pkg :: Bool

Do we require that our own package is trusted? This is to handle efficiently the case where a Safe module imports a Trustworthy module that resides in the same package as it. See Note [RnNames . Trust Own Package]

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)

plusImportAvails :: ImportAvails -> ImportAvails -> ImportAvails Source

Union two ImportAvails

This function is a key part of Import handling, basically for each import we create a separate ImportAvails structure and then union them all together with this function.

data DsLclEnv Source

Constructors

DsLclEnv 

data PArrBuiltin Source

Constructors

PArrBuiltin 

Fields

lengthPVar :: Var

lengthP

replicatePVar :: Var

replicateP

singletonPVar :: Var

singletonP

mapPVar :: Var

mapP

filterPVar :: Var

filterP

zipPVar :: Var

zipP

crossMapPVar :: Var

crossMapP

indexPVar :: Var

(!:)

emptyPVar :: Var

emptyP

appPVar :: Var

(+:+)

enumFromToPVar :: Var

enumFromToP

enumFromThenToPVar :: Var

enumFromThenToP

data DsMetaVal Source

Constructors

DsBound Id 
DsSplice (HsExpr Id) 

type Xi = Type Source

type Cts = Bag Ct Source

ctFlavour :: Ct -> CtFlavour Source

Get the flavour of the given Ct

ctEqRel :: Ct -> EqRel Source

Get the equality relation for the given Ct

ctEvEqRel :: CtEvidence -> EqRel Source

Get the equality relation relevant for a CtEvidence

ctEvCheckDepth :: Class -> CtLoc -> CtEvidence -> Bool Source

Checks whether the evidence can be used to solve a goal with the given minimum depth See Note [Preventing recursive dictionaries]

ctEvRole :: CtEvidence -> Role Source

Get the role relevant for a CtEvidence

data TcPlugin Source

Constructors

forall s . TcPlugin 

Fields

tcPluginInit :: TcPluginM s

Initialize plugin, when entering type-checker.

tcPluginSolve :: s -> TcPluginSolver

Solve some constraints. TODO: WRITE MORE DETAILS ON HOW THIS WORKS.

tcPluginStop :: s -> TcPluginM ()

Clean up after the plugin, when exiting the type-checker.

data TcPluginResult Source

Constructors

TcPluginContradiction [Ct]

The plugin found a contradiction. The returned constraints are removed from the inert set, and recorded as insoluable.

TcPluginOk [(EvTerm, Ct)] [Ct]

The first field is for constraints that were solved. These are removed from the inert set, and the evidence for them is recorded. The second field contains new work, that should be processed by the constraint solver.

unsafeTcPluginTcM :: TcM a -> TcPluginM a Source

This function provides an escape for direct access to the TcM monad. It should not be used lightly, and the provided TcPluginM API should be favoured instead.

type TcId = Id Source

data HoleSort Source

Used to indicate which sort of hole we have.

Constructors

ExprHole

A hole in an expression (TypedHoles)

TypeHole

A hole in a type (PartialTypeSignatures)