ghc-7.8.3: The GHC API

Safe HaskellNone
LanguageHaskell98

HsExpr

Contents

Description

Abstract Haskell syntax for expressions.

Synopsis

Expressions proper

type LHsExpr id = Located (HsExpr id) Source

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.

type SyntaxExpr id = HsExpr 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

data HsExpr id Source

A Haskell expression.

Constructors

HsVar id

Variable

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 PostTcType (MatchGroup id (LHsExpr id))

Lambda-case

HsApp (LHsExpr id) (LHsExpr id)

Application

OpApp (LHsExpr id) (LHsExpr 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 [HsTupArg 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 PostTcType [LGRHS id (LHsExpr id)]

Multi-way if

HsLet (HsLocalBinds id) (LHsExpr id)

let(rec)

HsDo (HsStmtContext Name) [ExprLStmt id] PostTcType 
ExplicitList PostTcType (Maybe (SyntaxExpr id)) [LHsExpr id]

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

ExplicitPArr PostTcType [LHsExpr id]

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

RecordCon (Located id) PostTcExpr (HsRecordBinds id)

Record construction

RecordUpd (LHsExpr id) (HsRecordBinds id) [DataCon] [PostTcType] [PostTcType]

Record update

ExprWithTySig (LHsExpr id) (LHsType id)

Expression with an explicit type signature. e :: type

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

Arithmetic sequence

PArrSeq PostTcExpr (ArithSeqInfo id)

Arithmetic sequence for parallel array

HsSCC FastString (LHsExpr id) 
HsCoreAnn FastString (LHsExpr id) 
HsBracket (HsBracket id) 
HsRnBracketOut (HsBracket Name) [PendingRnSplice] 
HsTcBracketOut (HsBracket Name) [PendingTcSplice] 
HsSpliceE Bool (HsSplice id) 
HsQuasiQuoteE (HsQuasiQuote id) 
HsProc (LPat id) (LHsCmdTop id)

proc notation for Arrows

HsArrApp (LHsExpr id) (LHsExpr id) PostTcType HsArrAppType Bool 
HsArrForm (LHsExpr id) (Maybe Fixity) [LHsCmdTop id] 
HsTick (Tickish id) (LHsExpr id) 
HsBinTick Int Int (LHsExpr id) 
HsTickPragma (FastString, (Int, Int), (Int, Int)) (LHsExpr id) 
EWildPat 
EAsPat (Located id) (LHsExpr id) 
EViewPat (LHsExpr id) (LHsExpr id) 
ELazyPat (LHsExpr id) 
HsType (LHsType id) 
HsWrap HsWrapper (HsExpr id) 
HsUnboundVar RdrName 

Instances

Data id => Data (HsExpr id) 
OutputableBndr id => Outputable (HsExpr id) 
Typeable (* -> *) HsExpr 

data HsTupArg id Source

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

Constructors

Present (LHsExpr id)

The argument

Missing PostTcType

The argument is missing, but this is its type

Instances

Data id => Data (HsTupArg id) 
Typeable (* -> *) HsTupArg 

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

type LHsCmd id = Located (HsCmd id) Source

data HsCmdTop id Source

Instances

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

data MatchGroup id body Source

Constructors

MG 

Instances

(Data id, Data body) => Data (MatchGroup id body) 
Typeable (* -> * -> *) MatchGroup 

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

data Match id body Source

Constructors

Match [LPat id] (Maybe (LHsType id)) (GRHSs id body) 

Instances

(Data id, Data body) => Data (Match id body) 
Typeable (* -> * -> *) Match 

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

grhssGRHSs :: [LGRHS id body]

Guarded RHSs

grhssLocalBinds :: HsLocalBinds id

The where clause

Instances

(Data id, Data body) => Data (GRHSs id body) 
Typeable (* -> * -> *) GRHSs 

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 id, Data body) => Data (GRHS id body) 
Typeable (* -> * -> *) GRHS 

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

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

pprGRHS :: (OutputableBndr idL, 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

Constructors

LastStmt body (SyntaxExpr idR) 
BindStmt (LPat idL) body (SyntaxExpr idR) (SyntaxExpr idR) 
BodyStmt body (SyntaxExpr idR) (SyntaxExpr idR) PostTcType 
LetStmt (HsLocalBindsLR idL idR) 
ParStmt [ParStmtBlock idL idR] (SyntaxExpr idR) (SyntaxExpr idR) 
TransStmt 

Fields

trS_form :: TransForm
 
trS_stmts :: [ExprLStmt idL]
 
trS_bndrs :: [(idR, idR)]
 
trS_using :: LHsExpr idR
 
trS_by :: Maybe (LHsExpr idR)
 
trS_ret :: SyntaxExpr idR
 
trS_bind :: SyntaxExpr idR
 
trS_fmap :: SyntaxExpr idR
 
RecStmt 

Instances

Typeable (* -> * -> * -> *) StmtLR 
(Data idL, Data idR, Data body) => Data (StmtLR idL idR body) 
(OutputableBndr idL, OutputableBndr idR, Outputable body) => Outputable (StmtLR idL idR body) 

data ParStmtBlock idL idR Source

Constructors

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

Instances

(Data idL, Data idR) => Data (ParStmtBlock idL idR) 
(OutputableBndr idL, OutputableBndr idR) => Outputable (ParStmtBlock idL idR) 
Typeable (* -> * -> *) ParStmtBlock 

pprStmt :: (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

Constructors

HsSplice id (LHsExpr id) 

Instances

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

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