ghc-lib-9.0.1.20210207: The GHC API, decoupled from GHC versions
Safe HaskellNone
LanguageHaskell2010

GHC.Tc.Utils.Env

Synopsis

Documentation

data TyThing #

Constructors

AnId Id 
AConLike ConLike 
ATyCon TyCon 
ACoAxiom (CoAxiom Branched) 

Instances

Instances details
NamedThing TyThing 
Instance details

Defined in GHC.Core.TyCo.Rep

Outputable TyThing 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: TyThing -> SDoc

pprPrec :: Rational -> TyThing -> SDoc

data TcTyThing #

Constructors

AGlobal TyThing 
ATcId 

Fields

ATyVar Name TcTyVar 
ATcTyCon TyCon 
APromotionErr PromotionErr 

Instances

Instances details
Outputable TcTyThing 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: TcTyThing -> SDoc

pprPrec :: Rational -> TcTyThing -> SDoc

type TcId = Id #

data InstInfo a Source #

Constructors

InstInfo 

Fields

Instances

Instances details
OutputableBndrId a => Outputable (InstInfo (GhcPass a)) Source # 
Instance details

Defined in GHC.Tc.Utils.Env

Methods

ppr :: InstInfo (GhcPass a) -> SDoc

pprPrec :: Rational -> InstInfo (GhcPass a) -> SDoc

iDFunId :: InstInfo a -> DFunId Source #

pprInstInfoDetails :: OutputableBndrId a => InstInfo (GhcPass a) -> SDoc Source #

data InstBindings a Source #

Constructors

InstBindings 

Fields

tcExtendGlobalEnv :: [TyThing] -> TcM r -> TcM r Source #

tcExtendTyConEnv :: [TyCon] -> TcM r -> TcM r Source #

tcExtendGlobalEnvImplicit :: [TyThing] -> TcM r -> TcM r Source #

setGlobalTypeEnv :: TcGblEnv -> TypeEnv -> TcM TcGblEnv Source #

tcExtendGlobalValEnv :: [Id] -> TcM a -> TcM a Source #

tcLookupPatSyn :: Name -> TcM PatSyn Source #

tcLookupConLike :: Name -> TcM ConLike Source #

tcLookupAxiom :: Name -> TcM (CoAxiom Branched) Source #

addTypecheckedBinds :: TcGblEnv -> [LHsBinds GhcTc] -> TcGblEnv Source #

tcExtendKindEnv :: NameEnv TcTyThing -> TcM r -> TcM r Source #

tcExtendKindEnvList :: [(Name, TcTyThing)] -> TcM r -> TcM r Source #

tcExtendTyVarEnv :: [TyVar] -> TcM r -> TcM r Source #

tcExtendNameTyVarEnv :: [(Name, TcTyVar)] -> TcM r -> TcM r Source #

tcExtendLetEnv :: TopLevelFlag -> TcSigFun -> IsGroupClosed -> [TcId] -> TcM a -> TcM a Source #

tcExtendSigIds :: TopLevelFlag -> [TcId] -> TcM a -> TcM a Source #

tcExtendRecIds :: [(Name, TcId)] -> TcM a -> TcM a Source #

tcExtendIdEnv :: [TcId] -> TcM a -> TcM a Source #

tcExtendIdEnv1 :: Name -> TcId -> TcM a -> TcM a Source #

tcExtendIdEnv2 :: [(Name, TcId)] -> TcM a -> TcM a Source #

tcExtendBinderStack :: [TcBinder] -> TcM a -> TcM a Source #

tcExtendLocalTypeEnv :: TcLclEnv -> [(Name, TcTyThing)] -> TcLclEnv Source #

tcCheckUsage :: Name -> Mult -> TcM a -> TcM (a, HsWrapper) Source #

tcCheckUsage name mult thing_inside runs thing_inside, checks that the usage of name is a submultiplicity of mult, and removes name from the usage environment. See also Note [Wrapper returned from tcSubMult] in GHC.Tc.Utils.Unify, which applies to the wrapper returned from this function.

tcLookupTcTyCon :: HasDebugCallStack => Name -> TcM TcTyCon Source #

pprBinders :: [Name] -> SDoc Source #

tcAddDataFamConPlaceholders :: [LInstDecl GhcRn] -> TcM a -> TcM a Source #

tcAddPatSynPlaceholders :: [PatSynBind GhcRn GhcRn] -> TcM a -> TcM a Source #

getTypeSigNames :: [LSig GhcRn] -> NameSet Source #

tcExtendRecEnv :: [(Name, TyThing)] -> TcM r -> TcM r Source #

tcInitTidyEnv :: TcM TidyEnv Source #

tcInitOpenTidyEnv :: [TyCoVar] -> TcM TidyEnv Source #

Get a TidyEnv that includes mappings for all vars free in the given type. Useful when tidying open types.

tcGetInstEnvs :: TcM InstEnvs Source #

tcExtendRules :: [LRuleDecl GhcTc] -> TcM a -> TcM a Source #

checkWellStaged :: SDoc -> ThLevel -> ThLevel -> TcM () Source #

thLevel :: ThStage -> ThLevel #

topIdLvl :: Id -> ThLevel Source #

isBrackStage :: ThStage -> Bool Source #

newDFunName :: Class -> [Type] -> SrcSpan -> TcM Name Source #

Make a name for the dict fun for an instance decl. It's an *external* name, like other top-level names, and hence must be made with newGlobalBinder.

mkWrapperName :: (MonadIO m, HasDynFlags m, HasModule m) => String -> String -> m FastString Source #

Orphan instances

MonadThings (IOEnv (Env TcGblEnv TcLclEnv)) Source # 
Instance details

Methods

lookupThing :: Name -> IOEnv (Env TcGblEnv TcLclEnv) TyThing

lookupId :: Name -> IOEnv (Env TcGblEnv TcLclEnv) Id

lookupDataCon :: Name -> IOEnv (Env TcGblEnv TcLclEnv) DataCon

lookupTyCon :: Name -> IOEnv (Env TcGblEnv TcLclEnv) TyCon