ghc-9.11: The GHC API
Safe HaskellNone
LanguageGHC2021

GHC.Tc.Gen.Head

Synopsis

Documentation

data HsExprArg (p :: TcPass) where Source #

Constructors

EValArg 

Fields

EValArgQL 

Fields

ETypeArg 

Fields

EPrag :: forall (p :: TcPass). AppCtxt -> HsPragE (GhcPass (XPass p)) -> HsExprArg p 
EWrap :: forall (p :: TcPass). EWrap -> HsExprArg p 

Instances

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

Defined in GHC.Tc.Gen.Head

Methods

ppr :: HsExprArg p -> SDoc Source #

data TcPass Source #

Constructors

TcpRn 
TcpInst 
TcpTc 

data QLFlag Source #

Constructors

DoQL 
NoQL 

Instances

Instances details
Outputable QLFlag Source # 
Instance details

Defined in GHC.Tc.Gen.Head

Methods

ppr :: QLFlag -> SDoc Source #

data EWrap Source #

Instances

Instances details
Outputable EWrap Source # 
Instance details

Defined in GHC.Tc.Gen.Head

Methods

ppr :: EWrap -> SDoc Source #

data AppCtxt Source #

Instances

Instances details
Outputable AppCtxt Source # 
Instance details

Defined in GHC.Tc.Gen.Head

Methods

ppr :: AppCtxt -> SDoc Source #

rebuildHsApps Source #

Arguments

:: (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 HsExprArgs 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].

addArgWrap :: forall (p :: TcPass). HsWrapper -> [HsExprArg p] -> [HsExprArg p] Source #

isHsValArg :: forall (id :: TcPass). HsExprArg id -> Bool Source #

isVisibleArg :: forall (id :: TcPass). HsExprArg id -> Bool Source #

addFunResCtxt :: forall (p :: TcPass) a. HsExpr GhcTc -> [HsExprArg p] -> TcType -> ExpRhoType -> TcM a -> TcM a Source #