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

Portabilityportable
Stabilityexperimental
MaintainerNiklas Broberg, d00nibro@dtek.chalmers.se

Language.Haskell.Exts.Syntax

Contents

Description

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

  • multi-parameter type classes with functional dependencies
  • parameters of type class assertions are unrestricted
  • forall types as universal and existential quantification
  • pattern guards
  • implicit parameters
  • generalised algebraic data types
  • template haskell
  • empty data type declarations
  • unboxed tuples
  • regular patterns (HaRP)
  • HSP-style XML expressions and patterns (HSP)

Also worth noting is that (n+k) patterns from Haskell 98 are not supported

Synopsis

Modules

data ExportSpec Source

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

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 {--}

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

Import specification.

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 ConDecl Source

Declaration of a data constructor.

Constructors

ConDecl Name [BangType]

ordinary data constructor

InfixConDecl BangType Name BangType

infix data constructor

RecDecl Name [([Name], BangType)]

record constructor

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

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 | exp = exp. The first expression will be Boolean-valued.

Constructors

GuardedRhs SrcLoc [Stmt] Exp 

Class Assertions and Contexts

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.

Types

data Type Source

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

Constructors

TyForall (Maybe [TyVarBind]) Context 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 | TyPred Asst -- ^ assertion of an implicit parameter

TyInfix Type QName Type

infix type constructor

TyKind Type Kind

type with explicit kind signature

data Boxed Source

Constructors

Boxed 
Unboxed 

Expressions

data Exp Source

Haskell expressions.

Notes:

  • Because it is difficult for parsers to distinguish patterns from expressions, they typically parse them in the same way and then check that they have the appropriate form. Hence the expression type includes some forms that are found only in patterns. After these checks, these constructors should not be used.
  • The parser does not take precedence and associativity into account, so it will leave InfixApps associated to the left.
  • The Language.Haskell.Exts.Pretty.Pretty instance for Exp does not add parentheses in printing.

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

Lambda SrcLoc [Pat] Exp

lambda expression

Let Binds Exp

local declarations with let

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

List [Exp]

list expression

Paren Exp

parenthesized 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

EnumFromTo Exp Exp

bounded arithmetic sequence, incrementing by 1

EnumFromThen Exp Exp

unbounded arithmetic sequence, with first two elements given

EnumFromThenTo Exp Exp Exp

bounded arithmetic sequence, with first two elements given

ListComp Exp [QualStmt]

list comprehension

ParComp Exp [[QualStmt]]

parallel list comprehension

ExpTypeSig SrcLoc Exp Type

expression type signature Template Haskell

VarQuote QName

'x

TypQuote QName

''T

BracketExp Bracket 
SpliceExp Splice 
QuasiQuote String String
$name| string |
XTag SrcLoc XName [XAttr] (Maybe Exp) [Exp] 
XETag SrcLoc XName [XAttr] (Maybe Exp) 
XPcdata String 
XExpTag Exp 
CorePragma String 
SCCPragma String 
GenPragma String (Int, Int) (Int, Int) 
Proc Pat Exp

proc pat -> exp

LeftArrApp Exp Exp

exp -< exp

RightArrApp Exp Exp

exp >- exp

LeftArrHighApp Exp Exp

exp -<< exp

RightArrHighApp Exp Exp

exp >>- exp

data Stmt Source

This type represents both stmt in a do-expression, and qual in a list comprehension, as well as 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, a guard expression

LetStmt Binds

local bindings

RecStmt [Stmt] 

data QualStmt Source

This type represents a qual in a list comprehension, which could potentially be a transform of the kind enabled by TransformListComp.

Constructors

QualStmt Stmt

an ordinary statement qualifier

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 Alt Source

An alt in a case expression.

data GuardedAlt Source

A guarded alternative | stmt, ... , stmt -> exp.

Constructors

GuardedAlt SrcLoc [Stmt] 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 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

PAsPat Name Pat

@-pattern

PWildCard

wildcard pattern (_)

PIrrPat Pat

irrefutable pattern (~)

PatTypeSig SrcLoc Pat Type

pattern type signature

PViewPat Exp Pat

view patterns of the form (e -> p) HaRP

PRPat [RPat]

regular pattern (HaRP) Hsx

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

XML tag pattern

PXETag SrcLoc XName [PXAttr] (Maybe Pat)

XML singleton tag pattern

PXPcdata String

XML PCDATA pattern

PXPatTag Pat

XML embedded pattern

PXRPats [RPat]

XML regular list pattern

PExplTypeArg QName Type

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

PQuasiQuote String String
$name| string |
PBangPat Pat

f !x = ...

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

GHC unboxed integer literal

PrimWord Integer

GHC unboxed word literal

PrimFloat Rational

GHC unboxed float literal

PrimDouble Rational

GHC unboxed double literal

PrimChar Char

GHC unboxed character literal

PrimString String

GHC 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 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.

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

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

This type is used to represent implicit parameter names.

Constructors

IPDup String 
IPLin String 

Template Haskell

HaRP

data RPat Source

An entity in a regular pattern (HaRP)

data RPatOp Source

A regular pattern operator (HaRP)

Hsx

data PXAttr Source

An XML attribute in an XML tag pattern

Constructors

PXAttr XName Pat 

FFI

Pragmas

Builtin names

Modules

Main function of a program

Constructors

Special identifiers

Type constructors

Source coordinates

data SrcLoc Source

A position in the source.

Constructors

SrcLoc