Safe Haskell | None |
---|
- 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_th_used :: TcRef Bool
- tcg_th_splice_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_dependent_files :: TcRef [FilePath]
- 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_doc_hdr :: Maybe LHsDocString
- tcg_hpc :: AnyHpcUsage
- tcg_main :: Maybe Name
- tcg_safeInfer :: TcRef Bool
- data TcLclEnv = TcLclEnv {}
- data IfGblEnv = IfGblEnv {
- if_rec_types :: Maybe (Module, IfG TypeEnv)
- data IfLclEnv = IfLclEnv {}
- type ErrCtxt = (Bool, TidyEnv -> TcM (TidyEnv, MsgDoc))
- data RecFieldEnv = RecFields (NameEnv [Name]) NameSet
- data ImportAvails = ImportAvails {}
- emptyImportAvails :: ImportAvails
- plusImportAvails :: ImportAvails -> ImportAvails -> ImportAvails
- data WhereFrom
- mkModDeps :: [(ModuleName, IsBootInterface)] -> ModuleNameEnv (ModuleName, IsBootInterface)
- type TcTypeEnv = NameEnv TcTyThing
- data TcTyThing
- = AGlobal TyThing
- | ATcId {
- tct_id :: TcId
- tct_closed :: TopLevelFlag
- tct_level :: ThLevel
- | ATyVar Name TcTyVar
- | AThing TcKind
- | APromotionErr PromotionErr
- data PromotionErr
- = TyConPE
- | ClassPE
- | FamDataConPE
- | RecDataConPE
- pprTcTyThingCategory :: TcTyThing -> SDoc
- pprPECategory :: PromotionErr -> 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 Xi = Type
- data Ct
- = CDictCan {
- cc_ev :: CtEvidence
- cc_class :: Class
- cc_tyargs :: [Xi]
- cc_depth :: SubGoalDepth
- | CIrredEvCan {
- cc_ev :: CtEvidence
- cc_ty :: Xi
- cc_depth :: SubGoalDepth
- | CTyEqCan {
- cc_ev :: CtEvidence
- cc_tyvar :: TcTyVar
- cc_rhs :: Xi
- cc_depth :: SubGoalDepth
- | CFunEqCan {
- cc_ev :: CtEvidence
- cc_fun :: TyCon
- cc_tyargs :: [Xi]
- cc_rhs :: Xi
- cc_depth :: SubGoalDepth
- | CNonCanonical { }
- = CDictCan {
- type Cts = Bag Ct
- emptyCts :: Cts
- andCts :: Cts -> Cts -> Cts
- andManyCts :: [Cts] -> Cts
- keepWanted :: Cts -> Cts
- singleCt :: Ct -> Cts
- extendCts :: Cts -> Ct -> Cts
- isEmptyCts :: Cts -> Bool
- isCTyEqCan :: Ct -> Bool
- isCFunEqCan :: Ct -> Bool
- isCDictCan_Maybe :: Ct -> Maybe Class
- isCFunEqCan_Maybe :: Ct -> Maybe TyCon
- isCIrredEvCan :: Ct -> Bool
- isCNonCanonical :: Ct -> Bool
- isWantedCt :: Ct -> Bool
- isDerivedCt :: Ct -> Bool
- isGivenCt :: Ct -> Bool
- ctWantedLoc :: Ct -> WantedLoc
- ctEvidence :: Ct -> CtEvidence
- type SubGoalDepth = Int
- mkNonCanonical :: CtEvidence -> Ct
- ctPred :: Ct -> PredType
- ctEvPred :: CtEvidence -> TcPredType
- ctEvTerm :: CtEvidence -> EvTerm
- ctEvId :: CtEvidence -> TcId
- data WantedConstraints = WC {}
- insolubleWC :: WantedConstraints -> Bool
- emptyWC :: WantedConstraints
- isEmptyWC :: WantedConstraints -> Bool
- andWC :: WantedConstraints -> WantedConstraints -> WantedConstraints
- addFlats :: WantedConstraints -> Bag Ct -> WantedConstraints
- addImplics :: WantedConstraints -> Bag Implication -> WantedConstraints
- mkFlatWC :: [Ct] -> WantedConstraints
- data Implication = Implic {}
- 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 HsIPName
- | LiteralOrigin (HsOverLit Name)
- | NegateOrigin
- | ArithSeqOrigin (ArithSeqInfo Name)
- | PArrSeqOrigin (ArithSeqInfo Name)
- | SectionOrigin
- | TupleOrigin
- | AmbigOrigin Name
- | ExprSigOrigin
- | PatSigOrigin
- | PatOrigin
- | RecordUpdOrigin
- | ViewPatOrigin
- | ScOrigin
- | DerivOrigin
- | StandAloneDerivOrigin
- | DefaultOrigin
- | DoOrigin
- | MCompOrigin
- | 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
- pushErrCtxtSameOrigin :: ErrCtxt -> CtLoc orig -> CtLoc orig
- data SkolemInfo
- = SigSkol UserTypeCtxt Type
- | ClsSkol Class
- | InstSkol
- | DataSkol
- | FamInstSkol
- | PatSkol DataCon (HsMatchContext Name)
- | ArrowSkol
- | IPSkol [HsIPName]
- | RuleSkol RuleName
- | InferSkol [(Name, TcType)]
- | BracketSkol
- | UnifyForAllSkol [TcTyVar] TcType
- | UnkSkol
- data CtEvidence
- pprFlavorArising :: CtEvidence -> SDoc
- mkGivenLoc :: WantedLoc -> SkolemInfo -> GivenLoc
- isWanted :: CtEvidence -> Bool
- isGiven :: CtEvidence -> Bool
- isDerived :: CtEvidence -> Bool
- getWantedLoc :: CtEvidence -> WantedLoc
- getGivenLoc :: CtEvidence -> GivenLoc
- canSolve :: CtEvidence -> CtEvidence -> Bool
- canRewrite :: CtEvidence -> CtEvidence -> Bool
- pprEvVarTheta :: [EvVar] -> SDoc
- pprWantedsWithLocs :: WantedConstraints -> 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 | |
|
plusImportAvails :: ImportAvails -> ImportAvails -> ImportAvailsSource
Union two ImportAvails
This function is a key part of Import handling, basically for each import we create a seperate ImportAvails structure and then union them all together with this function.
newArrowScope :: TcM a -> TcM aSource
escapeArrowScope :: TcM a -> TcM aSource
inTouchableRange :: Untouchables -> TcTyVar -> BoolSource
CDictCan | |
| |
CIrredEvCan | |
| |
CTyEqCan | |
| |
CFunEqCan | |
| |
CNonCanonical | |
|
andManyCts :: [Cts] -> CtsSource
keepWanted :: Cts -> CtsSource
isEmptyCts :: Cts -> BoolSource
isCTyEqCan :: Ct -> BoolSource
isCFunEqCan :: Ct -> BoolSource
isCDictCan_Maybe :: Ct -> Maybe ClassSource
isCFunEqCan_Maybe :: Ct -> Maybe TyConSource
isCIrredEvCan :: Ct -> BoolSource
isCNonCanonical :: Ct -> BoolSource
isWantedCt :: Ct -> BoolSource
isDerivedCt :: Ct -> BoolSource
ctWantedLoc :: Ct -> WantedLocSource
ctEvidence :: Ct -> CtEvidenceSource
type SubGoalDepth = IntSource
mkNonCanonical :: CtEvidence -> CtSource
ctEvTerm :: CtEvidence -> EvTermSource
ctEvId :: CtEvidence -> TcIdSource
data WantedConstraints Source
mkFlatWC :: [Ct] -> WantedConstraintsSource
data Implication Source
ctLocOrigin :: CtLoc o -> oSource
setCtLocOrigin :: CtLoc o -> o' -> CtLoc o'Source
type GivenLoc = CtLoc SkolemInfoSource
pushErrCtxt :: orig -> ErrCtxt -> CtLoc orig -> CtLoc origSource
pushErrCtxtSameOrigin :: ErrCtxt -> CtLoc orig -> CtLoc origSource
data SkolemInfo Source
mkGivenLoc :: WantedLoc -> SkolemInfo -> GivenLocSource
isWanted :: CtEvidence -> BoolSource
isGiven :: CtEvidence -> BoolSource
isDerived :: CtEvidence -> BoolSource
canSolve :: CtEvidence -> CtEvidence -> BoolSource
canRewrite :: CtEvidence -> CtEvidence -> BoolSource
pprEvVarTheta :: [EvVar] -> SDocSource
pprEvVarWithType :: EvVar -> SDocSource
pprArising :: CtOrigin -> SDocSource
pprArisingAt :: Outputable o => CtLoc o -> SDocSource
type TcTyVarBinds = Bag TcTyVarBindSource