haskell-src-exts-1.13.3: Manipulating Haskell source: abstract syntax, lexer, parser, and pretty-printer

Portabilityportable
Stabilitystable
MaintainerNiklas Broberg, d00nibro@chalmers.se
Safe HaskellSafe-Infered

Language.Haskell.Exts.Syntax

Contents

Description

A suite of datatypes describing the abstract syntax of Haskell 98 http://www.haskell.org/onlinereport/ plus registered extensions, including:

  • multi-parameter type classes with functional dependencies (MultiParamTypeClasses, FunctionalDependencies)
  • parameters of type class assertions are unrestricted (FlexibleContexts)
  • forall types as universal and existential quantification (RankNTypes, ExistentialQuantification, etc)
  • pattern guards (PatternGuards)
  • implicit parameters (ImplicitParameters)
  • generalised algebraic data types (GADTs)
  • template haskell (TemplateHaskell)
  • empty data type declarations (EmptyDataDecls)
  • unboxed tuples (UnboxedTuples)
  • regular patterns (RegularPatterns)
  • HSP-style XML expressions and patterns (XmlSyntax)

Synopsis

Modules

data WarningText Source

Warning text to optionally use in the module header of e.g. a deprecated module.

data ExportSpec Source

An item in a module's export specification.

Constructors

EVar QName

variable

EAbs QName

T: a class or datatype exported abstractly, or a type synonym.

EThingAll QName

T(..): a class exported with all of its methods, or a datatype exported with all of its constructors.

EThingWith QName [CName]

T(C_1,...,C_n): a class exported with some of its methods, or a datatype exported with some of its constructors.

EModuleContents ModuleName

module M: re-export a module.

data ImportDecl Source

An import declaration.

Constructors

ImportDecl 

Fields

importLoc :: SrcLoc

position of the import keyword.

importModule :: ModuleName

name of the module imported.

importQualified :: Bool

imported qualified?

importSrc :: Bool

imported with {-# SOURCE #-}?

importPkg :: Maybe String

imported with explicit package name

importAs :: Maybe ModuleName

optional alias name in an as clause.

importSpecs :: Maybe (Bool, [ImportSpec])

optional list of import specifications. The Bool is True if the names are excluded by hiding.

data ImportSpec Source

An import specification, representing a single explicit item imported (or hidden) from a module.

Constructors

IVar Name

variable

IAbs Name

T: the name of a class, datatype or type synonym.

IThingAll Name

T(..): a class imported with all of its methods, or a datatype imported with all of its constructors.

IThingWith Name [CName]

T(C_1,...,C_n): a class imported with some of its methods, or a datatype imported with some of its constructors.

data Assoc Source

Associativity of an operator.

Constructors

AssocNone

non-associative operator (declared with infix)

AssocLeft

left-associative operator (declared with infixl).

AssocRight

right-associative operator (declared with infixr)

Declarations

data Decl Source

A top-level declaration.

Constructors

TypeDecl SrcLoc Name [TyVarBind] Type

A type declaration

TypeFamDecl SrcLoc Name [TyVarBind] (Maybe Kind)

A type family declaration

DataDecl SrcLoc DataOrNew Context Name [TyVarBind] [QualConDecl] [Deriving]

A data OR newtype declaration

GDataDecl SrcLoc DataOrNew Context Name [TyVarBind] (Maybe Kind) [GadtDecl] [Deriving]

A data OR newtype declaration, GADT style

DataFamDecl SrcLoc Context Name [TyVarBind] (Maybe Kind)

A data family declaration

TypeInsDecl SrcLoc Type Type

A type family instance declaration

DataInsDecl SrcLoc DataOrNew Type [QualConDecl] [Deriving]

A data family instance declaration

GDataInsDecl SrcLoc DataOrNew Type (Maybe Kind) [GadtDecl] [Deriving]

A data family instance declaration, GADT style

ClassDecl SrcLoc Context Name [TyVarBind] [FunDep] [ClassDecl]

A declaration of a type class

InstDecl SrcLoc Context QName [Type] [InstDecl]

An declaration of a type class instance

DerivDecl SrcLoc Context QName [Type]

A standalone deriving declaration

InfixDecl SrcLoc Assoc Int [Op]

A declaration of operator fixity

DefaultDecl SrcLoc [Type]

A declaration of default types

SpliceDecl SrcLoc Exp

A Template Haskell splicing declaration

TypeSig SrcLoc [Name] Type

A type signature declaration

FunBind [Match]

A set of function binding clauses

PatBind SrcLoc Pat (Maybe Type) Rhs Binds

A pattern binding

ForImp SrcLoc CallConv Safety String Name Type

A foreign import declaration

ForExp SrcLoc CallConv String Name Type

A foreign export declaration

RulePragmaDecl SrcLoc [Rule]

A RULES pragma

DeprPragmaDecl SrcLoc [([Name], String)]

A DEPRECATED pragma

WarnPragmaDecl SrcLoc [([Name], String)]

A WARNING pragma

InlineSig SrcLoc Bool Activation QName

An INLINE pragma

InlineConlikeSig SrcLoc Activation QName

An INLINE CONLIKE pragma

SpecSig SrcLoc QName [Type]

A SPECIALISE pragma

SpecInlineSig SrcLoc Bool Activation QName [Type]

A SPECIALISE INLINE pragma

InstSig SrcLoc Context QName [Type]

A SPECIALISE instance pragma

AnnPragma SrcLoc Annotation

An ANN pragma

data Binds Source

A binding group inside a let or where clause.

Constructors

BDecls [Decl]

An ordinary binding group

IPBinds [IPBind]

A binding group for implicit parameters

data IPBind Source

A binding of an implicit parameter.

Constructors

IPBind SrcLoc IPName Exp 

Type classes and instances

data ClassDecl Source

Declarations inside a class declaration.

Constructors

ClsDecl Decl

ordinary declaration

ClsDataFam SrcLoc Context Name [TyVarBind] (Maybe Kind)

declaration of an associated data type

ClsTyFam SrcLoc Name [TyVarBind] (Maybe Kind)

declaration of an associated type synonym

ClsTyDef SrcLoc Type Type

default choice for an associated type synonym

data InstDecl Source

Declarations inside an instance declaration.

Constructors

InsDecl Decl

ordinary declaration

InsType SrcLoc Type Type

an associated type definition

InsData SrcLoc DataOrNew Type [QualConDecl] [Deriving]

an associated data type implementation

InsGData SrcLoc DataOrNew Type (Maybe Kind) [GadtDecl] [Deriving]

an associated data type implemented using GADT style

type Deriving = (QName, [Type])Source

A single derived instance, which may have arguments since it may be a MPTC.

Data type declarations

data DataOrNew Source

A flag stating whether a declaration is a data or newtype declaration.

Constructors

DataType 
NewType 

data ConDecl Source

Declaration of an ordinary data constructor.

Constructors

ConDecl Name [BangType]

ordinary data constructor

InfixConDecl BangType Name BangType

infix data constructor

RecDecl Name [([Name], BangType)]

record constructor

data QualConDecl Source

A single constructor declaration within a data type declaration, which may have an existential quantification binding.

data GadtDecl Source

A single constructor declaration in a GADT data type declaration.

Constructors

GadtDecl SrcLoc Name Type 

data BangType Source

The type of a constructor argument or field, optionally including a strictness annotation.

Constructors

BangedTy Type

strict component, marked with "!"

UnBangedTy Type

non-strict component

UnpackedTy Type

unboxed component, marked with an UNPACK pragma

Function bindings

data Match Source

Clauses of a function binding.

Constructors

Match SrcLoc Name [Pat] (Maybe Type) Rhs Binds 

data Rhs Source

The right hand side of a function or pattern binding.

Constructors

UnGuardedRhs Exp

unguarded right hand side (exp)

GuardedRhss [GuardedRhs]

guarded right hand side (gdrhs)

data GuardedRhs Source

A guarded right hand side | stmts = exp. The guard is a series of statements when using pattern guards, otherwise it will be a single qualifier expression.

Constructors

GuardedRhs SrcLoc [Stmt] Exp 

Class Assertions and Contexts

type Context = [Asst]Source

A context is a set of assertions

data FunDep Source

A functional dependency, given on the form l1 l2 ... ln -> r2 r3 .. rn

Constructors

FunDep [Name] [Name] 

data Asst Source

Class assertions. In Haskell 98, the argument would be a tyvar, but this definition allows multiple parameters, and allows them to be types. Also extended with support for implicit parameters and equality constraints.

Constructors

ClassA QName [Type]

ordinary class assertion

InfixA Type QName Type

class assertion where the class name is given infix

IParam IPName Type

implicit parameter assertion

EqualP Type Type

type equality constraint

Types

data Type Source

A type qualified with a context. An unqualified type has an empty context.

Constructors

TyForall (Maybe [TyVarBind]) Context Type

qualified type

TyFun Type Type

function type

TyTuple Boxed [Type]

tuple type, possibly boxed

TyList Type

list syntax, e.g. [a], as opposed to [] a

TyApp Type Type

application of a type constructor

TyVar Name

type variable

TyCon QName

named type or type constructor

TyParen Type

type surrounded by parentheses

TyInfix Type QName Type

infix type constructor

TyKind Type Kind

type with explicit kind signature

data Boxed Source

Flag denoting whether a tuple is boxed or unboxed.

Constructors

Boxed 
Unboxed 

data Kind Source

An explicit kind annotation.

Constructors

KindStar

*, the kind of types

KindBang

!, the kind of unboxed types

KindFn Kind Kind

->, the kind of a type constructor

KindParen Kind

a kind surrounded by parentheses

KindVar Name

a kind variable (as of yet unsupported by compilers)

data TyVarBind Source

A type variable declaration, optionally with an explicit kind annotation.

Constructors

KindedVar Name Kind

variable binding with kind annotation

UnkindedVar Name

ordinary variable binding

Expressions

data Exp Source

Haskell expressions.

Constructors

Var QName

variable

IPVar IPName

implicit parameter variable

Con QName

data constructor

Lit Literal

literal constant

InfixApp Exp QOp Exp

infix application

App Exp Exp

ordinary application

NegApp Exp

negation expression -exp (unary minus)

Lambda SrcLoc [Pat] Exp

lambda expression

Let Binds Exp

local declarations with let ... in ...

If Exp Exp Exp

if exp then exp else exp

Case Exp [Alt]

case exp of alts

Do [Stmt]

do-expression: the last statement in the list should be an expression.

MDo [Stmt]

mdo-expression

Tuple [Exp]

tuple expression

TupleSection [Maybe Exp]

tuple section expression, e.g. (,,3)

List [Exp]

list expression

Paren Exp

parenthesised expression

LeftSection Exp QOp

left section (exp qop)

RightSection QOp Exp

right section (qop exp)

RecConstr QName [FieldUpdate]

record construction expression

RecUpdate Exp [FieldUpdate]

record update expression

EnumFrom Exp

unbounded arithmetic sequence, incrementing by 1: [from ..]

EnumFromTo Exp Exp

bounded arithmetic sequence, incrementing by 1 [from .. to]

EnumFromThen Exp Exp

unbounded arithmetic sequence, with first two elements given [from, then ..]

EnumFromThenTo Exp Exp Exp

bounded arithmetic sequence, with first two elements given [from, then .. to]

ListComp Exp [QualStmt]

ordinary list comprehension

ParComp Exp [[QualStmt]]

parallel list comprehension

ExpTypeSig SrcLoc Exp Type

expression with explicit type signature

VarQuote QName

'x for template haskell reifying of expressions

TypQuote QName

''T for template haskell reifying of types

BracketExp Bracket

template haskell bracket expression

SpliceExp Splice

template haskell splice expression

QuasiQuote String String

quasi-quotaion: [$name| string |]

XTag SrcLoc XName [XAttr] (Maybe Exp) [Exp]

xml element, with attributes and children

XETag SrcLoc XName [XAttr] (Maybe Exp)

empty xml element, with attributes

XPcdata String

PCDATA child element

XExpTag Exp

escaped haskell expression inside xml

XChildTag SrcLoc [Exp]

children of an xml element

CorePragma String Exp

CORE pragma

SCCPragma String Exp

SCC pragma

GenPragma String (Int, Int) (Int, Int) Exp

GENERATED pragma

Proc SrcLoc Pat Exp

arrows proc: proc pat -> exp

LeftArrApp Exp Exp

arrow application (from left): exp -< exp

RightArrApp Exp Exp

arrow application (from right): exp >- exp

LeftArrHighApp Exp Exp

higher-order arrow application (from left): exp -<< exp

RightArrHighApp Exp Exp

higher-order arrow application (from right): exp >>- exp

data Stmt Source

A statement, representing both a stmt in a do-expression, an ordinary qual in a list comprehension, as well as a stmt in a pattern guard.

Constructors

Generator SrcLoc Pat Exp

a generator: pat <- exp

Qualifier Exp

an exp by itself: in a do-expression, an action whose result is discarded; in a list comprehension and pattern guard, a guard expression

LetStmt Binds

local bindings

RecStmt [Stmt]

a recursive binding group for arrows

data QualStmt Source

A general transqual in a list comprehension, which could potentially be a transform of the kind enabled by TransformListComp.

Constructors

QualStmt Stmt

an ordinary statement

ThenTrans Exp

then exp

ThenBy Exp Exp

then exp by exp

GroupBy Exp

then group by exp

GroupUsing Exp

then group using exp

GroupByUsing Exp Exp

then group by exp using exp

data FieldUpdate Source

An fbind in a labeled construction or update expression.

Constructors

FieldUpdate QName Exp

ordinary label-expresion pair

FieldPun Name

record field pun

FieldWildcard

record field wildcard

data Alt Source

An alt alternative in a case expression.

data GuardedAlts Source

The right-hand sides of a case alternative, which may be a single right-hand side or a set of guarded ones.

Constructors

UnGuardedAlt Exp

-> exp

GuardedAlts [GuardedAlt]

gdpat

data GuardedAlt Source

A guarded case alternative | stmts -> exp.

Constructors

GuardedAlt SrcLoc [Stmt] Exp 

data XAttr Source

An xml attribute, which is a name-expression pair.

Constructors

XAttr XName Exp 

Patterns

data Pat Source

A pattern, to be matched against a value.

Constructors

PVar Name

variable

PLit Literal

literal constant

PNeg Pat

negated pattern

PNPlusK Name Integer

n+k pattern

PInfixApp Pat QName Pat

pattern with an infix data constructor

PApp QName [Pat]

data constructor and argument patterns

PTuple [Pat]

tuple pattern

PList [Pat]

list pattern

PParen Pat

parenthesized pattern

PRec QName [PatField]

labelled pattern, record style

PAsPat Name Pat

@-pattern

PWildCard

wildcard pattern: _

PIrrPat Pat

irrefutable pattern: ~pat

PatTypeSig SrcLoc Pat Type

pattern with type signature

PViewPat Exp Pat

view patterns of the form (exp -> pat)

PRPat [RPat]

regular list pattern

PXTag SrcLoc XName [PXAttr] (Maybe Pat) [Pat]

XML element pattern

PXETag SrcLoc XName [PXAttr] (Maybe Pat)

XML singleton element pattern

PXPcdata String

XML PCDATA pattern

PXPatTag Pat

XML embedded pattern

PXRPats [RPat]

XML regular list pattern

PExplTypeArg QName Type

Explicit generics style type argument e.g. f {| Int |} x = ...

PQuasiQuote String String

quasi quote patter: [$name| string |]

PBangPat Pat

strict (bang) pattern: f !x = ...

data PatField Source

An fpat in a labeled record pattern.

Constructors

PFieldPat QName Pat

ordinary label-pattern pair

PFieldPun Name

record field pun

PFieldWildcard

record field wildcard

data PXAttr Source

An XML attribute in a pattern.

Constructors

PXAttr XName Pat 

data RPat Source

An entity in a regular pattern.

Constructors

RPOp RPat RPatOp

operator pattern, e.g. pat*

RPEither RPat RPat

choice pattern, e.g. (1 | 2)

RPSeq [RPat]

sequence pattern, e.g. (| 1, 2, 3 |)

RPGuard Pat [Stmt]

guarded pattern, e.g. (| p | p < 3 |)

RPCAs Name RPat

non-linear variable binding, e.g. (foo@:(1 | 2))*

RPAs Name RPat

linear variable binding, e.g. foo@(1 | 2)

RPParen RPat

parenthesised pattern, e.g. (2*)

RPPat Pat

an ordinary pattern

data RPatOp Source

A regular pattern operator.

Constructors

RPStar

* = 0 or more

RPStarG

*! = 0 or more, greedy

RPPlus

+ = 1 or more

RPPlusG

+! = 1 or more, greedy

RPOpt

? = 0 or 1

RPOptG

?! = 0 or 1, greedy

Literals

data Literal Source

literal Values of this type hold the abstract value of the literal, not the precise string representation used. For example, 10, 0o12 and 0xa have the same representation.

Constructors

Char Char

character literal

String String

string literal

Int Integer

integer literal

Frac Rational

floating point literal

PrimInt Integer

unboxed integer literal

PrimWord Integer

unboxed word literal

PrimFloat Rational

unboxed float literal

PrimDouble Rational

unboxed double literal

PrimChar Char

unboxed character literal

PrimString String

unboxed string literal

Variables, Constructors and Operators

newtype ModuleName Source

The name of a Haskell module.

Constructors

ModuleName String 

data QName Source

This type is used to represent qualified variables, and also qualified constructors.

Constructors

Qual ModuleName Name

name qualified with a module name

UnQual Name

unqualified local name

Special SpecialCon

built-in constructor with special syntax

data Name Source

This type is used to represent variables, and also constructors.

Constructors

Ident String

varid or conid.

Symbol String

varsym or consym

data QOp Source

Possibly qualified infix operators (qop), appearing in expressions.

Constructors

QVarOp QName

variable operator (qvarop)

QConOp QName

constructor operator (qconop)

data Op Source

Operators appearing in infix declarations are never qualified.

Constructors

VarOp Name

variable operator (varop)

ConOp Name

constructor operator (conop)

Instances

data SpecialCon Source

Constructors with special syntax. These names are never qualified, and always refer to builtin type or data constructors.

Constructors

UnitCon

unit type and data constructor ()

ListCon

list type constructor []

FunCon

function type constructor ->

TupleCon Boxed Int

n-ary tuple type and data constructors (,) etc, possibly boxed (#,#)

Cons

list data constructor (:)

UnboxedSingleCon

unboxed singleton tuple constructor (# #)

data CName Source

A name (cname) of a component of a class or data type in an import or export specification.

Constructors

VarName Name

name of a method or field

ConName Name

name of a data constructor

data IPName Source

An implicit parameter name.

Constructors

IPDup String

?ident, non-linear implicit parameter

IPLin String

%ident, linear implicit parameter

data XName Source

The name of an xml element or attribute, possibly qualified with a namespace.

Template Haskell

data Bracket Source

A template haskell bracket expression.

Constructors

ExpBracket Exp

expression bracket: [| ... |]

PatBracket Pat

pattern bracket: [p| ... |]

TypeBracket Type

type bracket: [t| ... |]

DeclBracket [Decl]

declaration bracket: [d| ... |]

data Splice Source

A template haskell splice expression

Constructors

IdSplice String

variable splice: $var

ParenSplice Exp

parenthesised expression splice: $(exp)

FFI

data Safety Source

The safety of a foreign function call.

Constructors

PlayRisky

unsafe

PlaySafe Bool

safe (False) or threadsafe (True)

data CallConv Source

The calling convention of a foreign function call.

Constructors

StdCall 
CCall 

Pragmas

data ModulePragma Source

A top level options pragma, preceding the module header.

Constructors

LanguagePragma SrcLoc [Name]

LANGUAGE pragma

OptionsPragma SrcLoc (Maybe Tool) String

OPTIONS pragma, possibly qualified with a tool, e.g. OPTIONS_GHC

AnnModulePragma SrcLoc Annotation

ANN pragma with module scope

data Tool Source

Recognised tools for OPTIONS pragmas.

data Rule Source

The body of a RULES pragma.

data RuleVar Source

Variables used in a RULES pragma, optionally annotated with types

data Annotation Source

An annotation through an ANN pragma.

Constructors

Ann Name Exp

An annotation for a declared name.

TypeAnn Name Exp

An annotation for a declared type.

ModuleAnn Exp

An annotation for the defining module.

Builtin names

Modules

Main function of a program

Constructors

Special identifiers

Type constructors

Source coordinates

data SrcLoc Source

A single position in the source.

Constructors

SrcLoc