ghc-8.0.0.20160204: 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

Instances

ContainsModule gbl => ContainsModule (Env gbl lcl) 

Methods

extractModule :: Env gbl lcl -> Module Source

ContainsDynFlags (Env gbl lcl) 

Methods

extractDynFlags :: Env gbl lcl -> DynFlags Source

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

data IfGblEnv Source

Constructors

IfGblEnv 

data FrontendResult Source

FrontendResult describes the result of running the frontend of a Haskell module. Usually, you'll get a FrontendTypecheck, since running the frontend involves typechecking a program, but for an hs-boot merge you'll just get a ModIface, since no actual typechecking occurred.

This data type really should be in HscTypes, but it needs to have a TcGblEnv which is only defined here.

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

    See the documentaion on ImportedModsVal in HscTypes for the meaning of the fields.

    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 :: [UnitId]

    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 :: [UnitId]

    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 (UnitId, 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 TcTyThing Source

A typecheckable thing available in a local context. Could be AGlobal TyThing, but also lexically scoped variables, etc. See TcEnv for how to retrieve a TyThing given a Name.

data PArrBuiltin Source

Constructors

PArrBuiltin 

Fields

data DsMetaVal Source

Constructors

DsBound Id 
DsSplice (HsExpr Id) 

data SpliceType Source

Constructors

Typed 
Untyped 

noCompleteSig :: Maybe TcSigInfo -> Bool Source

No signature or a partial signature

type Xi = Type Source

type Cts = Bag Ct Source

superClassesMightHelp :: Ct -> Bool Source

True if taking superclasses of givens, or of wanteds (to perhaps expose more equalities or functional dependencies) might help to solve this constraint. See Note [When superclases help]

isCallStackDict :: Class -> [Type] -> Maybe FastString Source

Are we looking at an Implicit CallStack (i.e. IP "name" CallStack)?

If so, returns Just "name".

getUserTypeErrorMsg :: Ct -> Maybe Type Source

The following constraints are considered to be a custom type error: 1. TypeError msg a b c 2. TypeError msg a b c ~ Something (and the other way around) 4. C (TypeError msg a b c) (for any parameter of class constraint)

ctFlavour :: Ct -> CtFlavour Source

Get the flavour of the given Ct

ctEqRel :: Ct -> EqRel Source

Get the equality relation for the given Ct

mkTcEqPredLikeEv :: CtEvidence -> TcType -> TcType -> TcType Source

Makes a new equality predicate with the same role as the given evidence.

ctEvEqRel :: CtEvidence -> EqRel Source

Get the equality relation relevant for a CtEvidence

tyCoVarsOfCt :: Ct -> TcTyCoVarSet Source

Returns free variables of constraints as a non-deterministic set

tyCoVarsOfCts :: Cts -> TcTyCoVarSet Source

Returns free variables of a bag of constraints as a non-deterministic set. See Note [Deterministic FV] in FV.

tyCoVarsOfCtList :: Ct -> [TcTyCoVar] Source

Returns free variables of constraints as a deterministically ordered. list. See Note [Deterministic FV] in FV.

tyCoVarsOfCtsList :: Cts -> [TcTyCoVar] Source

Returns free variables of a bag of constraints as a deterministically odered list. See Note [Deterministic FV] in FV.

toDerivedCt :: Ct -> Ct Source

Convert a Wanted to a Derived

toDerivedWC :: WantedConstraints -> WantedConstraints Source

Convert all Wanteds into Deriveds (ignoring insolubles)

exprCtOrigin :: HsExpr Name -> CtOrigin Source

Extract a suitable CtOrigin from a HsExpr

matchesCtOrigin :: MatchGroup Name (LHsExpr Name) -> CtOrigin Source

Extract a suitable CtOrigin from a MatchGroup

grhssCtOrigin :: GRHSs Name (LHsExpr Name) -> CtOrigin Source

Extract a suitable CtOrigin from guarded RHSs

data ErrorThing Source

A thing that can be stored for error message generation only. It is stored with a function to zonk and tidy the thing.

Constructors

Outputable a => ErrorThing a (Maybe Arity) (TidyEnv -> a -> TcM (TidyEnv, a)) 

mkErrorThing :: Outputable a => a -> ErrorThing Source

Make an ErrorThing that doesn't need tidying or zonking

errorThingNumArgs_maybe :: ErrorThing -> Maybe Arity Source

Retrieve the # of arguments in the error thing, if known

data TypeOrKind Source

Flag to see whether we're type-checking terms or kind-checking types

Constructors

TypeLevel 
KindLevel 

data TcEvDest Source

A place for type-checking evidence to go after it is generated. Wanted equalities are always HoleDest; other wanteds are always EvVarDest.

Constructors

EvVarDest EvVar

bind this var to the evidence

HoleDest CoercionHole

fill in this hole with the evidence See Note [Coercion holes] in TyCoRep

toKindLoc :: CtLoc -> CtLoc Source

Take a CtLoc and moves it to the kind level

ctEvRole :: CtEvidence -> Role Source

Get the role relevant for a CtEvidence

data TcPlugin Source

Constructors

TcPlugin 

Fields

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.

getEvBindsTcPluginM_maybe :: TcPluginM (Maybe EvBindsVar) Source

Access the EvBindsVar carried by the TcPluginM during constraint solving. Returns Nothing if invoked during tcPluginInit or tcPluginStop.

type CtFlavourRole = (CtFlavour, EqRel) Source

Whether or not one Ct can rewrite another is determined by its flavour and its equality relation. See also Note [Flavours with roles] in TcSMonad

ctEvFlavourRole :: CtEvidence -> CtFlavourRole Source

Extract the flavour, role, and boxity from a CtEvidence

ctFlavourRole :: Ct -> CtFlavourRole Source

Extract the flavour, role, and boxity from a Ct

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)