Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- data HsExprArg (p :: TcPass) where
- data TcPass
- data QLFlag
- data EWrap
- data AppCtxt
- appCtxtLoc :: AppCtxt -> SrcSpan
- insideExpansion :: AppCtxt -> Bool
- splitHsApps :: HsExpr GhcRn -> TcM ((HsExpr GhcRn, AppCtxt), [HsExprArg 'TcpRn])
- rebuildHsApps :: (HsExpr GhcTc, AppCtxt) -> [HsExprArg 'TcpTc] -> HsExpr GhcTc
- addArgWrap :: forall (p :: TcPass). HsWrapper -> [HsExprArg p] -> [HsExprArg p]
- isHsValArg :: forall (id :: TcPass). HsExprArg id -> Bool
- leadingValArgs :: [HsExprArg 'TcpRn] -> [LHsExpr GhcRn]
- isVisibleArg :: forall (id :: TcPass). HsExprArg id -> Bool
- tcInferAppHead :: (HsExpr GhcRn, AppCtxt) -> TcM (HsExpr GhcTc, TcSigmaType)
- tcInferAppHead_maybe :: HsExpr GhcRn -> TcM (Maybe (HsExpr GhcTc, TcSigmaType))
- tcInferId :: LocatedN Name -> TcM (HsExpr GhcTc, TcSigmaType)
- tcCheckId :: Name -> ExpRhoType -> TcM (HsExpr GhcTc)
- tcInferConLike :: ConLike -> TcM (HsExpr GhcTc, TcSigmaType)
- obviousSig :: HsExpr GhcRn -> Maybe (LHsSigWcType GhcRn)
- tyConOf :: FamInstEnvs -> TcSigmaType -> Maybe TyCon
- tyConOfET :: FamInstEnvs -> ExpRhoType -> Maybe TyCon
- fieldNotInType :: RecSelParent -> RdrName -> TcRnMessage
- nonBidirectionalErr :: Name -> TcRnMessage
- pprArgInst :: HsExprArg 'TcpInst -> SDoc
- addHeadCtxt :: AppCtxt -> TcM a -> TcM a
- addExprCtxt :: HsExpr GhcRn -> TcRn a -> TcRn a
- addStmtCtxt :: ExprStmt GhcRn -> TcRn a -> TcRn a
- addFunResCtxt :: forall (p :: TcPass) a. HsExpr GhcTc -> [HsExprArg p] -> TcType -> ExpRhoType -> TcM a -> TcM a
Documentation
data HsExprArg (p :: TcPass) where Source #
EValArg | |
EValArgQL | |
| |
ETypeArg | |
EPrag :: forall (p :: TcPass). AppCtxt -> HsPragE (GhcPass (XPass p)) -> HsExprArg p | |
EWrap :: forall (p :: TcPass). EWrap -> HsExprArg p |
Instances
OutputableBndrId (XPass p) => Outputable (HsExprArg p) Source # | |
Instances
Instances
Instances
appCtxtLoc :: AppCtxt -> SrcSpan Source #
insideExpansion :: AppCtxt -> Bool Source #
:: (HsExpr GhcTc, AppCtxt) | the function being applied |
-> [HsExprArg 'TcpTc] | the arguments to the function |
-> HsExpr GhcTc |
Rebuild an application: takes a type-checked application head
expression together with arguments in the form of typechecked HsExprArg
s
and returns a typechecked application of the head to the arguments.
This performs a representation-polymorphism check to ensure that representation-polymorphic unlifted newtypes have been eta-expanded.
See Note [Eta-expanding rep-poly unlifted newtypes].
tcInferAppHead :: (HsExpr GhcRn, AppCtxt) -> TcM (HsExpr GhcTc, TcSigmaType) Source #
tcInferAppHead_maybe :: HsExpr GhcRn -> TcM (Maybe (HsExpr GhcTc, TcSigmaType)) Source #
tcInferConLike :: ConLike -> TcM (HsExpr GhcTc, TcSigmaType) Source #
obviousSig :: HsExpr GhcRn -> Maybe (LHsSigWcType GhcRn) Source #
tyConOf :: FamInstEnvs -> TcSigmaType -> Maybe TyCon Source #
tyConOfET :: FamInstEnvs -> ExpRhoType -> Maybe TyCon Source #
fieldNotInType :: RecSelParent -> RdrName -> TcRnMessage Source #