ghc-7.6.2: The GHC API

Safe HaskellNone

HsExpr

Contents

Description

Abstract Haskell syntax for expressions.

Synopsis

Expressions proper

type PostTcExpr = HsExpr IdSource

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 idSource

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

type SyntaxTable id = [(Name, SyntaxExpr id)]Source

Currently used only for CmdTop (sigh)

  • Before the renamer, this list is noSyntaxTable
  • After the renamer, it takes the form [(std_name, HsVar actual_name)] For example, for the return op of a monad
  • normal case: (GHC.Base.return, HsVar GHC.Base.return)
  • with rebindable syntax: (GHC.Base.return, return_22) where return_22 is whatever return is in scope
  • After the type checker, it takes the form [(std_name, expression)] where expression is the evidence for the method

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) 
HsLamCase PostTcType (MatchGroup id) 
HsApp (LHsExpr id) (LHsExpr id) 
OpApp (LHsExpr id) (LHsExpr id) Fixity (LHsExpr id) 
NegApp (LHsExpr id) (SyntaxExpr id) 
HsPar (LHsExpr id) 
SectionL (LHsExpr id) (LHsExpr id) 
SectionR (LHsExpr id) (LHsExpr id) 
ExplicitTuple [HsTupArg id] Boxity 
HsCase (LHsExpr id) (MatchGroup id) 
HsIf (Maybe (SyntaxExpr id)) (LHsExpr id) (LHsExpr id) (LHsExpr id) 
HsMultiIf PostTcType [LGRHS id] 
HsLet (HsLocalBinds id) (LHsExpr id) 
HsDo (HsStmtContext Name) [LStmt id] PostTcType 
ExplicitList PostTcType [LHsExpr id] 
ExplicitPArr PostTcType [LHsExpr id] 
RecordCon (Located id) PostTcExpr (HsRecordBinds id) 
RecordUpd (LHsExpr id) (HsRecordBinds id) [DataCon] [PostTcType] [PostTcType] 
ExprWithTySig (LHsExpr id) (LHsType id) 
ExprWithTySigOut (LHsExpr id) (LHsType Name) 
ArithSeq PostTcExpr (ArithSeqInfo id) 
PArrSeq PostTcExpr (ArithSeqInfo id) 
HsSCC FastString (LHsExpr id) 
HsCoreAnn FastString (LHsExpr id) 
HsBracket (HsBracket id) 
HsBracketOut (HsBracket Name) [PendingSplice] 
HsSpliceE (HsSplice id) 
HsQuasiQuoteE (HsQuasiQuote id) 
HsProc (LPat id) (LHsCmdTop id) 
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) 

Instances

data HsTupArg id Source

Constructors

Present (LHsExpr id) 
Missing PostTcType 

Instances

ppr_expr :: forall id. OutputableBndr id => HsExpr id -> SDocSource

type HsCmd id = HsExpr idSource

type LHsCmd id = LHsExpr idSource

data MatchGroup id Source

Constructors

MatchGroup [LMatch id] PostTcType 

Instances

type LMatch id = Located (Match id)Source

data Match id Source

Constructors

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

Instances

Typeable1 Match 
Data id => Data (Match id) 

data GRHSs id Source

GRHSs are used both for pattern bindings and for Matches

Constructors

GRHSs 

Fields

grhssGRHSs :: [LGRHS id]

Guarded RHSs

grhssLocalBinds :: HsLocalBinds id

The where clause

Instances

Typeable1 GRHSs 
Data id => Data (GRHSs id) 

type LGRHS id = Located (GRHS id)Source

data GRHS id Source

Guarded Right Hand Side.

Constructors

GRHS [LStmt id] (LHsExpr id) 

Instances

Typeable1 GRHS 
Data id => Data (GRHS id) 

pprPatBind :: forall bndr id. (OutputableBndr bndr, OutputableBndr id) => LPat bndr -> GRHSs id -> SDocSource

type LStmt id = Located (StmtLR id id)Source

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

type Stmt id = StmtLR id idSource

data StmtLR idL idR Source

Instances

Typeable2 StmtLR 
(Data idL, Data idR) => Data (StmtLR idL idR) 
(OutputableBndr idL, OutputableBndr idR) => Outputable (StmtLR idL idR) 

data ParStmtBlock idL idR Source

Constructors

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

Instances

data HsSplice id Source

Constructors

HsSplice id (LHsExpr id) 

data HsBracket id Source

Constructors

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