- type TcRnIf a b c = IOEnv (Env a b) c
- type TcRn a = TcRnIf TcGblEnv TcLclEnv a
- type TcM a = TcRn a
- type RnM a = TcRn a
- type IfM lcl a = TcRnIf IfGblEnv lcl a
- type IfL a = IfM IfLclEnv a
- type IfG a = IfM () a
- type TcRef a = IORef a
- data Env gbl lcl = Env {}
- data TcGblEnv = TcGblEnv {
- tcg_mod :: Module
- tcg_src :: HscSource
- tcg_rdr_env :: GlobalRdrEnv
- tcg_default :: Maybe [Type]
- tcg_fix_env :: FixityEnv
- tcg_field_env :: RecFieldEnv
- tcg_type_env :: TypeEnv
- tcg_type_env_var :: TcRef TypeEnv
- tcg_inst_env :: InstEnv
- tcg_fam_inst_env :: FamInstEnv
- tcg_exports :: [AvailInfo]
- tcg_imports :: ImportAvails
- tcg_dus :: DefUses
- tcg_keep :: TcRef NameSet
- tcg_inst_uses :: TcRef NameSet
- tcg_th_used :: TcRef Bool
- tcg_dfun_n :: TcRef OccSet
- tcg_rn_exports :: Maybe [Located (IE Name)]
- tcg_rn_imports :: [LImportDecl Name]
- tcg_used_rdrnames :: TcRef (Set RdrName)
- tcg_rn_decls :: Maybe (HsGroup Name)
- 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
- tcg_hpc :: AnyHpcUsage
- tcg_main :: Maybe Name
- data TcLclEnv = TcLclEnv {}
- data IfGblEnv = IfGblEnv {
- if_rec_types :: Maybe (Module, IfG TypeEnv)
- data IfLclEnv = IfLclEnv {}
- type ErrCtxt = (Bool, TidyEnv -> TcM (TidyEnv, Message))
- data RecFieldEnv = RecFields (NameEnv [Name]) NameSet
- data ImportAvails = ImportAvails {
- imp_mods :: ModuleEnv [(ModuleName, Bool, SrcSpan)]
- imp_dep_mods :: ModuleNameEnv (ModuleName, IsBootInterface)
- imp_dep_pkgs :: [PackageId]
- imp_orphs :: [Module]
- imp_finsts :: [Module]
- emptyImportAvails :: ImportAvails
- plusImportAvails :: ImportAvails -> ImportAvails -> ImportAvails
- data WhereFrom
- mkModDeps :: [(ModuleName, IsBootInterface)] -> ModuleNameEnv (ModuleName, IsBootInterface)
- type TcTypeEnv = NameEnv TcTyThing
- data TcTyThing
- pprTcTyThingCategory :: TcTyThing -> SDoc
- data ThStage
- = Splice
- | Comp
- | Brack ThStage (TcRef [PendingSplice]) (TcRef WantedConstraints)
- topStage :: ThStage
- topAnnStage :: ThStage
- topSpliceStage :: ThStage
- type ThLevel = Int
- impLevel :: ThLevel
- outerLevel :: ThLevel
- thLevel :: ThStage -> ThLevel
- data ArrowCtxt = NoArrowCtxt
- newArrowScope :: TcM a -> TcM a
- escapeArrowScope :: TcM a -> TcM a
- data Untouchables
- inTouchableRange :: Untouchables -> TcTyVar -> Bool
- isNoUntouchables :: Untouchables -> Bool
- type WantedConstraints = Bag WantedConstraint
- emptyWanteds :: WantedConstraints
- andWanteds :: WantedConstraints -> WantedConstraints -> WantedConstraints
- extendWanteds :: WantedConstraints -> WantedConstraint -> WantedConstraints
- data WantedConstraint
- data WantedEvVar = WantedEvVar EvVar WantedLoc
- wantedEvVarLoc :: WantedEvVar -> WantedLoc
- wantedEvVarToVar :: WantedEvVar -> EvVar
- wantedEvVarPred :: WantedEvVar -> PredType
- splitWanteds :: WantedConstraints -> (Bag WantedEvVar, Bag Implication)
- evVarsToWanteds :: WantedLoc -> [EvVar] -> WantedConstraints
- data Implication = Implic {
- ic_untch :: Untouchables
- ic_env :: TcTypeEnv
- ic_skols :: TcTyVarSet
- ic_scoped :: [TcTyVar]
- ic_given :: [EvVar]
- ic_wanted :: WantedConstraints
- ic_binds :: EvBindsVar
- ic_loc :: GivenLoc
- data CtLoc orig = CtLoc orig SrcSpan [ErrCtxt]
- ctLocSpan :: CtLoc o -> SrcSpan
- ctLocOrigin :: CtLoc o -> o
- setCtLocOrigin :: CtLoc o -> o' -> CtLoc o'
- data CtOrigin
- = OccurrenceOf Name
- | AppOrigin
- | SpecPragOrigin Name
- | TypeEqOrigin EqOrigin
- | IPOccOrigin (IPName Name)
- | LiteralOrigin (HsOverLit Name)
- | NegateOrigin
- | ArithSeqOrigin (ArithSeqInfo Name)
- | PArrSeqOrigin (ArithSeqInfo Name)
- | SectionOrigin
- | TupleOrigin
- | ExprSigOrigin
- | PatSigOrigin
- | PatOrigin
- | RecordUpdOrigin
- | ViewPatOrigin
- | ScOrigin
- | DerivOrigin
- | StandAloneDerivOrigin
- | DefaultOrigin
- | DoOrigin
- | IfOrigin
- | ProcOrigin
- | AnnOrigin
- | FunDepOrigin
- data EqOrigin = UnifyOrigin {
- uo_actual :: TcType
- uo_expected :: TcType
- type WantedLoc = CtLoc CtOrigin
- type GivenLoc = CtLoc SkolemInfo
- pushErrCtxt :: orig -> ErrCtxt -> CtLoc orig -> CtLoc orig
- data SkolemInfo
- pprEvVarTheta :: [EvVar] -> SDoc
- pprWantedsWithLocs :: Bag WantedConstraint -> SDoc
- pprWantedWithLoc :: WantedConstraint -> SDoc
- pprEvVars :: [EvVar] -> SDoc
- pprEvVarWithType :: EvVar -> SDoc
- pprArising :: CtOrigin -> SDoc
- pprArisingAt :: Outputable o => CtLoc o -> SDoc
- type TcId = Id
- type TcIdSet = IdSet
- data TcTyVarBind = TcTyVarBind TcTyVar TcType
- type TcTyVarBinds = Bag TcTyVarBind
Documentation
TcGblEnv | |
|
TcLclEnv | |
|
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
ImportAvails | |
|
newArrowScope :: TcM a -> TcM aSource
escapeArrowScope :: TcM a -> TcM aSource
inTouchableRange :: Untouchables -> TcTyVar -> BoolSource
evVarsToWanteds :: WantedLoc -> [EvVar] -> WantedConstraintsSource
data Implication Source
Implic | |
|
ctLocOrigin :: CtLoc o -> oSource
setCtLocOrigin :: CtLoc o -> o' -> CtLoc o'Source
type GivenLoc = CtLoc SkolemInfoSource
pushErrCtxt :: orig -> ErrCtxt -> CtLoc orig -> CtLoc origSource
data SkolemInfo Source
pprEvVarTheta :: [EvVar] -> SDocSource
pprEvVarWithType :: EvVar -> SDocSource
pprArising :: CtOrigin -> SDocSource
pprArisingAt :: Outputable o => CtLoc o -> SDocSource
type TcTyVarBinds = Bag TcTyVarBindSource