| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GHC.Tc.Gen.Head
Synopsis
- data HsExprArg (p :: TcPass)
 - data EValArg (p :: TcPass) where
 - data TcPass
 - data AppCtxt
 - appCtxtLoc :: AppCtxt -> SrcSpan
 - insideExpansion :: AppCtxt -> Bool
 - splitHsApps :: HsExpr GhcRn -> ((HsExpr GhcRn, AppCtxt), [HsExprArg 'TcpRn])
 - rebuildHsApps :: HsExpr GhcTc -> AppCtxt -> [HsExprArg 'TcpTc] -> TcRhoType -> TcM (HsExpr GhcTc)
 - addArgWrap :: HsWrapper -> [HsExprArg 'TcpInst] -> [HsExprArg 'TcpInst]
 - isHsValArg :: forall (id :: TcPass). HsExprArg id -> Bool
 - countLeadingValArgs :: forall (id :: TcPass). [HsExprArg id] -> Int
 - isVisibleArg :: forall (id :: TcPass). HsExprArg id -> Bool
 - pprHsExprArgTc :: HsExprArg 'TcpInst -> SDoc
 - countVisAndInvisValArgs :: forall (id :: TcPass). [HsExprArg id] -> Arity
 - countHsWrapperInvisArgs :: HsWrapper -> Arity
 - tcInferAppHead :: (HsExpr GhcRn, AppCtxt) -> [HsExprArg 'TcpRn] -> TcM (HsExpr GhcTc, TcSigmaType)
 - tcInferAppHead_maybe :: HsExpr GhcRn -> [HsExprArg 'TcpRn] -> TcM (Maybe (HsExpr GhcTc, TcSigmaType))
 - tcInferId :: Name -> TcM (HsExpr GhcTc, TcSigmaType)
 - tcCheckId :: Name -> ExpRhoType -> TcM (HsExpr GhcTc)
 - obviousSig :: HsExpr GhcRn -> Maybe (LHsSigWcType GhcRn)
 - tyConOf :: FamInstEnvs -> TcSigmaType -> Maybe TyCon
 - tyConOfET :: FamInstEnvs -> ExpRhoType -> Maybe TyCon
 - fieldNotInType :: RecSelParent -> RdrName -> TcRnMessage
 - nonBidirectionalErr :: Name -> TcRnMessage
 - addHeadCtxt :: AppCtxt -> TcM a -> TcM a
 - addExprCtxt :: HsExpr GhcRn -> TcRn a -> TcRn a
 - addFunResCtxt :: HsExpr GhcRn -> [HsExprArg 'TcpRn] -> TcType -> ExpRhoType -> TcM a -> TcM a
 
Documentation
data HsExprArg (p :: TcPass) Source #
Constructors
| EValArg | |
Fields 
  | |
| ETypeArg | |
| EPrag AppCtxt (HsPragE (GhcPass (XPass p))) | |
| EWrap EWrap | |
Instances
| OutputableBndrId (XPass p) => Outputable (HsExprArg p) Source # | |
data EValArg (p :: TcPass) where Source #
Instances
| OutputableBndrId (XPass p) => Outputable (EValArg p) Source # | |
Instances
appCtxtLoc :: AppCtxt -> SrcSpan Source #
insideExpansion :: AppCtxt -> Bool Source #
Arguments
| :: HsExpr GhcTc | the function being applied  | 
| -> AppCtxt | |
| -> [HsExprArg 'TcpTc] | the arguments to the function  | 
| -> TcRhoType | result type of the application  | 
| -> TcM (HsExpr GhcTc) | 
Rebuild an application: takes a type-checked application head
 expression together with arguments in the form of typechecked HsExprArgs
 and returns a typechecked application of the head to the arguments.
This performs a representation-polymorphism check to ensure that the remaining value arguments in an application have a fixed RuntimeRep.
See Note [Checking for representation-polymorphic built-ins].
countVisAndInvisValArgs :: forall (id :: TcPass). [HsExprArg id] -> Arity Source #
Count visible and invisible value arguments in a list
 of HsExprArg arguments.
countHsWrapperInvisArgs :: HsWrapper -> Arity Source #
Counts the number of invisible term-level arguments applied by an HsWrapper.
 Precondition: this wrapper contains no abstractions.
tcInferAppHead :: (HsExpr GhcRn, AppCtxt) -> [HsExprArg 'TcpRn] -> TcM (HsExpr GhcTc, TcSigmaType) Source #
tcInferAppHead_maybe :: HsExpr GhcRn -> [HsExprArg 'TcpRn] -> TcM (Maybe (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 #