ghc-8.0.0.20160204: The GHC API

Safe HaskellNone
LanguageHaskell2010

HsExpr

Contents

Description

Abstract Haskell syntax for expressions.

Synopsis

Expressions proper

type LHsExpr id Source

Arguments

 = Located (HsExpr id)

May have AnnKeywordId : AnnComma when in a list

type PostTcExpr = HsExpr Id Source

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

type PostTcTable = [(Name, PostTcExpr)] Source

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

data SyntaxExpr id Source

SyntaxExpr is like PostTcExpr, but it's filled in a little earlier, by the renamer. It's used for rebindable syntax.

E.g. (>>=) is filled in before the renamer by the appropriate Name for (>>=), and then instantiated by the type checker with its type args etc

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. This could be defined using PostRn and PostTc and such, but it's harder to get it all to work out that way. (noSyntaxExpr is hard to write, for example.)

Instances

DataId id => Data (SyntaxExpr id) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SyntaxExpr id -> c (SyntaxExpr id) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SyntaxExpr id) Source

toConstr :: SyntaxExpr id -> Constr Source

dataTypeOf :: SyntaxExpr id -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c (SyntaxExpr id)) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SyntaxExpr id)) Source

gmapT :: (forall b. Data b => b -> b) -> SyntaxExpr id -> SyntaxExpr id Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SyntaxExpr id -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SyntaxExpr id -> r Source

gmapQ :: (forall d. Data d => d -> u) -> SyntaxExpr id -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> SyntaxExpr id -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SyntaxExpr id -> m (SyntaxExpr id) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SyntaxExpr id -> m (SyntaxExpr id) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SyntaxExpr id -> m (SyntaxExpr id) Source

OutputableBndr id => Outputable (SyntaxExpr id) 

noExpr :: HsExpr id Source

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

mkRnSyntaxExpr :: Name -> SyntaxExpr Name Source

Make a 'SyntaxExpr Name' (the "rn" is because this is used in the renamer), missing its HsWrappers.

type CmdSyntaxTable id = [(Name, HsExpr id)] Source

data HsExpr id Source

A Haskell expression.

Constructors

HsVar (Located id)

Variable

HsUnboundVar OccName

Unbound variable; also used for "holes" _, or _x. Turned from HsVar to HsUnboundVar by the renamer, when it finds an out-of-scope variable Turned into HsVar by type checker, to support deferred type errors. (The HsUnboundVar only has an OccName.)

HsRecFld (AmbiguousFieldOcc id)

Variable pointing to record selector

HsOverLabel FastString

Overloaded label (See Note [Overloaded labels] in GHC.OverloadedLabels)

HsIPVar HsIPName

Implicit parameter

HsOverLit (HsOverLit id)

Overloaded literals

HsLit HsLit

Simple (non-overloaded) literals

HsLam (MatchGroup id (LHsExpr id))

Lambda abstraction. Currently always a single match

HsLamCase (PostTc id Type) (MatchGroup id (LHsExpr id))

Lambda-case

HsApp (LHsExpr id) (LHsExpr id)

Application

OpApp (LHsExpr id) (LHsExpr id) (PostRn id Fixity) (LHsExpr id)

Operator applications: NB Bracketed ops such as (+) come out as Vars.

NegApp (LHsExpr id) (SyntaxExpr id)

Negation operator. Contains the negated expression and the name of negate

HsPar (LHsExpr id)

Parenthesised expr; see Note [Parens in HsSyn]

SectionL (LHsExpr id) (LHsExpr id) 
SectionR (LHsExpr id) (LHsExpr id) 
ExplicitTuple [LHsTupArg id] Boxity

Used for explicit tuples and sections thereof

HsCase (LHsExpr id) (MatchGroup id (LHsExpr id))
HsIf (Maybe (SyntaxExpr id)) (LHsExpr id) (LHsExpr id) (LHsExpr id)
HsMultiIf (PostTc id Type) [LGRHS id (LHsExpr id)]

Multi-way if

HsLet (Located (HsLocalBinds id)) (LHsExpr id)

let(rec)

HsDo (HsStmtContext Name) (Located [ExprLStmt id]) (PostTc id Type)
ExplicitList (PostTc id Type) (Maybe (SyntaxExpr id)) [LHsExpr id]

Syntactic list: [a,b,c,...]

ExplicitPArr (PostTc id Type) [LHsExpr id]

Syntactic parallel array: [:e1, ..., en:]

RecordCon

Record construction

RecordUpd

Record update

ExprWithTySig (LHsExpr id) (LHsSigWcType id)

Expression with an explicit type signature. e :: type

ExprWithTySigOut (LHsExpr id) (LHsSigWcType Name) 
ArithSeq PostTcExpr (Maybe (SyntaxExpr id)) (ArithSeqInfo id)

Arithmetic sequence

PArrSeq PostTcExpr (ArithSeqInfo id)

Arithmetic sequence for parallel array

[:e1..e2:] or [:e1, e2..e3:]
HsSCC SourceText StringLiteral (LHsExpr id)
HsCoreAnn SourceText StringLiteral (LHsExpr id)
HsBracket (HsBracket id)
HsRnBracketOut (HsBracket Name) [PendingRnSplice] 
HsTcBracketOut (HsBracket Name) [PendingTcSplice] 
HsSpliceE (HsSplice id)
HsProc (LPat id) (LHsCmdTop id)

proc notation for Arrows

HsStatic (LHsExpr id)
HsArrApp (LHsExpr id) (LHsExpr id) (PostTc id Type) HsArrAppType Bool
HsArrForm (LHsExpr id) (Maybe Fixity) [LHsCmdTop id]
HsTick (Tickish id) (LHsExpr id) 
HsBinTick Int Int (LHsExpr id) 
HsTickPragma SourceText (StringLiteral, (Int, Int), (Int, Int)) ((SourceText, SourceText), (SourceText, SourceText)) (LHsExpr id)
EWildPat 
EAsPat (Located id) (LHsExpr id)
EViewPat (LHsExpr id) (LHsExpr id)
ELazyPat (LHsExpr id)
HsType (LHsWcType id)

Use for type application in expressions. AnnKeywordId : AnnAt

HsTypeOut (LHsWcType Name) 
HsWrap HsWrapper (HsExpr id) 

Instances

DataId id => Data (HsExpr id) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsExpr id -> c (HsExpr id) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsExpr id) Source

toConstr :: HsExpr id -> Constr Source

dataTypeOf :: HsExpr id -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c (HsExpr id)) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsExpr id)) Source

gmapT :: (forall b. Data b => b -> b) -> HsExpr id -> HsExpr id Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr id -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr id -> r Source

gmapQ :: (forall d. Data d => d -> u) -> HsExpr id -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsExpr id -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsExpr id -> m (HsExpr id) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr id -> m (HsExpr id) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr id -> m (HsExpr id) Source

OutputableBndr id => Outputable (HsExpr id) 

Methods

ppr :: HsExpr id -> SDoc Source

pprPrec :: Rational -> HsExpr id -> SDoc Source

type LHsTupArg id = Located (HsTupArg id) Source

HsTupArg is used for tuple sections (,a,) is represented by ExplicitTuple [Missing ty1, Present a, Missing ty3] Which in turn stands for (x:ty1 y:ty2. (x,a,y))

data HsTupArg id Source

Constructors

Present (LHsExpr id)

The argument

Missing (PostTc id Type)

The argument is missing, but this is its type

Instances

DataId id => Data (HsTupArg id) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTupArg id -> c (HsTupArg id) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTupArg id) Source

toConstr :: HsTupArg id -> Constr Source

dataTypeOf :: HsTupArg id -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c (HsTupArg id)) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTupArg id)) Source

gmapT :: (forall b. Data b => b -> b) -> HsTupArg id -> HsTupArg id Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg id -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg id -> r Source

gmapQ :: (forall d. Data d => d -> u) -> HsTupArg id -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTupArg id -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTupArg id -> m (HsTupArg id) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg id -> m (HsTupArg id) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg id -> m (HsTupArg id) Source

ppr_expr :: forall id. OutputableBndr id => HsExpr id -> SDoc Source

type LHsCmd id = Located (HsCmd id) Source

data HsCmd id Source

Instances

DataId id => Data (HsCmd id) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsCmd id -> c (HsCmd id) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmd id) Source

toConstr :: HsCmd id -> Constr Source

dataTypeOf :: HsCmd id -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmd id)) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmd id)) Source

gmapT :: (forall b. Data b => b -> b) -> HsCmd id -> HsCmd id Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd id -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd id -> r Source

gmapQ :: (forall d. Data d => d -> u) -> HsCmd id -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmd id -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmd id -> m (HsCmd id) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd id -> m (HsCmd id) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd id -> m (HsCmd id) Source

OutputableBndr id => Outputable (HsCmd id) 

Methods

ppr :: HsCmd id -> SDoc Source

pprPrec :: Rational -> HsCmd id -> SDoc Source

data HsArrAppType Source

Instances

Data HsArrAppType 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsArrAppType -> c HsArrAppType Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsArrAppType Source

toConstr :: HsArrAppType -> Constr Source

dataTypeOf :: HsArrAppType -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c HsArrAppType) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsArrAppType) Source

gmapT :: (forall b. Data b => b -> b) -> HsArrAppType -> HsArrAppType Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArrAppType -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArrAppType -> r Source

gmapQ :: (forall d. Data d => d -> u) -> HsArrAppType -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArrAppType -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArrAppType -> m HsArrAppType Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrAppType -> m HsArrAppType Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrAppType -> m HsArrAppType Source

type LHsCmdTop id = Located (HsCmdTop id) Source

Top-level command, introducing a new arrow. This may occur inside a proc (where the stack is empty) or as an argument of a command-forming operator.

data HsCmdTop id Source

Constructors

HsCmdTop (LHsCmd id) (PostTc id Type) (PostTc id Type) (CmdSyntaxTable id) 

Instances

DataId id => Data (HsCmdTop id) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsCmdTop id -> c (HsCmdTop id) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmdTop id) Source

toConstr :: HsCmdTop id -> Constr Source

dataTypeOf :: HsCmdTop id -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmdTop id)) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmdTop id)) Source

gmapT :: (forall b. Data b => b -> b) -> HsCmdTop id -> HsCmdTop id Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop id -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop id -> r Source

gmapQ :: (forall d. Data d => d -> u) -> HsCmdTop id -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmdTop id -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmdTop id -> m (HsCmdTop id) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop id -> m (HsCmdTop id) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop id -> m (HsCmdTop id) Source

OutputableBndr id => Outputable (HsCmdTop id) 

ppr_cmd :: forall id. OutputableBndr id => HsCmd id -> SDoc Source

data MatchGroup id body Source

Constructors

MG 

Fields

Instances

(Data body, DataId id) => Data (MatchGroup id body) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup id body -> c (MatchGroup id body) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup id body) Source

toConstr :: MatchGroup id body -> Constr Source

dataTypeOf :: MatchGroup id body -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup id body)) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup id body)) Source

gmapT :: (forall b. Data b => b -> b) -> MatchGroup id body -> MatchGroup id body Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup id body -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup id body -> r Source

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup id body -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup id body -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup id body -> m (MatchGroup id body) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup id body -> m (MatchGroup id body) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup id body -> m (MatchGroup id body) Source

type LMatch id body = Located (Match id body) Source

May have AnnKeywordId : AnnSemi when in a list

data Match id body Source

Constructors

Match 

Fields

Instances

(Data body, DataId id) => Data (Match id body) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match id body -> c (Match id body) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match id body) Source

toConstr :: Match id body -> Constr Source

dataTypeOf :: Match id body -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c (Match id body)) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match id body)) Source

gmapT :: (forall b. Data b => b -> b) -> Match id body -> Match id body Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match id body -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match id body -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Match id body -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match id body -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match id body -> m (Match id body) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match id body -> m (Match id body) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match id body -> m (Match id body) Source

data MatchFixity id Source

When a Match is part of a FunBind, it captures one complete equation for the function. As such it has the function name, and its fixity.

Instances

DataId id => Data (MatchFixity id) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchFixity id -> c (MatchFixity id) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchFixity id) Source

toConstr :: MatchFixity id -> Constr Source

dataTypeOf :: MatchFixity id -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c (MatchFixity id)) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchFixity id)) Source

gmapT :: (forall b. Data b => b -> b) -> MatchFixity id -> MatchFixity id Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchFixity id -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchFixity id -> r Source

gmapQ :: (forall d. Data d => d -> u) -> MatchFixity id -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchFixity id -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchFixity id -> m (MatchFixity id) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchFixity id -> m (MatchFixity id) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchFixity id -> m (MatchFixity id) Source

isSingletonMatchGroup :: MatchGroup id body -> Bool Source

Is there only one RHS in this group?

hsLMatchPats :: LMatch id body -> [LPat id] Source

data GRHSs id body Source

GRHSs are used both for pattern bindings and for Matches

Constructors

GRHSs 

Fields

Instances

(Data body, DataId id) => Data (GRHSs id body) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs id body -> c (GRHSs id body) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs id body) Source

toConstr :: GRHSs id body -> Constr Source

dataTypeOf :: GRHSs id body -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs id body)) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs id body)) Source

gmapT :: (forall b. Data b => b -> b) -> GRHSs id body -> GRHSs id body Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs id body -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs id body -> r Source

gmapQ :: (forall d. Data d => d -> u) -> GRHSs id body -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs id body -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs id body -> m (GRHSs id body) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs id body -> m (GRHSs id body) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs id body -> m (GRHSs id body) Source

type LGRHS id body = Located (GRHS id body) Source

data GRHS id body Source

Guarded Right Hand Side.

Constructors

GRHS [GuardLStmt id] body 

Instances

(Data body, DataId id) => Data (GRHS id body) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS id body -> c (GRHS id body) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS id body) Source

toConstr :: GRHS id body -> Constr Source

dataTypeOf :: GRHS id body -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS id body)) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS id body)) Source

gmapT :: (forall b. Data b => b -> b) -> GRHS id body -> GRHS id body Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS id body -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS id body -> r Source

gmapQ :: (forall d. Data d => d -> u) -> GRHS id body -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS id body -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS id body -> m (GRHS id body) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS id body -> m (GRHS id body) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS id body -> m (GRHS id body) Source

pprFunBind :: (OutputableBndr idL, OutputableBndr idR, Outputable body) => idL -> MatchGroup idR body -> SDoc Source

pprPatBind :: forall bndr id body. (OutputableBndr bndr, OutputableBndr id, Outputable body) => LPat bndr -> GRHSs id body -> SDoc Source

pprGRHSs :: (OutputableBndr idR, Outputable body) => HsMatchContext idL -> GRHSs idR body -> SDoc Source

pprGRHS :: (OutputableBndr idR, Outputable body) => HsMatchContext idL -> GRHS idR body -> SDoc Source

pp_rhs :: Outputable body => HsMatchContext idL -> body -> SDoc Source

type LStmt id body = Located (StmtLR id id body) Source

type LStmtLR idL idR body = Located (StmtLR idL idR body) Source

type Stmt id body = StmtLR id id body Source

type CmdLStmt id = LStmt id (LHsCmd id) Source

type CmdStmt id = Stmt id (LHsCmd id) Source

type ExprLStmt id = LStmt id (LHsExpr id) Source

type ExprStmt id = Stmt id (LHsExpr id) Source

type GuardLStmt id = LStmt id (LHsExpr id) Source

type GuardStmt id = Stmt id (LHsExpr id) Source

type GhciLStmt id = LStmt id (LHsExpr id) Source

type GhciStmt id = Stmt id (LHsExpr id) Source

data StmtLR idL idR body Source

API Annotations when in qualifier lists or guards - AnnKeywordId : AnnVbar, AnnComma,AnnThen, AnnBy,AnnBy, AnnGroup,AnnUsing

Constructors

LastStmt body Bool (SyntaxExpr idR) 
BindStmt (LPat idL) body (SyntaxExpr idR) (SyntaxExpr idR) (PostTc idR Type) 
ApplicativeStmt [(SyntaxExpr idR, ApplicativeArg idL idR)] (Maybe (SyntaxExpr idR)) (PostTc idR Type)

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 RnExpr

BodyStmt body (SyntaxExpr idR) (SyntaxExpr idR) (PostTc idR Type) 
LetStmt (Located (HsLocalBindsLR idL idR))
ParStmt [ParStmtBlock idL idR] (HsExpr idR) (SyntaxExpr idR) (PostTc idR Type) 
TransStmt 

Fields

RecStmt

Instances

(Data body, DataId idL, DataId idR) => Data (StmtLR idL idR body) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR idL idR body -> c (StmtLR idL idR body) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR idL idR body) Source

toConstr :: StmtLR idL idR body -> Constr Source

dataTypeOf :: StmtLR idL idR body -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR idL idR body)) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR idL idR body)) Source

gmapT :: (forall b. Data b => b -> b) -> StmtLR idL idR body -> StmtLR idL idR body Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR idL idR body -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR idL idR body -> r Source

gmapQ :: (forall d. Data d => d -> u) -> StmtLR idL idR body -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR idL idR body -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR idL idR body -> m (StmtLR idL idR body) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR idL idR body -> m (StmtLR idL idR body) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR idL idR body -> m (StmtLR idL idR body) Source

(OutputableBndr idL, OutputableBndr idR, Outputable body) => Outputable (StmtLR idL idR body) 

Methods

ppr :: StmtLR idL idR body -> SDoc Source

pprPrec :: Rational -> StmtLR idL idR body -> SDoc Source

data TransForm Source

Constructors

ThenForm 
GroupForm 

Instances

Data TransForm 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TransForm -> c TransForm Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TransForm Source

toConstr :: TransForm -> Constr Source

dataTypeOf :: TransForm -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c TransForm) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TransForm) Source

gmapT :: (forall b. Data b => b -> b) -> TransForm -> TransForm Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TransForm -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TransForm -> r Source

gmapQ :: (forall d. Data d => d -> u) -> TransForm -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> TransForm -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TransForm -> m TransForm Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TransForm -> m TransForm Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TransForm -> m TransForm Source

data ParStmtBlock idL idR Source

Constructors

ParStmtBlock [ExprLStmt idL] [idR] (SyntaxExpr idR) 

Instances

(DataId idL, DataId idR) => Data (ParStmtBlock idL idR) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParStmtBlock idL idR -> c (ParStmtBlock idL idR) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParStmtBlock idL idR) Source

toConstr :: ParStmtBlock idL idR -> Constr Source

dataTypeOf :: ParStmtBlock idL idR -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c (ParStmtBlock idL idR)) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParStmtBlock idL idR)) Source

gmapT :: (forall b. Data b => b -> b) -> ParStmtBlock idL idR -> ParStmtBlock idL idR Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock idL idR -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock idL idR -> r Source

gmapQ :: (forall d. Data d => d -> u) -> ParStmtBlock idL idR -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParStmtBlock idL idR -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParStmtBlock idL idR -> m (ParStmtBlock idL idR) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock idL idR -> m (ParStmtBlock idL idR) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock idL idR -> m (ParStmtBlock idL idR) Source

OutputableBndr idL => Outputable (ParStmtBlock idL idR) 

Methods

ppr :: ParStmtBlock idL idR -> SDoc Source

pprPrec :: Rational -> ParStmtBlock idL idR -> SDoc Source

data ApplicativeArg idL idR Source

Constructors

ApplicativeArgOne (LPat idL) (LHsExpr idL) 
ApplicativeArgMany [ExprLStmt idL] (HsExpr idL) (LPat idL) 

Instances

(DataId idL, DataId idR) => Data (ApplicativeArg idL idR) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicativeArg idL idR -> c (ApplicativeArg idL idR) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeArg idL idR) Source

toConstr :: ApplicativeArg idL idR -> Constr Source

dataTypeOf :: ApplicativeArg idL idR -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeArg idL idR)) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeArg idL idR)) Source

gmapT :: (forall b. Data b => b -> b) -> ApplicativeArg idL idR -> ApplicativeArg idL idR Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg idL idR -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg idL idR -> r Source

gmapQ :: (forall d. Data d => d -> u) -> ApplicativeArg idL idR -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeArg idL idR -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeArg idL idR -> m (ApplicativeArg idL idR) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg idL idR -> m (ApplicativeArg idL idR) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg idL idR -> m (ApplicativeArg idL idR) Source

pprStmt :: forall idL idR body. (OutputableBndr idL, OutputableBndr idR, Outputable body) => StmtLR idL idR body -> SDoc Source

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

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

pprDo :: (OutputableBndr id, Outputable body) => HsStmtContext any -> [LStmt id body] -> SDoc Source

ppr_do_stmts :: (OutputableBndr idL, OutputableBndr idR, Outputable body) => [LStmtLR idL idR body] -> SDoc Source

pprComp :: (OutputableBndr id, Outputable body) => [LStmt id body] -> SDoc Source

pprQuals :: (OutputableBndr id, Outputable body) => [LStmt id body] -> SDoc Source

data HsSplice id Source

Instances

DataId id => Data (HsSplice id) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSplice id -> c (HsSplice id) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSplice id) Source

toConstr :: HsSplice id -> Constr Source

dataTypeOf :: HsSplice id -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c (HsSplice id)) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSplice id)) Source

gmapT :: (forall b. Data b => b -> b) -> HsSplice id -> HsSplice id Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSplice id -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSplice id -> r Source

gmapQ :: (forall d. Data d => d -> u) -> HsSplice id -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSplice id -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSplice id -> m (HsSplice id) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplice id -> m (HsSplice id) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplice id -> m (HsSplice id) Source

OutputableBndr id => Outputable (HsSplice id) 

data PendingRnSplice Source

Instances

Data PendingRnSplice 

Methods

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

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

toConstr :: PendingRnSplice -> Constr Source

dataTypeOf :: PendingRnSplice -> DataType Source

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

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

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

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

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

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

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

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

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

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

Outputable PendingRnSplice 

data UntypedSpliceFlavour Source

Instances

Data UntypedSpliceFlavour 

Methods

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

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

toConstr :: UntypedSpliceFlavour -> Constr Source

dataTypeOf :: UntypedSpliceFlavour -> DataType Source

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

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

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

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

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

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

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

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

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

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

data PendingTcSplice Source

Instances

Data PendingTcSplice 

Methods

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

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

toConstr :: PendingTcSplice -> Constr Source

dataTypeOf :: PendingTcSplice -> DataType Source

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

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

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

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

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

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

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

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

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

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

Outputable PendingTcSplice 

data HsBracket id Source

Constructors

ExpBr (LHsExpr id) 
PatBr (LPat id) 
DecBrL [LHsDecl id] 
DecBrG (HsGroup id) 
TypBr (LHsType id) 
VarBr Bool id 
TExpBr (LHsExpr id) 

Instances

DataId id => Data (HsBracket id) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBracket id -> c (HsBracket id) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBracket id) Source

toConstr :: HsBracket id -> Constr Source

dataTypeOf :: HsBracket id -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c (HsBracket id)) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBracket id)) Source

gmapT :: (forall b. Data b => b -> b) -> HsBracket id -> HsBracket id Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket id -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket id -> r Source

gmapQ :: (forall d. Data d => d -> u) -> HsBracket id -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBracket id -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBracket id -> m (HsBracket id) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket id -> m (HsBracket id) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket id -> m (HsBracket id) Source

OutputableBndr id => Outputable (HsBracket id) 

data ArithSeqInfo id Source

Constructors

From (LHsExpr id) 
FromThen (LHsExpr id) (LHsExpr id) 
FromTo (LHsExpr id) (LHsExpr id) 
FromThenTo (LHsExpr id) (LHsExpr id) (LHsExpr id) 

Instances

DataId id => Data (ArithSeqInfo id) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArithSeqInfo id -> c (ArithSeqInfo id) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ArithSeqInfo id) Source

toConstr :: ArithSeqInfo id -> Constr Source

dataTypeOf :: ArithSeqInfo id -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c (ArithSeqInfo id)) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ArithSeqInfo id)) Source

gmapT :: (forall b. Data b => b -> b) -> ArithSeqInfo id -> ArithSeqInfo id Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo id -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo id -> r Source

gmapQ :: (forall d. Data d => d -> u) -> ArithSeqInfo id -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> ArithSeqInfo id -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArithSeqInfo id -> m (ArithSeqInfo id) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo id -> m (ArithSeqInfo id) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo id -> m (ArithSeqInfo id) Source

OutputableBndr id => Outputable (ArithSeqInfo id) 

data HsMatchContext id Source

Instances

Data id => Data (HsMatchContext id) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsMatchContext id -> c (HsMatchContext id) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsMatchContext id) Source

toConstr :: HsMatchContext id -> Constr Source

dataTypeOf :: HsMatchContext id -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c (HsMatchContext id)) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsMatchContext id)) Source

gmapT :: (forall b. Data b => b -> b) -> HsMatchContext id -> HsMatchContext id Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsMatchContext id -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsMatchContext id -> r Source

gmapQ :: (forall d. Data d => d -> u) -> HsMatchContext id -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsMatchContext id -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsMatchContext id -> m (HsMatchContext id) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsMatchContext id -> m (HsMatchContext id) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsMatchContext id -> m (HsMatchContext id) Source

data HsStmtContext id Source

Instances

Data id => Data (HsStmtContext id) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsStmtContext id -> c (HsStmtContext id) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsStmtContext id) Source

toConstr :: HsStmtContext id -> Constr Source

dataTypeOf :: HsStmtContext id -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c (HsStmtContext id)) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsStmtContext id)) Source

gmapT :: (forall b. Data b => b -> b) -> HsStmtContext id -> HsStmtContext id Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsStmtContext id -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsStmtContext id -> r Source

gmapQ :: (forall d. Data d => d -> u) -> HsStmtContext id -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsStmtContext id -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsStmtContext id -> m (HsStmtContext id) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsStmtContext id -> m (HsStmtContext id) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsStmtContext id -> m (HsStmtContext id) Source