ghc-6.10.3: The GHC APIContentsIndex
TcRnTypes
Documentation
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
Constructors
Env
env_top :: HscEnv
env_us :: !(IORef UniqSupply)
env_gbl :: gbl
env_lcl :: lcl
data TcGblEnv
Constructors
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 Int
tcg_rn_imports :: Maybe [LImportDecl Name]
tcg_rn_exports :: Maybe [Located (IE Name)]
tcg_rn_decls :: Maybe (HsGroup Name)
tcg_binds :: LHsBinds Id
tcg_warns :: Warnings
tcg_insts :: [Instance]
tcg_fam_insts :: [FamInst]
tcg_rules :: [LRuleDecl Id]
tcg_fords :: [LForeignDecl Id]
tcg_doc :: Maybe (HsDoc Name)
tcg_hmi :: HaddockModInfo Name
tcg_hpc :: AnyHpcUsage
data TcLclEnv
Constructors
TcLclEnv
tcl_loc :: SrcSpan
tcl_ctxt :: ErrCtxt
tcl_errs :: TcRef Messages
tcl_th_ctxt :: ThStage
tcl_arrow_ctxt :: ArrowCtxt
tcl_rdr :: LocalRdrEnv
tcl_env :: NameEnv TcTyThing
tcl_tyvars :: TcRef TcTyVarSet
tcl_lie :: TcRef LIE
data IfGblEnv
Constructors
IfGblEnv
if_rec_types :: Maybe (Module, IfG TypeEnv)
data IfLclEnv
Constructors
IfLclEnv
if_mod :: Module
if_loc :: SDoc
if_tv_env :: UniqFM TyVar
if_id_env :: UniqFM Id
type ErrCtxt = [TidyEnv -> TcM (TidyEnv, Message)]
data RecFieldEnv
Constructors
RecFields (NameEnv [Name]) NameSet
data ImportAvails
Constructors
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
Constructors
ImportByUser IsBootInterface
ImportBySystem
show/hide Instances
mkModDeps :: [(ModuleName, IsBootInterface)] -> ModuleNameEnv (ModuleName, IsBootInterface)
data TcTyThing
Constructors
AGlobal TyThing
ATcId
tct_id :: TcId
tct_co :: RefinementVisibility
tct_type :: TcType
tct_level :: ThLevel
ATyVar Name TcType
AThing TcKind
show/hide Instances
pprTcTyThingCategory :: TcTyThing -> SDoc
data RefinementVisibility
Constructors
Unrefineable
Rigid HsWrapper
Wobbly
WobblyInvisible
show/hide Instances
data ThStage
Constructors
Comp
Splice ThLevel
Brack ThLevel (TcRef [PendingSplice]) (TcRef LIE)
show/hide Instances
topStage :: ThStage
topSpliceStage :: ThStage
type ThLevel = Int
impLevel :: ThLevel
topLevel :: ThLevel
data ArrowCtxt
Constructors
NoArrowCtxt
newArrowScope :: TcM a -> TcM a
escapeArrowScope :: TcM a -> TcM a
data Inst
Constructors
Dict
tci_name :: Name
tci_pred :: TcPredType
tci_loc :: InstLoc
ImplicInst
tci_name :: Name
tci_tyvars :: [TcTyVar]
tci_given :: [Inst]
tci_wanted :: [Inst]
tci_loc :: InstLoc
Method
tci_id :: TcId
tci_oid :: TcId
tci_tys :: [TcType]
tci_theta :: TcThetaType
tci_loc :: InstLoc
LitInst
tci_name :: Name
tci_lit :: HsOverLit Name
tci_ty :: TcType
tci_loc :: InstLoc
EqInst
tci_left :: TcType
tci_right :: TcType
tci_co :: EqInstCo
tci_loc :: InstLoc
tci_name :: Name
show/hide Instances
type EqInstCo = Either TcTyVar Coercion
data InstOrigin
Constructors
SigOrigin SkolemInfo
IPBindOrigin (IPName Name)
OccurrenceOf Name
SpecPragOrigin Name
IPOccOrigin (IPName Name)
LiteralOrigin (HsOverLit Name)
NegateOrigin
ArithSeqOrigin (ArithSeqInfo Name)
PArrSeqOrigin (ArithSeqInfo Name)
TupleOrigin
InstSigOrigin
ExprSigOrigin
RecordUpdOrigin
ViewPatOrigin
InstScOrigin
NoScOrigin
DerivOrigin
StandAloneDerivOrigin
DefaultOrigin
DoOrigin
ProcOrigin
ImplicOrigin SDoc
EqOrigin
show/hide Instances
data InstLoc
Constructors
InstLoc InstOrigin SrcSpan ErrCtxt
pprInstLoc :: InstLoc -> SDoc
pprInstArising :: Inst -> SDoc
instLocSpan :: InstLoc -> SrcSpan
instLocOrigin :: InstLoc -> InstOrigin
setInstLoc :: Inst -> InstLoc -> Inst
type LIE = Bag Inst
emptyLIE :: LIE
unitLIE :: Inst -> LIE
plusLIE :: LIE -> LIE -> LIE
consLIE :: Inst -> LIE -> LIE
instLoc :: Inst -> InstLoc
instSpan :: Inst -> SrcSpan
plusLIEs :: [LIE] -> LIE
mkLIE :: [Inst] -> LIE
isEmptyLIE :: LIE -> Bool
lieToList :: LIE -> [Inst]
listToLIE :: [Inst] -> LIE
type TcId = Id
type TcIdSet = IdSet
type TcDictBinds = DictBinds TcId
Produced by Haddock version 2.4.2