ghc-lib-parser-9.12.2.20250421: The GHC API, decoupled from GHC versions
Safe HaskellIgnore
LanguageGHC2021

GHC.Hs.Expr

Description

Abstract Haskell syntax for expressions.

Synopsis

Documentation

pprExpr :: forall (p :: Pass). OutputableBndrId p => HsExpr (GhcPass p) -> SDoc Source #

pprFunBind :: forall (idR :: Pass). OutputableBndrId idR => MatchGroup (GhcPass idR) (LHsExpr (GhcPass idR)) -> SDoc Source #

pprPatBind :: forall (bndr :: Pass) (p :: Pass). (OutputableBndrId bndr, OutputableBndrId p) => LPat (GhcPass bndr) -> GRHSs (GhcPass p) (LHsExpr (GhcPass p)) -> SDoc Source #

pprLExpr :: forall (p :: Pass). OutputableBndrId p => LHsExpr (GhcPass p) -> SDoc Source #

data HsUntypedSpliceResult thing Source #

Constructors

HsUntypedSpliceTop 

Fields

HsUntypedSpliceNested SplicePointName 

Instances

Instances details
Data a => Data (HsUntypedSpliceResult a) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsUntypedSpliceResult a -> c (HsUntypedSpliceResult a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsUntypedSpliceResult a) #

toConstr :: HsUntypedSpliceResult a -> Constr #

dataTypeOf :: HsUntypedSpliceResult a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsUntypedSpliceResult a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsUntypedSpliceResult a)) #

gmapT :: (forall b. Data b => b -> b) -> HsUntypedSpliceResult a -> HsUntypedSpliceResult a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsUntypedSpliceResult a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsUntypedSpliceResult a -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsUntypedSpliceResult a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsUntypedSpliceResult a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsUntypedSpliceResult a -> m (HsUntypedSpliceResult a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsUntypedSpliceResult a -> m (HsUntypedSpliceResult a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsUntypedSpliceResult a -> m (HsUntypedSpliceResult a) #

data PendingTcSplice Source #

Pending Type-checker Splice

Instances

Instances details
Data PendingTcSplice Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PendingTcSplice -> c PendingTcSplice #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PendingTcSplice #

toConstr :: PendingTcSplice -> Constr #

dataTypeOf :: PendingTcSplice -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PendingTcSplice) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PendingTcSplice) #

gmapT :: (forall b. Data b => b -> b) -> PendingTcSplice -> PendingTcSplice #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PendingTcSplice -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PendingTcSplice -> r #

gmapQ :: (forall d. Data d => d -> u) -> PendingTcSplice -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PendingTcSplice -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PendingTcSplice -> m PendingTcSplice #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PendingTcSplice -> m PendingTcSplice #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PendingTcSplice -> m PendingTcSplice #

Outputable PendingTcSplice Source # 
Instance details

Defined in GHC.Hs.Expr

data PendingRnSplice Source #

Pending Renamer Splice

Instances

Instances details
Data PendingRnSplice Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PendingRnSplice -> c PendingRnSplice #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PendingRnSplice #

toConstr :: PendingRnSplice -> Constr #

dataTypeOf :: PendingRnSplice -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PendingRnSplice) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PendingRnSplice) #

gmapT :: (forall b. Data b => b -> b) -> PendingRnSplice -> PendingRnSplice #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PendingRnSplice -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PendingRnSplice -> r #

gmapQ :: (forall d. Data d => d -> u) -> PendingRnSplice -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PendingRnSplice -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PendingRnSplice -> m PendingRnSplice #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PendingRnSplice -> m PendingRnSplice #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PendingRnSplice -> m PendingRnSplice #

Outputable PendingRnSplice Source # 
Instance details

Defined in GHC.Hs.Expr

data SyntaxExprTc Source #

An expression with wrappers, used for rebindable syntax

This should desugar to

syn_res_wrap $ syn_expr (syn_arg_wraps[0] arg0)
                        (syn_arg_wraps[1] arg1) ...

where the actual arguments come from elsewhere in the AST.

Instances

Instances details
Data SyntaxExprTc Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SyntaxExprTc -> c SyntaxExprTc #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SyntaxExprTc #

toConstr :: SyntaxExprTc -> Constr #

dataTypeOf :: SyntaxExprTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SyntaxExprTc) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SyntaxExprTc) #

gmapT :: (forall b. Data b => b -> b) -> SyntaxExprTc -> SyntaxExprTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SyntaxExprTc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SyntaxExprTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> SyntaxExprTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SyntaxExprTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SyntaxExprTc -> m SyntaxExprTc #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SyntaxExprTc -> m SyntaxExprTc #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SyntaxExprTc -> m SyntaxExprTc #

Outputable SyntaxExprTc Source # 
Instance details

Defined in GHC.Hs.Expr

newtype ThModFinalizers Source #

Finalizers produced by a splice with addModFinalizer

See Note [Delaying modFinalizers in untyped splices] in GHC.Rename.Splice. For how this is used.

Constructors

ThModFinalizers [ForeignRef (Q ())] 

Instances

Instances details
Data ThModFinalizers Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ThModFinalizers -> c ThModFinalizers #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ThModFinalizers #

toConstr :: ThModFinalizers -> Constr #

dataTypeOf :: ThModFinalizers -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ThModFinalizers) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ThModFinalizers) #

gmapT :: (forall b. Data b => b -> b) -> ThModFinalizers -> ThModFinalizers #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ThModFinalizers -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ThModFinalizers -> r #

gmapQ :: (forall d. Data d => d -> u) -> ThModFinalizers -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ThModFinalizers -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ThModFinalizers -> m ThModFinalizers #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ThModFinalizers -> m ThModFinalizers #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ThModFinalizers -> m ThModFinalizers #

pp_rhs :: Outputable body => HsMatchContext fn -> body -> SDoc Source #

ppr_expr :: forall (p :: Pass). OutputableBndrId p => HsExpr (GhcPass p) -> SDoc Source #

pprArg :: forall (idL :: Pass). OutputableBndrId idL => ApplicativeArg (GhcPass idL) -> SDoc Source #

type PostTcExpr = HsExpr GhcTc Source #

Post-Type checking Expression

PostTcExpr is an evidence expression attached to the syntax tree by the type checker (c.f. postTcType).

type PostTcTable = [(Name, PostTcExpr)] Source #

Post-Type checking Table

We use a PostTcTable where there are a bunch of pieces of evidence, more than is convenient to keep individually.

data SyntaxExprRn Source #

The function to use in rebindable syntax. See Note [NoSyntaxExpr].

Instances

Instances details
Data SyntaxExprRn Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SyntaxExprRn -> c SyntaxExprRn #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SyntaxExprRn #

toConstr :: SyntaxExprRn -> Constr #

dataTypeOf :: SyntaxExprRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SyntaxExprRn) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SyntaxExprRn) #

gmapT :: (forall b. Data b => b -> b) -> SyntaxExprRn -> SyntaxExprRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SyntaxExprRn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SyntaxExprRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> SyntaxExprRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SyntaxExprRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SyntaxExprRn -> m SyntaxExprRn #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SyntaxExprRn -> m SyntaxExprRn #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SyntaxExprRn -> m SyntaxExprRn #

Outputable SyntaxExprRn Source # 
Instance details

Defined in GHC.Hs.Expr

noExpr :: forall (p :: Pass). HsExpr (GhcPass p) Source #

This is used for rebindable-syntax pieces that are too polymorphic for tcSyntaxOp (trS_fmap and the mzip in ParStmt)

noSyntaxExpr :: forall (p :: Pass). IsPass p => SyntaxExpr (GhcPass p) Source #

mkSyntaxExpr :: HsExpr GhcRn -> SyntaxExprRn Source #

Make a 'SyntaxExpr GhcRn' from an expression Used only in getMonadFailOp. See Note [Monad fail : Rebindable syntax, overloaded strings] in GHC.Rename.Expr

mkRnSyntaxExpr :: Name -> SyntaxExprRn Source #

Make a SyntaxExpr from a Name (the "rn" is because this is used in the renamer).

data HsWrap (hs_syn :: Type -> Type) Source #

HsWrap appears only in typechecker output

Constructors

HsWrap HsWrapper (hs_syn GhcTc) 

Instances

Instances details
(Data (hs_syn GhcTc), Typeable hs_syn) => Data (HsWrap hs_syn) Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsWrap hs_syn -> c (HsWrap hs_syn) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsWrap hs_syn) #

toConstr :: HsWrap hs_syn -> Constr #

dataTypeOf :: HsWrap hs_syn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsWrap hs_syn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsWrap hs_syn)) #

gmapT :: (forall b. Data b => b -> b) -> HsWrap hs_syn -> HsWrap hs_syn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWrap hs_syn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWrap hs_syn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsWrap hs_syn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWrap hs_syn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWrap hs_syn -> m (HsWrap hs_syn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWrap hs_syn -> m (HsWrap hs_syn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWrap hs_syn -> m (HsWrap hs_syn) #

data HsBracketTc Source #

Instances

Instances details
Data HsBracketTc Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBracketTc -> c HsBracketTc #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsBracketTc #

toConstr :: HsBracketTc -> Constr #

dataTypeOf :: HsBracketTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsBracketTc) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsBracketTc) #

gmapT :: (forall b. Data b => b -> b) -> HsBracketTc -> HsBracketTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBracketTc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBracketTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsBracketTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBracketTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBracketTc -> m HsBracketTc #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracketTc -> m HsBracketTc #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracketTc -> m HsBracketTc #

data BracketAnn noE hasE Source #

Constructors

BracketNoE noE 
BracketHasE hasE 

Instances

Instances details
(Data noE, Data hasE) => Data (BracketAnn noE hasE) Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BracketAnn noE hasE -> c (BracketAnn noE hasE) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (BracketAnn noE hasE) #

toConstr :: BracketAnn noE hasE -> Constr #

dataTypeOf :: BracketAnn noE hasE -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (BracketAnn noE hasE)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (BracketAnn noE hasE)) #

gmapT :: (forall b. Data b => b -> b) -> BracketAnn noE hasE -> BracketAnn noE hasE #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BracketAnn noE hasE -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BracketAnn noE hasE -> r #

gmapQ :: (forall d. Data d => d -> u) -> BracketAnn noE hasE -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BracketAnn noE hasE -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BracketAnn noE hasE -> m (BracketAnn noE hasE) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BracketAnn noE hasE -> m (BracketAnn noE hasE) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BracketAnn noE hasE -> m (BracketAnn noE hasE) #

(NoAnn n, NoAnn h) => NoAnn (BracketAnn n h) Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

noAnn :: BracketAnn n h Source #

data EpAnnHsCase Source #

Constructors

EpAnnHsCase 

Fields

Instances

Instances details
Data EpAnnHsCase Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EpAnnHsCase -> c EpAnnHsCase #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EpAnnHsCase #

toConstr :: EpAnnHsCase -> Constr #

dataTypeOf :: EpAnnHsCase -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EpAnnHsCase) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EpAnnHsCase) #

gmapT :: (forall b. Data b => b -> b) -> EpAnnHsCase -> EpAnnHsCase #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EpAnnHsCase -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EpAnnHsCase -> r #

gmapQ :: (forall d. Data d => d -> u) -> EpAnnHsCase -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EpAnnHsCase -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EpAnnHsCase -> m EpAnnHsCase #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EpAnnHsCase -> m EpAnnHsCase #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EpAnnHsCase -> m EpAnnHsCase #

NoAnn EpAnnHsCase Source # 
Instance details

Defined in GHC.Hs.Expr

data EpAnnLam Source #

Constructors

EpAnnLam 

Fields

Instances

Instances details
Data EpAnnLam Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EpAnnLam -> c EpAnnLam #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EpAnnLam #

toConstr :: EpAnnLam -> Constr #

dataTypeOf :: EpAnnLam -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EpAnnLam) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EpAnnLam) #

gmapT :: (forall b. Data b => b -> b) -> EpAnnLam -> EpAnnLam #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EpAnnLam -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EpAnnLam -> r #

gmapQ :: (forall d. Data d => d -> u) -> EpAnnLam -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EpAnnLam -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EpAnnLam -> m EpAnnLam #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EpAnnLam -> m EpAnnLam #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EpAnnLam -> m EpAnnLam #

NoAnn EpAnnLam Source # 
Instance details

Defined in GHC.Hs.Expr

data EpAnnUnboundVar Source #

Constructors

EpAnnUnboundVar 

Instances

Instances details
Data EpAnnUnboundVar Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EpAnnUnboundVar -> c EpAnnUnboundVar #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EpAnnUnboundVar #

toConstr :: EpAnnUnboundVar -> Constr #

dataTypeOf :: EpAnnUnboundVar -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EpAnnUnboundVar) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EpAnnUnboundVar) #

gmapT :: (forall b. Data b => b -> b) -> EpAnnUnboundVar -> EpAnnUnboundVar #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EpAnnUnboundVar -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EpAnnUnboundVar -> r #

gmapQ :: (forall d. Data d => d -> u) -> EpAnnUnboundVar -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EpAnnUnboundVar -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EpAnnUnboundVar -> m EpAnnUnboundVar #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EpAnnUnboundVar -> m EpAnnUnboundVar #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EpAnnUnboundVar -> m EpAnnUnboundVar #

data AnnExplicitSum Source #

Instances

Instances details
Data AnnExplicitSum Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnExplicitSum -> c AnnExplicitSum #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnExplicitSum #

toConstr :: AnnExplicitSum -> Constr #

dataTypeOf :: AnnExplicitSum -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnExplicitSum) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnExplicitSum) #

gmapT :: (forall b. Data b => b -> b) -> AnnExplicitSum -> AnnExplicitSum #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnExplicitSum -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnExplicitSum -> r #

gmapQ :: (forall d. Data d => d -> u) -> AnnExplicitSum -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnExplicitSum -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnExplicitSum -> m AnnExplicitSum #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnExplicitSum -> m AnnExplicitSum #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnExplicitSum -> m AnnExplicitSum #

NoAnn AnnExplicitSum Source # 
Instance details

Defined in GHC.Hs.Expr

data AnnsIf Source #

Constructors

AnnsIf 

Fields

Instances

Instances details
Data AnnsIf Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnsIf -> c AnnsIf #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnsIf #

toConstr :: AnnsIf -> Constr #

dataTypeOf :: AnnsIf -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnsIf) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnsIf) #

gmapT :: (forall b. Data b => b -> b) -> AnnsIf -> AnnsIf #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnsIf -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnsIf -> r #

gmapQ :: (forall d. Data d => d -> u) -> AnnsIf -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnsIf -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnsIf -> m AnnsIf #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnsIf -> m AnnsIf #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnsIf -> m AnnsIf #

NoAnn AnnsIf Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

noAnn :: AnnsIf Source #

data family HsRecUpdParent x Source #

Information about the parent of a record update:

  • the parent type constructor or pattern synonym,
  • the relevant con-likes,
  • the field labels.

Instances

Instances details
Data (HsRecUpdParent GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsRecUpdParent GhcPs -> c (HsRecUpdParent GhcPs) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecUpdParent GhcPs) #

toConstr :: HsRecUpdParent GhcPs -> Constr #

dataTypeOf :: HsRecUpdParent GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecUpdParent GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecUpdParent GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> HsRecUpdParent GhcPs -> HsRecUpdParent GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecUpdParent GhcPs -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecUpdParent GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsRecUpdParent GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecUpdParent GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecUpdParent GhcPs -> m (HsRecUpdParent GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecUpdParent GhcPs -> m (HsRecUpdParent GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecUpdParent GhcPs -> m (HsRecUpdParent GhcPs) #

Data (HsRecUpdParent GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsRecUpdParent GhcRn -> c (HsRecUpdParent GhcRn) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecUpdParent GhcRn) #

toConstr :: HsRecUpdParent GhcRn -> Constr #

dataTypeOf :: HsRecUpdParent GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecUpdParent GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecUpdParent GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> HsRecUpdParent GhcRn -> HsRecUpdParent GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecUpdParent GhcRn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecUpdParent GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsRecUpdParent GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecUpdParent GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecUpdParent GhcRn -> m (HsRecUpdParent GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecUpdParent GhcRn -> m (HsRecUpdParent GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecUpdParent GhcRn -> m (HsRecUpdParent GhcRn) #

Data (HsRecUpdParent GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsRecUpdParent GhcTc -> c (HsRecUpdParent GhcTc) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecUpdParent GhcTc) #

toConstr :: HsRecUpdParent GhcTc -> Constr #

dataTypeOf :: HsRecUpdParent GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecUpdParent GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecUpdParent GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> HsRecUpdParent GhcTc -> HsRecUpdParent GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecUpdParent GhcTc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecUpdParent GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsRecUpdParent GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecUpdParent GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecUpdParent GhcTc -> m (HsRecUpdParent GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecUpdParent GhcTc -> m (HsRecUpdParent GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecUpdParent GhcTc -> m (HsRecUpdParent GhcTc) #

data HsRecUpdParent GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

data HsRecUpdParent GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

data HsRecUpdParent GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

data AnnProjection Source #

Constructors

AnnProjection 

Fields

Instances

Instances details
Data AnnProjection Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnProjection -> c AnnProjection #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnProjection #

toConstr :: AnnProjection -> Constr #

dataTypeOf :: AnnProjection -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnProjection) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnProjection) #

gmapT :: (forall b. Data b => b -> b) -> AnnProjection -> AnnProjection #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnProjection -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnProjection -> r #

gmapQ :: (forall d. Data d => d -> u) -> AnnProjection -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnProjection -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnProjection -> m AnnProjection #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnProjection -> m AnnProjection #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnProjection -> m AnnProjection #

NoAnn AnnProjection Source # 
Instance details

Defined in GHC.Hs.Expr

data AnnArithSeq Source #

Constructors

AnnArithSeq 

Fields

Instances

Instances details
Data AnnArithSeq Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnArithSeq -> c AnnArithSeq #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnArithSeq #

toConstr :: AnnArithSeq -> Constr #

dataTypeOf :: AnnArithSeq -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnArithSeq) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnArithSeq) #

gmapT :: (forall b. Data b => b -> b) -> AnnArithSeq -> AnnArithSeq #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnArithSeq -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnArithSeq -> r #

gmapQ :: (forall d. Data d => d -> u) -> AnnArithSeq -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnArithSeq -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnArithSeq -> m AnnArithSeq #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnArithSeq -> m AnnArithSeq #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnArithSeq -> m AnnArithSeq #

NoAnn AnnArithSeq Source # 
Instance details

Defined in GHC.Hs.Expr

data AnnFunRhs Source #

Constructors

AnnFunRhs 

Fields

Instances

Instances details
Data AnnFunRhs Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnFunRhs -> c AnnFunRhs #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnFunRhs #

toConstr :: AnnFunRhs -> Constr #

dataTypeOf :: AnnFunRhs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnFunRhs) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnFunRhs) #

gmapT :: (forall b. Data b => b -> b) -> AnnFunRhs -> AnnFunRhs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnFunRhs -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnFunRhs -> r #

gmapQ :: (forall d. Data d => d -> u) -> AnnFunRhs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnFunRhs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnFunRhs -> m AnnFunRhs #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnFunRhs -> m AnnFunRhs #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnFunRhs -> m AnnFunRhs #

NoAnn AnnFunRhs Source # 
Instance details

Defined in GHC.Hs.Expr

data AnnFieldLabel Source #

Constructors

AnnFieldLabel 

Fields

Instances

Instances details
Data AnnFieldLabel Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnFieldLabel -> c AnnFieldLabel #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnFieldLabel #

toConstr :: AnnFieldLabel -> Constr #

dataTypeOf :: AnnFieldLabel -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnFieldLabel) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnFieldLabel) #

gmapT :: (forall b. Data b => b -> b) -> AnnFieldLabel -> AnnFieldLabel #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnFieldLabel -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnFieldLabel -> r #

gmapQ :: (forall d. Data d => d -> u) -> AnnFieldLabel -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnFieldLabel -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnFieldLabel -> m AnnFieldLabel #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnFieldLabel -> m AnnFieldLabel #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnFieldLabel -> m AnnFieldLabel #

NoAnn AnnFieldLabel Source # 
Instance details

Defined in GHC.Hs.Expr

tupArgPresent :: forall (p :: Pass). HsTupArg (GhcPass p) -> Bool Source #

data XXExprGhcRn Source #

Constructors

ExpandedThingRn 
PopErrCtxt !(LHsExpr GhcRn) 
HsRecSelRn (FieldOcc GhcRn)

Variable pointing to record selector See Note [Non-overloaded record field selectors] and Note [Record selectors in the AST]

Instances

Instances details
Data XXExprGhcRn Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> XXExprGhcRn -> c XXExprGhcRn #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c XXExprGhcRn #

toConstr :: XXExprGhcRn -> Constr #

dataTypeOf :: XXExprGhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c XXExprGhcRn) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c XXExprGhcRn) #

gmapT :: (forall b. Data b => b -> b) -> XXExprGhcRn -> XXExprGhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> XXExprGhcRn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> XXExprGhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> XXExprGhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> XXExprGhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> XXExprGhcRn -> m XXExprGhcRn #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> XXExprGhcRn -> m XXExprGhcRn #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> XXExprGhcRn -> m XXExprGhcRn #

Outputable XXExprGhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: XXExprGhcRn -> SDoc Source #

data XXExprGhcTc Source #

Constructors

WrapExpr HsWrapper (HsExpr GhcTc) 
ExpandedThingTc 
ConLikeTc ConLike [TcTyVar] [Scaled TcType] 
HsTick CoreTickish (LHsExpr GhcTc) 
HsBinTick Int Int (LHsExpr GhcTc) 
HsRecSelTc (FieldOcc GhcTc)

Variable pointing to record selector See Note [Non-overloaded record field selectors] and Note [Record selectors in the AST]

Instances

Instances details
Data XXExprGhcTc Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> XXExprGhcTc -> c XXExprGhcTc #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c XXExprGhcTc #

toConstr :: XXExprGhcTc -> Constr #

dataTypeOf :: XXExprGhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c XXExprGhcTc) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c XXExprGhcTc) #

gmapT :: (forall b. Data b => b -> b) -> XXExprGhcTc -> XXExprGhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> XXExprGhcTc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> XXExprGhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> XXExprGhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> XXExprGhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> XXExprGhcTc -> m XXExprGhcTc #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> XXExprGhcTc -> m XXExprGhcTc #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> XXExprGhcTc -> m XXExprGhcTc #

Outputable XXExprGhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: XXExprGhcTc -> SDoc Source #

data HsThingRn Source #

The different source constructs that we use to instantiate the "original" field in an `XXExprGhcRn original expansion`

Instances

Instances details
Data HsThingRn Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsThingRn -> c HsThingRn #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsThingRn #

toConstr :: HsThingRn -> Constr #

dataTypeOf :: HsThingRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsThingRn) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsThingRn) #

gmapT :: (forall b. Data b => b -> b) -> HsThingRn -> HsThingRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsThingRn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsThingRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsThingRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsThingRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsThingRn -> m HsThingRn #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsThingRn -> m HsThingRn #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsThingRn -> m HsThingRn #

Outputable HsThingRn Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: HsThingRn -> SDoc Source #

mkPopErrCtxtExpr :: LHsExpr GhcRn -> HsExpr GhcRn Source #

Wrap a located expression with a PopErrCtxt

mkPopErrCtxtExprAt :: SrcSpanAnnA -> LHsExpr GhcRn -> LHsExpr GhcRn Source #

Wrap a located expression with a PopSrcExpr with an appropriate location

mkExpandedExpr Source #

Arguments

:: HsExpr GhcRn

source expression

-> HsExpr GhcRn

expanded expression

-> HsExpr GhcRn

suitably wrapped XXExprGhcRn

Build an expression using the extension constructor XExpr, and the two components of the expansion: original expression and expanded expressions.

mkExpandedStmt Source #

Arguments

:: ExprLStmt GhcRn

source statement

-> HsExpr GhcRn

expanded expression

-> HsExpr GhcRn

suitably wrapped XXExprGhcRn

Build an expression using the extension constructor XExpr, and the two components of the expansion: original do stmt and expanded expression

mkExpandedPatRn Source #

Arguments

:: LPat GhcRn

source pattern

-> HsExpr GhcRn

expanded expression

-> HsExpr GhcRn

suitably wrapped XXExprGhcRn

mkExpandedStmtAt Source #

Arguments

:: SrcSpanAnnA

Location for the expansion expression

-> ExprLStmt GhcRn

source statement

-> HsExpr GhcRn

expanded expression

-> LHsExpr GhcRn

suitably wrapped located XXExprGhcRn

Build an expression using the extension constructor XExpr, and the two components of the expansion: original do stmt and expanded expression an associate with a provided location

mkExpandedStmtPopAt Source #

Arguments

:: SrcSpanAnnA

Location for the expansion statement

-> ExprLStmt GhcRn

source statement

-> HsExpr GhcRn

expanded expression

-> LHsExpr GhcRn

suitably wrapped XXExprGhcRn

Wrap the expanded version of the expression with a pop.

mkExpandedExprTc Source #

Arguments

:: HsExpr GhcRn

source expression

-> HsExpr GhcTc

expanded typechecked expression

-> HsExpr GhcTc

suitably wrapped XXExprGhcRn

Build a XXExprGhcRn out of an extension constructor, and the two components of the expansion: original and expanded typechecked expressions.

mkExpandedStmtTc Source #

Arguments

:: ExprLStmt GhcRn

source do statement

-> HsExpr GhcTc

expanded typechecked expression

-> HsExpr GhcTc

suitably wrapped XXExprGhcRn

Build a XXExprGhcRn out of an extension constructor. The two components of the expansion are: original statement and expanded typechecked expression.

isAtomicHsExpr :: forall (p :: Pass). IsPass p => HsExpr (GhcPass p) -> Bool Source #

pprBinds :: forall (idL :: Pass) (idR :: Pass). (OutputableBndrId idL, OutputableBndrId idR) => HsLocalBindsLR (GhcPass idL) (GhcPass idR) -> SDoc Source #

ppr_lexpr :: forall (p :: Pass). OutputableBndrId p => LHsExpr (GhcPass p) -> SDoc Source #

pprMatches :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable body) => MatchGroup (GhcPass idR) body -> SDoc Source #

pprDo :: forall (p :: Pass) body. (OutputableBndrId p, Outputable body, Anno (StmtLR (GhcPass p) (GhcPass p) body) ~ SrcSpanAnnA) => HsDoFlavour -> [LStmt (GhcPass p) body] -> SDoc Source #

hsExprNeedsParens :: forall (p :: Pass). IsPass p => PprPrec -> HsExpr (GhcPass p) -> Bool Source #

hsExprNeedsParens p e returns True if the expression e needs parentheses under precedence p.

gHsPar :: forall (p :: Pass). IsPass p => LHsExpr (GhcPass p) -> HsExpr (GhcPass p) Source #

Parenthesize an expression without token information

parenthesizeHsExpr :: forall (p :: Pass). IsPass p => PprPrec -> LHsExpr (GhcPass p) -> LHsExpr (GhcPass p) Source #

parenthesizeHsExpr p e checks if hsExprNeedsParens p e is true, and if so, surrounds e with an HsPar. Otherwise, it simply returns e.

stripParensHsExpr :: forall (p :: Pass). HsExpr (GhcPass p) -> HsExpr (GhcPass p) Source #

type CmdSyntaxTable p = [(Name, HsExpr p)] Source #

Command Syntax Table (for Arrow syntax)

data CmdTopTc Source #

Instances

Instances details
Data CmdTopTc Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CmdTopTc -> c CmdTopTc #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CmdTopTc #

toConstr :: CmdTopTc -> Constr #

dataTypeOf :: CmdTopTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CmdTopTc) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CmdTopTc) #

gmapT :: (forall b. Data b => b -> b) -> CmdTopTc -> CmdTopTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CmdTopTc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CmdTopTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> CmdTopTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CmdTopTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CmdTopTc -> m CmdTopTc #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CmdTopTc -> m CmdTopTc #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CmdTopTc -> m CmdTopTc #

pprCmd :: forall (p :: Pass). OutputableBndrId p => HsCmd (GhcPass p) -> SDoc Source #

pprLCmd :: forall (p :: Pass). OutputableBndrId p => LHsCmd (GhcPass p) -> SDoc Source #

ppr_cmd :: forall (p :: Pass). OutputableBndrId p => HsCmd (GhcPass p) -> SDoc Source #

ppr_lcmd :: forall (p :: Pass). OutputableBndrId p => LHsCmd (GhcPass p) -> SDoc Source #

pprArrowExpr :: forall (p :: Pass) body. (OutputableBndrId p, Outputable body, Anno (StmtLR (GhcPass p) (GhcPass p) body) ~ SrcSpanAnnA) => [LStmt (GhcPass p) body] -> SDoc Source #

pprCmdArg :: forall (p :: Pass). OutputableBndrId p => HsCmdTop (GhcPass p) -> SDoc Source #

data MatchGroupTc Source #

Constructors

MatchGroupTc 

Instances

Instances details
Data MatchGroupTc Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroupTc -> c MatchGroupTc #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MatchGroupTc #

toConstr :: MatchGroupTc -> Constr #

dataTypeOf :: MatchGroupTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MatchGroupTc) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MatchGroupTc) #

gmapT :: (forall b. Data b => b -> b) -> MatchGroupTc -> MatchGroupTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroupTc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroupTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroupTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroupTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroupTc -> m MatchGroupTc #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroupTc -> m MatchGroupTc #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroupTc -> m MatchGroupTc #

pprMatch :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable body) => Match (GhcPass idR) body -> SDoc Source #

isEmptyMatchGroup :: forall (p :: Pass) body. MatchGroup (GhcPass p) body -> Bool Source #

isSingletonMatchGroup :: forall (p :: Pass) body. [LMatch (GhcPass p) body] -> Bool Source #

Is there only one RHS in this list of matches?

matchGroupArity :: forall (id :: Pass) body. MatchGroup (GhcPass id) body -> Arity Source #

hsLMatchPats :: forall (id :: Pass) body. LMatch (GhcPass id) body -> [LPat (GhcPass id)] Source #

data GrhsAnn Source #

Constructors

GrhsAnn 

Fields

Instances

Instances details
Data GrhsAnn Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GrhsAnn -> c GrhsAnn #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GrhsAnn #

toConstr :: GrhsAnn -> Constr #

dataTypeOf :: GrhsAnn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GrhsAnn) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GrhsAnn) #

gmapT :: (forall b. Data b => b -> b) -> GrhsAnn -> GrhsAnn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GrhsAnn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GrhsAnn -> r #

gmapQ :: (forall d. Data d => d -> u) -> GrhsAnn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GrhsAnn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GrhsAnn -> m GrhsAnn #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GrhsAnn -> m GrhsAnn #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GrhsAnn -> m GrhsAnn #

NoAnn GrhsAnn Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

noAnn :: GrhsAnn Source #

Outputable GrhsAnn Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: GrhsAnn -> SDoc Source #

pprGRHSs :: forall (idR :: Pass) body fn. (OutputableBndrId idR, Outputable body) => HsMatchContext fn -> GRHSs (GhcPass idR) body -> SDoc Source #

pprGRHS :: forall (idR :: Pass) body fn. (OutputableBndrId idR, Outputable body) => HsMatchContext fn -> GRHS (GhcPass idR) body -> SDoc Source #

data RecStmtTc Source #

Instances

Instances details
Data RecStmtTc Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RecStmtTc -> c RecStmtTc #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RecStmtTc #

toConstr :: RecStmtTc -> Constr #

dataTypeOf :: RecStmtTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RecStmtTc) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RecStmtTc) #

gmapT :: (forall b. Data b => b -> b) -> RecStmtTc -> RecStmtTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RecStmtTc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RecStmtTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> RecStmtTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RecStmtTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RecStmtTc -> m RecStmtTc #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RecStmtTc -> m RecStmtTc #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RecStmtTc -> m RecStmtTc #

data XBindStmtRn Source #

Instances

Instances details
Data XBindStmtRn Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> XBindStmtRn -> c XBindStmtRn #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c XBindStmtRn #

toConstr :: XBindStmtRn -> Constr #

dataTypeOf :: XBindStmtRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c XBindStmtRn) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c XBindStmtRn) #

gmapT :: (forall b. Data b => b -> b) -> XBindStmtRn -> XBindStmtRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> XBindStmtRn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> XBindStmtRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> XBindStmtRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> XBindStmtRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> XBindStmtRn -> m XBindStmtRn #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> XBindStmtRn -> m XBindStmtRn #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> XBindStmtRn -> m XBindStmtRn #

data XBindStmtTc Source #

Instances

Instances details
Data XBindStmtTc Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> XBindStmtTc -> c XBindStmtTc #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c XBindStmtTc #

toConstr :: XBindStmtTc -> Constr #

dataTypeOf :: XBindStmtTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c XBindStmtTc) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c XBindStmtTc) #

gmapT :: (forall b. Data b => b -> b) -> XBindStmtTc -> XBindStmtTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> XBindStmtTc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> XBindStmtTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> XBindStmtTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> XBindStmtTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> XBindStmtTc -> m XBindStmtTc #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> XBindStmtTc -> m XBindStmtTc #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> XBindStmtTc -> m XBindStmtTc #

type family XApplicativeStmt x x' Source #

Instances

Instances details
type XApplicativeStmt (GhcPass _1) GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeStmt (GhcPass _1) GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeStmt (GhcPass _1) GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

data AnnTransStmt Source #

Constructors

AnnTransStmt 

Fields

Instances

Instances details
Data AnnTransStmt Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnTransStmt -> c AnnTransStmt #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnTransStmt #

toConstr :: AnnTransStmt -> Constr #

dataTypeOf :: AnnTransStmt -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnTransStmt) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnTransStmt) #

gmapT :: (forall b. Data b => b -> b) -> AnnTransStmt -> AnnTransStmt #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnTransStmt -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnTransStmt -> r #

gmapQ :: (forall d. Data d => d -> u) -> AnnTransStmt -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnTransStmt -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnTransStmt -> m AnnTransStmt #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnTransStmt -> m AnnTransStmt #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnTransStmt -> m AnnTransStmt #

NoAnn AnnTransStmt Source # 
Instance details

Defined in GHC.Hs.Expr

data ApplicativeStmt idL idR Source #

ApplicativeStmt represents an applicative expression built with <$> and <*>. It is generated by the renamer, and is desugared into the appropriate applicative expression by the desugarer, but it is intended to be invisible in error messages.

For full details, see Note [ApplicativeDo] in GHC.Rename.Expr

Constructors

ApplicativeStmt (XApplicativeStmt idL idR) [(SyntaxExpr idR, ApplicativeArg idL)] (Maybe (SyntaxExpr idR)) 

Instances

Instances details
Data (ApplicativeStmt GhcPs GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicativeStmt GhcPs GhcPs -> c (ApplicativeStmt GhcPs GhcPs) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeStmt GhcPs GhcPs) #

toConstr :: ApplicativeStmt GhcPs GhcPs -> Constr #

dataTypeOf :: ApplicativeStmt GhcPs GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeStmt GhcPs GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeStmt GhcPs GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> ApplicativeStmt GhcPs GhcPs -> ApplicativeStmt GhcPs GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeStmt GhcPs GhcPs -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeStmt GhcPs GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicativeStmt GhcPs GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeStmt GhcPs GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcPs GhcPs -> m (ApplicativeStmt GhcPs GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcPs GhcPs -> m (ApplicativeStmt GhcPs GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcPs GhcPs -> m (ApplicativeStmt GhcPs GhcPs) #

Data (ApplicativeStmt GhcPs GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicativeStmt GhcPs GhcRn -> c (ApplicativeStmt GhcPs GhcRn) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeStmt GhcPs GhcRn) #

toConstr :: ApplicativeStmt GhcPs GhcRn -> Constr #

dataTypeOf :: ApplicativeStmt GhcPs GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeStmt GhcPs GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeStmt GhcPs GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> ApplicativeStmt GhcPs GhcRn -> ApplicativeStmt GhcPs GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeStmt GhcPs GhcRn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeStmt GhcPs GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicativeStmt GhcPs GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeStmt GhcPs GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcPs GhcRn -> m (ApplicativeStmt GhcPs GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcPs GhcRn -> m (ApplicativeStmt GhcPs GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcPs GhcRn -> m (ApplicativeStmt GhcPs GhcRn) #

Data (ApplicativeStmt GhcPs GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicativeStmt GhcPs GhcTc -> c (ApplicativeStmt GhcPs GhcTc) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeStmt GhcPs GhcTc) #

toConstr :: ApplicativeStmt GhcPs GhcTc -> Constr #

dataTypeOf :: ApplicativeStmt GhcPs GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeStmt GhcPs GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeStmt GhcPs GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> ApplicativeStmt GhcPs GhcTc -> ApplicativeStmt GhcPs GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeStmt GhcPs GhcTc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeStmt GhcPs GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicativeStmt GhcPs GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeStmt GhcPs GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcPs GhcTc -> m (ApplicativeStmt GhcPs GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcPs GhcTc -> m (ApplicativeStmt GhcPs GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcPs GhcTc -> m (ApplicativeStmt GhcPs GhcTc) #

Data (ApplicativeStmt GhcRn GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicativeStmt GhcRn GhcPs -> c (ApplicativeStmt GhcRn GhcPs) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeStmt GhcRn GhcPs) #

toConstr :: ApplicativeStmt GhcRn GhcPs -> Constr #

dataTypeOf :: ApplicativeStmt GhcRn GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeStmt GhcRn GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeStmt GhcRn GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> ApplicativeStmt GhcRn GhcPs -> ApplicativeStmt GhcRn GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeStmt GhcRn GhcPs -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeStmt GhcRn GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicativeStmt GhcRn GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeStmt GhcRn GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcRn GhcPs -> m (ApplicativeStmt GhcRn GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcRn GhcPs -> m (ApplicativeStmt GhcRn GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcRn GhcPs -> m (ApplicativeStmt GhcRn GhcPs) #

Data (ApplicativeStmt GhcRn GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicativeStmt GhcRn GhcRn -> c (ApplicativeStmt GhcRn GhcRn) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeStmt GhcRn GhcRn) #

toConstr :: ApplicativeStmt GhcRn GhcRn -> Constr #

dataTypeOf :: ApplicativeStmt GhcRn GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeStmt GhcRn GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeStmt GhcRn GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> ApplicativeStmt GhcRn GhcRn -> ApplicativeStmt GhcRn GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeStmt GhcRn GhcRn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeStmt GhcRn GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicativeStmt GhcRn GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeStmt GhcRn GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcRn GhcRn -> m (ApplicativeStmt GhcRn GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcRn GhcRn -> m (ApplicativeStmt GhcRn GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcRn GhcRn -> m (ApplicativeStmt GhcRn GhcRn) #

Data (ApplicativeStmt GhcRn GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicativeStmt GhcRn GhcTc -> c (ApplicativeStmt GhcRn GhcTc) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeStmt GhcRn GhcTc) #

toConstr :: ApplicativeStmt GhcRn GhcTc -> Constr #

dataTypeOf :: ApplicativeStmt GhcRn GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeStmt GhcRn GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeStmt GhcRn GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> ApplicativeStmt GhcRn GhcTc -> ApplicativeStmt GhcRn GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeStmt GhcRn GhcTc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeStmt GhcRn GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicativeStmt GhcRn GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeStmt GhcRn GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcRn GhcTc -> m (ApplicativeStmt GhcRn GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcRn GhcTc -> m (ApplicativeStmt GhcRn GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcRn GhcTc -> m (ApplicativeStmt GhcRn GhcTc) #

Data (ApplicativeStmt GhcTc GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicativeStmt GhcTc GhcPs -> c (ApplicativeStmt GhcTc GhcPs) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeStmt GhcTc GhcPs) #

toConstr :: ApplicativeStmt GhcTc GhcPs -> Constr #

dataTypeOf :: ApplicativeStmt GhcTc GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeStmt GhcTc GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeStmt GhcTc GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> ApplicativeStmt GhcTc GhcPs -> ApplicativeStmt GhcTc GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeStmt GhcTc GhcPs -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeStmt GhcTc GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicativeStmt GhcTc GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeStmt GhcTc GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcTc GhcPs -> m (ApplicativeStmt GhcTc GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcTc GhcPs -> m (ApplicativeStmt GhcTc GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcTc GhcPs -> m (ApplicativeStmt GhcTc GhcPs) #

Data (ApplicativeStmt GhcTc GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicativeStmt GhcTc GhcRn -> c (ApplicativeStmt GhcTc GhcRn) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeStmt GhcTc GhcRn) #

toConstr :: ApplicativeStmt GhcTc GhcRn -> Constr #

dataTypeOf :: ApplicativeStmt GhcTc GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeStmt GhcTc GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeStmt GhcTc GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> ApplicativeStmt GhcTc GhcRn -> ApplicativeStmt GhcTc GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeStmt GhcTc GhcRn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeStmt GhcTc GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicativeStmt GhcTc GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeStmt GhcTc GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcTc GhcRn -> m (ApplicativeStmt GhcTc GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcTc GhcRn -> m (ApplicativeStmt GhcTc GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcTc GhcRn -> m (ApplicativeStmt GhcTc GhcRn) #

Data (ApplicativeStmt GhcTc GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicativeStmt GhcTc GhcTc -> c (ApplicativeStmt GhcTc GhcTc) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeStmt GhcTc GhcTc) #

toConstr :: ApplicativeStmt GhcTc GhcTc -> Constr #

dataTypeOf :: ApplicativeStmt GhcTc GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeStmt GhcTc GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeStmt GhcTc GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> ApplicativeStmt GhcTc GhcTc -> ApplicativeStmt GhcTc GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeStmt GhcTc GhcTc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeStmt GhcTc GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicativeStmt GhcTc GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeStmt GhcTc GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcTc GhcTc -> m (ApplicativeStmt GhcTc GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcTc GhcTc -> m (ApplicativeStmt GhcTc GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeStmt GhcTc GhcTc -> m (ApplicativeStmt GhcTc GhcTc) #

data ApplicativeArg idL Source #

Applicative Argument

Constructors

ApplicativeArgOne 

Fields

  • xarg_app_arg_one :: XApplicativeArgOne idL

    The fail operator, after renaming

    The fail operator is needed if this is a BindStmt where the pattern can fail. E.g.: (Just a) <- stmt The fail operator will be invoked if the pattern match fails. It is also used for guards in MonadComprehensions. The fail operator is Nothing if the pattern match can't fail

  • app_arg_pattern :: LPat idL
     
  • arg_expr :: LHsExpr idL
     
  • is_body_stmt :: Bool

    True = was a BodyStmt, False = was a BindStmt. See Note [Applicative BodyStmt]

ApplicativeArgMany 

Fields

XApplicativeArg !(XXApplicativeArg idL) 

Instances

Instances details
Data (ApplicativeArg GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicativeArg GhcPs -> c (ApplicativeArg GhcPs) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeArg GhcPs) #

toConstr :: ApplicativeArg GhcPs -> Constr #

dataTypeOf :: ApplicativeArg GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeArg GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeArg GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> ApplicativeArg GhcPs -> ApplicativeArg GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcPs -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicativeArg GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeArg GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcPs -> m (ApplicativeArg GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcPs -> m (ApplicativeArg GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcPs -> m (ApplicativeArg GhcPs) #

Data (ApplicativeArg GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicativeArg GhcRn -> c (ApplicativeArg GhcRn) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeArg GhcRn) #

toConstr :: ApplicativeArg GhcRn -> Constr #

dataTypeOf :: ApplicativeArg GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeArg GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeArg GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> ApplicativeArg GhcRn -> ApplicativeArg GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcRn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicativeArg GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeArg GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcRn -> m (ApplicativeArg GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcRn -> m (ApplicativeArg GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcRn -> m (ApplicativeArg GhcRn) #

Data (ApplicativeArg GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicativeArg GhcTc -> c (ApplicativeArg GhcTc) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeArg GhcTc) #

toConstr :: ApplicativeArg GhcTc -> Constr #

dataTypeOf :: ApplicativeArg GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeArg GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeArg GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> ApplicativeArg GhcTc -> ApplicativeArg GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcTc -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicativeArg GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeArg GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcTc -> m (ApplicativeArg GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcTc -> m (ApplicativeArg GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcTc -> m (ApplicativeArg GhcTc) #

OutputableBndrId idL => Outputable (ApplicativeArg (GhcPass idL)) Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: ApplicativeArg (GhcPass idL) -> SDoc Source #

type family XApplicativeArgOne x Source #

Instances

Instances details
type XApplicativeArgOne GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeArgOne GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeArgOne GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XApplicativeArgMany x Source #

Instances

Instances details
type XApplicativeArgMany (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXApplicativeArg x Source #

Instances

Instances details
type XXApplicativeArg (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

pprStmt :: forall (idL :: Pass) (idR :: Pass) body. (OutputableBndrId idL, OutputableBndrId idR, Anno (StmtLR (GhcPass idL) (GhcPass idR) body) ~ SrcSpanAnnA, Outputable body) => StmtLR (GhcPass idL) (GhcPass idR) body -> SDoc Source #

pprBindStmt :: (Outputable pat, Outputable expr) => pat -> expr -> SDoc Source #

pprTransStmt :: Outputable body => Maybe body -> body -> TransForm -> SDoc Source #

ppr_do_stmts :: forall (idL :: Pass) (idR :: Pass) body. (OutputableBndrId idL, OutputableBndrId idR, Anno (StmtLR (GhcPass idL) (GhcPass idR) body) ~ SrcSpanAnnA, Outputable body) => [LStmtLR (GhcPass idL) (GhcPass idR) body] -> SDoc Source #

pprTransformStmt :: forall (p :: Pass). OutputableBndrId p => [IdP (GhcPass p)] -> LHsExpr (GhcPass p) -> Maybe (LHsExpr (GhcPass p)) -> SDoc Source #

pprBy :: Outputable body => Maybe body -> SDoc Source #

pprComp :: forall (p :: Pass) body. (OutputableBndrId p, Outputable body, Anno (StmtLR (GhcPass p) (GhcPass p) body) ~ SrcSpanAnnA) => [LStmt (GhcPass p) body] -> SDoc Source #

pprQuals :: forall (p :: Pass) body. (OutputableBndrId p, Outputable body, Anno (StmtLR (GhcPass p) (GhcPass p) body) ~ SrcSpanAnnA) => [LStmt (GhcPass p) body] -> SDoc Source #

data DelayedSplice Source #

Instances

Instances details
Data DelayedSplice Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DelayedSplice -> c DelayedSplice #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DelayedSplice #

toConstr :: DelayedSplice -> Constr #

dataTypeOf :: DelayedSplice -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DelayedSplice) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DelayedSplice) #

gmapT :: (forall b. Data b => b -> b) -> DelayedSplice -> DelayedSplice #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DelayedSplice -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DelayedSplice -> r #

gmapQ :: (forall d. Data d => d -> u) -> DelayedSplice -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DelayedSplice -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DelayedSplice -> m DelayedSplice #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DelayedSplice -> m DelayedSplice #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DelayedSplice -> m DelayedSplice #

data UntypedSpliceFlavour Source #

Instances

Instances details
Data UntypedSpliceFlavour Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UntypedSpliceFlavour -> c UntypedSpliceFlavour #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UntypedSpliceFlavour #

toConstr :: UntypedSpliceFlavour -> Constr #

dataTypeOf :: UntypedSpliceFlavour -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UntypedSpliceFlavour) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UntypedSpliceFlavour) #

gmapT :: (forall b. Data b => b -> b) -> UntypedSpliceFlavour -> UntypedSpliceFlavour #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UntypedSpliceFlavour -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UntypedSpliceFlavour -> r #

gmapQ :: (forall d. Data d => d -> u) -> UntypedSpliceFlavour -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UntypedSpliceFlavour -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UntypedSpliceFlavour -> m UntypedSpliceFlavour #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UntypedSpliceFlavour -> m UntypedSpliceFlavour #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UntypedSpliceFlavour -> m UntypedSpliceFlavour #

pprMatchInCtxt :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable body) => Match (GhcPass idR) body -> SDoc Source #

pprStmtInCtxt :: forall (idL :: Pass) (idR :: Pass) fn body. (OutputableBndrId idL, OutputableBndrId idR, Outputable fn, Outputable body, Anno (StmtLR (GhcPass idL) (GhcPass idR) body) ~ SrcSpanAnnA) => HsStmtContext fn -> StmtLR (GhcPass idL) (GhcPass idR) body -> SDoc Source #

pprStmtCat :: forall (p :: Pass) body. IsPass p => Stmt (GhcPass p) body -> SDoc Source #

Orphan instances

Outputable HsArrowMatchContext Source # 
Instance details

Outputable HsLamVariant Source # 
Instance details

OutputableBndrId p => Outputable (ArithSeqInfo (GhcPass p)) Source # 
Instance details

Methods

ppr :: ArithSeqInfo (GhcPass p) -> SDoc Source #

UnXRec p => Outputable (DotFieldOcc p) Source # 
Instance details

Methods

ppr :: DotFieldOcc p -> SDoc Source #

(UnXRec p, Outputable (XRec p FieldLabelString)) => Outputable (FieldLabelStrings p) Source # 
Instance details

OutputableBndrId p => Outputable (HsCmd (GhcPass p)) Source # 
Instance details

Methods

ppr :: HsCmd (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (HsCmdTop (GhcPass p)) Source # 
Instance details

Methods

ppr :: HsCmdTop (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (HsExpr (GhcPass p)) Source # 
Instance details

Methods

ppr :: HsExpr (GhcPass p) -> SDoc Source #

Outputable fn => Outputable (HsMatchContext fn) Source # 
Instance details

Methods

ppr :: HsMatchContext fn -> SDoc Source #

Outputable (HsPragE (GhcPass p)) Source # 
Instance details

Methods

ppr :: HsPragE (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (HsQuote (GhcPass p)) Source # 
Instance details

Methods

ppr :: HsQuote (GhcPass p) -> SDoc Source #

Outputable fn => Outputable (HsStmtContext fn) Source # 
Instance details

Methods

ppr :: HsStmtContext fn -> SDoc Source #

(UnXRec p, Outputable (XRec p FieldLabelString)) => OutputableBndr (Located (FieldLabelStrings p)) Source # 
Instance details

(UnXRec p, Outputable (XRec p FieldLabelString)) => OutputableBndr (FieldLabelStrings p) Source # 
Instance details

HasAnnotation (Anno a) => WrapXRec (GhcPass p) a Source # 
Instance details

Methods

wrapXRec :: a -> XRec (GhcPass p) a Source #

(OutputableBndrId pr, Outputable body) => Outputable (Match (GhcPass pr) body) Source # 
Instance details

Methods

ppr :: Match (GhcPass pr) body -> SDoc Source #

(Outputable (StmtLR (GhcPass idL) (GhcPass idL) (LHsExpr (GhcPass idL))), Outputable (XXParStmtBlock (GhcPass idL) (GhcPass idR))) => Outputable (ParStmtBlock (GhcPass idL) (GhcPass idR)) Source # 
Instance details

Methods

ppr :: ParStmtBlock (GhcPass idL) (GhcPass idR) -> SDoc Source #

(OutputableBndrId pl, OutputableBndrId pr, Anno (StmtLR (GhcPass pl) (GhcPass pr) body) ~ SrcSpanAnnA, Outputable body) => Outputable (StmtLR (GhcPass pl) (GhcPass pr) body) Source # 
Instance details

Methods

ppr :: StmtLR (GhcPass pl) (GhcPass pr) body -> SDoc Source #