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

GHC.Tc.Gen.Head

Synopsis

Documentation

data HsExprArg (p :: TcPass) Source #

Constructors

EValArg 

Fields

ETypeArg 

Fields

EPrag AppCtxt (HsPragE (GhcPass (XPass p))) 
EWrap EWrap 

Instances

Instances details
OutputableBndrId (XPass p) => Outputable (HsExprArg p) Source # 
Instance details

Defined in GHC.Tc.Gen.Head

Methods

ppr :: HsExprArg p -> SDoc

data EValArg (p :: TcPass) where Source #

Constructors

ValArg :: LHsExpr (GhcPass (XPass p)) -> EValArg p 
ValArgQL 

Fields

Instances

Instances details
OutputableBndrId (XPass p) => Outputable (EValArg p) Source # 
Instance details

Defined in GHC.Tc.Gen.Head

Methods

ppr :: EValArg p -> SDoc

data TcPass Source #

Constructors

TcpRn 
TcpInst 
TcpTc 

data AppCtxt Source #

Constructors

VAExpansion (HsExpr GhcRn) SrcSpan 
VACall (HsExpr GhcRn) Int SrcSpan 

Instances

Instances details
Outputable AppCtxt Source # 
Instance details

Defined in GHC.Tc.Gen.Head

Methods

ppr :: AppCtxt -> SDoc

splitHsApps :: HsExpr GhcRn -> ((HsExpr GhcRn, AppCtxt), [HsExprArg 'TcpRn]) Source #

rebuildHsApps :: HsExpr GhcTc -> AppCtxt -> [HsExprArg 'TcpTc] -> HsExpr GhcTc Source #

tcInferAppHead :: (HsExpr GhcRn, AppCtxt) -> [HsExprArg 'TcpRn] -> Maybe TcRhoType -> TcM (HsExpr GhcTc, TcSigmaType) Source #

tcInferAppHead_maybe :: HsExpr GhcRn -> [HsExprArg 'TcpRn] -> Maybe TcRhoType -> TcM (Maybe (HsExpr GhcTc, TcSigmaType)) Source #

tcInferId :: Name -> TcM (HsExpr GhcTc, TcSigmaType) Source #

tcCheckId :: Name -> ExpRhoType -> TcM (HsExpr GhcTc) Source #

obviousSig :: HsExpr GhcRn -> Maybe (LHsSigWcType GhcRn) Source #

addAmbiguousNameErr :: RdrName -> TcM () Source #

This name really is ambiguous, so add a suitable "ambiguous occurrence" error, then continue

tyConOf :: FamInstEnvs -> TcSigmaType -> Maybe TyCon Source #

lookupParents :: Bool -> RdrName -> RnM [(RecSelParent, GlobalRdrElt)] Source #

fieldNotInType :: RecSelParent -> RdrName -> SDoc Source #

nonBidirectionalErr :: Outputable name => name -> SDoc Source #

addExprCtxt :: HsExpr GhcRn -> TcRn a -> TcRn a Source #

addFunResCtxt :: HsExpr GhcRn -> [HsExprArg 'TcpRn] -> TcType -> ExpRhoType -> TcM a -> TcM a Source #