ghc-6.12.1: The GHC APISource codeContentsIndex
TcEnv
Synopsis
data TyThing
= AnId Id
| ADataCon DataCon
| ATyCon TyCon
| AClass Class
data TcTyThing
= AGlobal TyThing
| ATcId {
tct_id :: TcId
tct_co :: RefinementVisibility
tct_type :: TcType
tct_level :: ThLevel
}
| ATyVar Name TcType
| AThing TcKind
type TcId = Id
data InstInfo a = InstInfo {
iSpec :: Instance
iBinds :: InstBindings a
}
iDFunId :: InstInfo a -> DFunId
pprInstInfo :: InstInfo a -> SDoc
pprInstInfoDetails :: OutputableBndr a => InstInfo a -> SDoc
simpleInstInfoClsTy :: InstInfo a -> (Class, Type)
simpleInstInfoTy :: InstInfo a -> Type
simpleInstInfoTyCon :: InstInfo a -> TyCon
data InstBindings a
= VanillaInst (LHsBinds a) [LSig a] Bool
| NewTypeDerived CoercionI
tcExtendGlobalEnv :: [TyThing] -> TcM r -> TcM r
setGlobalTypeEnv :: TcGblEnv -> TypeEnv -> TcM TcGblEnv
tcExtendGlobalValEnv :: [Id] -> TcM a -> TcM a
tcLookupLocatedGlobal :: Located Name -> TcM TyThing
tcLookupGlobal :: Name -> TcM TyThing
tcLookupField :: Name -> TcM Id
tcLookupTyCon :: Name -> TcM TyCon
tcLookupClass :: Name -> TcM Class
tcLookupDataCon :: Name -> TcM DataCon
tcLookupLocatedGlobalId :: Located Name -> TcM Id
tcLookupLocatedTyCon :: Located Name -> TcM TyCon
tcLookupLocatedClass :: Located Name -> TcM Class
tcLookupFamInst :: TyCon -> [Type] -> TcM (Maybe (TyCon, [Type]))
tcExtendKindEnv :: [(Name, TcKind)] -> TcM r -> TcM r
tcExtendKindEnvTvs :: [LHsTyVarBndr Name] -> TcM r -> TcM r
tcExtendTyVarEnv :: [TyVar] -> TcM r -> TcM r
tcExtendTyVarEnv2 :: [(Name, TcType)] -> TcM r -> TcM r
tcExtendGhciEnv :: [TcId] -> TcM a -> TcM a
tcExtendIdEnv :: [TcId] -> TcM a -> TcM a
tcExtendIdEnv1 :: Name -> TcId -> TcM a -> TcM a
tcExtendIdEnv2 :: [(Name, TcId)] -> TcM a -> TcM a
tcLookup :: Name -> TcM TcTyThing
tcLookupLocated :: Located Name -> TcM TcTyThing
tcLookupLocalIds :: [Name] -> TcM [TcId]
tcLookupId :: Name -> TcM Id
tcLookupTyVar :: Name -> TcM TcTyVar
getScopedTyVarBinds :: TcM [(Name, TcType)]
lclEnvElts :: TcLclEnv -> [TcTyThing]
getInLocalScope :: TcM (Name -> Bool)
findGlobals :: TcTyVarSet -> TidyEnv -> TcM (TidyEnv, [SDoc])
wrongThingErr :: String -> TcTyThing -> Name -> TcM a
pprBinders :: [Name] -> SDoc
tcExtendRecEnv :: [(Name, TyThing)] -> TcM r -> TcM r
tcExtendRules :: [LRuleDecl Id] -> TcM a -> TcM a
tcGetGlobalTyVars :: TcM TcTyVarSet
checkWellStaged :: SDoc -> ThLevel -> ThLevel -> TcM ()
tcMetaTy :: Name -> TcM Type
thLevel :: ThStage -> ThLevel
topIdLvl :: Id -> ThLevel
thTopLevelId :: Id -> Bool
thRnBrack :: ThStage
isBrackStage :: ThStage -> Bool
newLocalName :: Name -> TcRnIf gbl lcl Name
newDFunName :: Class -> [Type] -> SrcSpan -> TcM Name
newFamInstTyConName :: Name -> [Type] -> SrcSpan -> TcM Name
mkStableIdFromString :: String -> Type -> SrcSpan -> (OccName -> OccName) -> TcM TcId
mkStableIdFromName :: Name -> Type -> SrcSpan -> (OccName -> OccName) -> TcM TcId
Documentation
data TyThing Source
A typecheckable-thing, essentially anything that has a name
Constructors
AnId Id
ADataCon DataCon
ATyCon TyCon
AClass Class
show/hide Instances
data TcTyThing Source
Constructors
AGlobal TyThing
ATcId
tct_id :: TcId
tct_co :: RefinementVisibility
tct_type :: TcType
tct_level :: ThLevel
ATyVar Name TcType
AThing TcKind
show/hide Instances
type TcId = IdSource
data InstInfo a Source
Constructors
InstInfo
iSpec :: Instance
iBinds :: InstBindings a
iDFunId :: InstInfo a -> DFunIdSource
pprInstInfo :: InstInfo a -> SDocSource
pprInstInfoDetails :: OutputableBndr a => InstInfo a -> SDocSource
simpleInstInfoClsTy :: InstInfo a -> (Class, Type)Source
simpleInstInfoTy :: InstInfo a -> TypeSource
simpleInstInfoTyCon :: InstInfo a -> TyConSource
data InstBindings a Source
Constructors
VanillaInst (LHsBinds a) [LSig a] Bool
NewTypeDerived CoercionI
tcExtendGlobalEnv :: [TyThing] -> TcM r -> TcM rSource
setGlobalTypeEnv :: TcGblEnv -> TypeEnv -> TcM TcGblEnvSource
tcExtendGlobalValEnv :: [Id] -> TcM a -> TcM aSource
tcLookupLocatedGlobal :: Located Name -> TcM TyThingSource
tcLookupGlobal :: Name -> TcM TyThingSource
tcLookupField :: Name -> TcM IdSource
tcLookupTyCon :: Name -> TcM TyConSource
tcLookupClass :: Name -> TcM ClassSource
tcLookupDataCon :: Name -> TcM DataConSource
tcLookupLocatedGlobalId :: Located Name -> TcM IdSource
tcLookupLocatedTyCon :: Located Name -> TcM TyConSource
tcLookupLocatedClass :: Located Name -> TcM ClassSource
tcLookupFamInst :: TyCon -> [Type] -> TcM (Maybe (TyCon, [Type]))Source
tcExtendKindEnv :: [(Name, TcKind)] -> TcM r -> TcM rSource
tcExtendKindEnvTvs :: [LHsTyVarBndr Name] -> TcM r -> TcM rSource
tcExtendTyVarEnv :: [TyVar] -> TcM r -> TcM rSource
tcExtendTyVarEnv2 :: [(Name, TcType)] -> TcM r -> TcM rSource
tcExtendGhciEnv :: [TcId] -> TcM a -> TcM aSource
tcExtendIdEnv :: [TcId] -> TcM a -> TcM aSource
tcExtendIdEnv1 :: Name -> TcId -> TcM a -> TcM aSource
tcExtendIdEnv2 :: [(Name, TcId)] -> TcM a -> TcM aSource
tcLookup :: Name -> TcM TcTyThingSource
tcLookupLocated :: Located Name -> TcM TcTyThingSource
tcLookupLocalIds :: [Name] -> TcM [TcId]Source
tcLookupId :: Name -> TcM IdSource
tcLookupTyVar :: Name -> TcM TcTyVarSource
getScopedTyVarBinds :: TcM [(Name, TcType)]Source
lclEnvElts :: TcLclEnv -> [TcTyThing]Source
getInLocalScope :: TcM (Name -> Bool)Source
findGlobals :: TcTyVarSet -> TidyEnv -> TcM (TidyEnv, [SDoc])Source
wrongThingErr :: String -> TcTyThing -> Name -> TcM aSource
pprBinders :: [Name] -> SDocSource
tcExtendRecEnv :: [(Name, TyThing)] -> TcM r -> TcM rSource
tcExtendRules :: [LRuleDecl Id] -> TcM a -> TcM aSource
tcGetGlobalTyVars :: TcM TcTyVarSetSource
checkWellStaged :: SDoc -> ThLevel -> ThLevel -> TcM ()Source
tcMetaTy :: Name -> TcM TypeSource
thLevel :: ThStage -> ThLevelSource
topIdLvl :: Id -> ThLevelSource
thTopLevelId :: Id -> BoolSource
thRnBrack :: ThStageSource
isBrackStage :: ThStage -> BoolSource
newLocalName :: Name -> TcRnIf gbl lcl NameSource
newDFunName :: Class -> [Type] -> SrcSpan -> TcM NameSource
newFamInstTyConName :: Name -> [Type] -> SrcSpan -> TcM NameSource
mkStableIdFromString :: String -> Type -> SrcSpan -> (OccName -> OccName) -> TcM TcIdSource
mkStableIdFromName :: Name -> Type -> SrcSpan -> (OccName -> OccName) -> TcM TcIdSource
Produced by Haddock version 2.6.0