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

Portabilityportable
Stabilitystable
MaintainerNiklas Broberg, d00nibro@chalmers.se

Language.Haskell.Exts.Annotated.Syntax

Contents

Description

A suite of datatypes describing the (semi-concrete) 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)

All nodes in the syntax tree are annotated with something of a user-definable data type. When parsing, this annotation will contain information about the source location that the particular node comes from.

Synopsis

Modules

data Module l Source

A complete Haskell source module.

Constructors

Module l (Maybe (ModuleHead l)) [OptionPragma l] [ImportDecl l] [Decl l]

an ordinary Haskell module

XmlPage l (ModuleName l) [OptionPragma l] (XName l) [XAttr l] (Maybe (Exp l)) [Exp l]

a module consisting of a single XML document. The ModuleName never appears in the source but is needed for semantic purposes, it will be the same as the file name.

XmlHybrid l (Maybe (ModuleHead l)) [OptionPragma l] [ImportDecl l] [Decl l] (XName l) [XAttr l] (Maybe (Exp l)) [Exp l]

a hybrid module combining an XML document with an ordinary module

Instances

data ModuleHead l Source

The head of a module, including the name and export specification.

Constructors

ModuleHead l (ModuleName l) (Maybe (WarningText l)) (Maybe (ExportSpecList l)) 

data WarningText l Source

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

Constructors

DeprText l String 
WarnText l String 

data ExportSpec l Source

An item in a module's export specification.

Constructors

EVar l (QName l)

variable

EAbs l (QName l)

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

EThingAll l (QName l)

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

EThingWith l (QName l) [CName l]

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

EModuleContents l (ModuleName l)

module M: re-export a module.

data ImportDecl l Source

An import declaration.

Constructors

ImportDecl 

Fields

importAnn :: l

annotation, used by parser for position of the import keyword.

importModule :: ModuleName l

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 l)

optional alias name in an as clause.

importSpecs :: Maybe (ImportSpecList l)

optional list of import specifications.

data ImportSpec l Source

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

Constructors

IVar l (Name l)

variable

IAbs l (Name l)

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

IThingAll l (Name l)

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

IThingWith l (Name l) [CName l]

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

data Assoc l Source

Associativity of an operator.

Constructors

AssocNone l

non-associative operator (declared with infix)

AssocLeft l

left-associative operator (declared with infixl).

AssocRight l

right-associative operator (declared with infixr)

Instances

Declarations

data Decl l Source

A top-level declaration.

Constructors

TypeDecl l (DeclHead l) (Type l)

A type declaration

TypeFamDecl l (DeclHead l) (Maybe (Kind l))

A type family declaration

DataDecl l (DataOrNew l) (Maybe (Context l)) (DeclHead l) [QualConDecl l] (Maybe (Deriving l))

A data OR newtype declaration

GDataDecl l (DataOrNew l) (Maybe (Context l)) (DeclHead l) (Maybe (Kind l)) [GadtDecl l] (Maybe (Deriving l))

A data OR newtype declaration, GADT style

DataFamDecl l (Maybe (Context l)) (DeclHead l) (Maybe (Kind l))

A data family declaration

TypeInsDecl l (Type l) (Type l)

A type family instance declaration

DataInsDecl l (DataOrNew l) (Type l) [QualConDecl l] (Maybe (Deriving l))

A data family instance declaration

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

A data family instance declaration, GADT style

ClassDecl l (Maybe (Context l)) (DeclHead l) [FunDep l] (Maybe [ClassDecl l])

A declaration of a type class

InstDecl l (Maybe (Context l)) (InstHead l) (Maybe [InstDecl l])

An declaration of a type class instance

DerivDecl l (Maybe (Context l)) (InstHead l)

A standalone deriving declaration

InfixDecl l (Assoc l) (Maybe Int) [Op l]

A declaration of operator fixity

DefaultDecl l [Type l]

A declaration of default types

SpliceDecl l (Exp l)

A Template Haskell splicing declaration

TypeSig l [Name l] (Type l)

A type signature declaration

FunBind l [Match l]

A set of function binding clauses

PatBind l (Pat l) (Maybe (Type l)) (Rhs l) (Maybe (Binds l))

A pattern binding

ForImp l (CallConv l) (Maybe (Safety l)) (Maybe String) (Name l) (Type l)

A foreign import declaration

ForExp l (CallConv l) (Maybe String) (Name l) (Type l)

A foreign export declaration

RulePragmaDecl l [Rule l]

A RULES pragma

DeprPragmaDecl l [([Name l], String)]

A DEPRECATED pragma

WarnPragmaDecl l [([Name l], String)]

A WARNING pragma

InlineSig l Bool (Maybe (Activation l)) (QName l)

An INLINE pragma

InlineConlikeSig l (Maybe (Activation l)) (QName l)

An INLINE pragma

SpecSig l (QName l) [Type l]

A SPECIALISE pragma

SpecInlineSig l Bool (Maybe (Activation l)) (QName l) [Type l]

A SPECIALISE INLINE pragma

InstSig l (Maybe (Context l)) (InstHead l)

A SPECIALISE instance pragma

AnnPragma l (Annotation l)

An ANN pragma

Instances

Functor Decl 
Typeable1 Decl 
Annotated Decl 
ExactP Decl 
AppFixity Decl 
Eq l => Eq (Decl l) 
Data l => Data (Decl l) 
Ord l => Ord (Decl l) 
Show l => Show (Decl l) 
SrcInfo pos => Pretty (Decl pos) 
SrcInfo loc => Parseable (Decl loc) 

data DeclHead l Source

The head of a type or class declaration.

Constructors

DHead l (Name l) [TyVarBind l] 
DHInfix l (TyVarBind l) (Name l) (TyVarBind l) 
DHParen l (DeclHead l) 

data InstHead l Source

The head of an instance declaration.

Constructors

IHead l (QName l) [Type l] 
IHInfix l (Type l) (QName l) (Type l) 
IHParen l (InstHead l) 

data Binds l Source

A binding group inside a let or where clause.

Constructors

BDecls l [Decl l]

An ordinary binding group

IPBinds l [IPBind l]

A binding group for implicit parameters

Instances

data IPBind l Source

A binding of an implicit parameter.

Constructors

IPBind l (IPName l) (Exp l) 

Instances

Type classes and instances

data ClassDecl l Source

Declarations inside a class declaration.

Constructors

ClsDecl l (Decl l)

ordinary declaration

ClsDataFam l (Maybe (Context l)) (DeclHead l) (Maybe (Kind l))

declaration of an associated data type

ClsTyFam l (DeclHead l) (Maybe (Kind l))

declaration of an associated type synonym

ClsTyDef l (Type l) (Type l)

default choice for an associated type synonym

data InstDecl l Source

Declarations inside an instance declaration.

Constructors

InsDecl l (Decl l)

ordinary declaration

InsType l (Type l) (Type l)

an associated type definition

InsData l (DataOrNew l) (Type l) [QualConDecl l] (Maybe (Deriving l))

an associated data type implementation

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

an associated data type implemented using GADT style

data Deriving l Source

A deriving clause following a data type declaration.

Constructors

Deriving l [InstHead l] 

Data type declarations

data DataOrNew l Source

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

Constructors

DataType l 
NewType l 

data ConDecl l Source

Declaration of an ordinary data constructor.

Constructors

ConDecl l (Name l) [BangType l]

ordinary data constructor

InfixConDecl l (BangType l) (Name l) (BangType l)

infix data constructor

RecDecl l (Name l) [FieldDecl l]

record constructor

data FieldDecl l Source

Declaration of a (list of) named field(s).

Constructors

FieldDecl l [Name l] (BangType l) 

data QualConDecl l Source

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

Constructors

QualConDecl l (Maybe [TyVarBind l]) (Maybe (Context l)) (ConDecl l) 

data GadtDecl l Source

A single constructor declaration in a GADT data type declaration.

Constructors

GadtDecl l (Name l) (Type l) 

data BangType l Source

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

Constructors

BangedTy l (Type l)

strict component, marked with "!"

UnBangedTy l (Type l)

non-strict component

UnpackedTy l (Type l)

unboxed component, marked with an UNPACK pragma

Function bindings

data Match l Source

Clauses of a function binding.

Constructors

Match l (Name l) [Pat l] (Rhs l) (Maybe (Binds l))

A clause defined with prefix notation, i.e. the function name followed by its argument patterns, the right-hand side and an optional where clause.

InfixMatch l (Pat l) (Name l) [Pat l] (Rhs l) (Maybe (Binds l))

A clause defined with infix notation, i.e. first its first argument pattern, then the function name, then its following argument(s), the right-hand side and an optional where clause. Note that there can be more than two arguments to a function declared infix, hence the list of pattern arguments.

Instances

data Rhs l Source

The right hand side of a function or pattern binding.

Constructors

UnGuardedRhs l (Exp l)

unguarded right hand side (exp)

GuardedRhss l [GuardedRhs l]

guarded right hand side (gdrhs)

Instances

Functor Rhs 
Typeable1 Rhs 
Annotated Rhs 
ExactP Rhs 
AppFixity Rhs 
Eq l => Eq (Rhs l) 
Data l => Data (Rhs l) 
Ord l => Ord (Rhs l) 
Show l => Show (Rhs l) 
SrcInfo loc => Pretty (Rhs loc) 

data GuardedRhs l 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 l [Stmt l] (Exp l) 

Class Assertions and Contexts

data Context l Source

A context is a set of assertions

Constructors

CxSingle l (Asst l) 
CxTuple l [Asst l] 
CxParen l (Context l) 
CxEmpty l 

data FunDep l Source

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

Constructors

FunDep l [Name l] [Name l] 

Instances

data Asst l 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 l (QName l) [Type l]

ordinary class assertion

InfixA l (Type l) (QName l) (Type l)

class assertion where the class name is given infix

IParam l (IPName l) (Type l)

implicit parameter assertion

EqualP l (Type l) (Type l)

type equality constraint

Instances

Functor Asst 
Typeable1 Asst 
Annotated Asst 
ExactP Asst 
Eq l => Eq (Asst l) 
Data l => Data (Asst l) 
Ord l => Ord (Asst l) 
Show l => Show (Asst l) 
Pretty (Asst l) 

Types

data Type l Source

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

Constructors

TyForall l (Maybe [TyVarBind l]) (Maybe (Context l)) (Type l)

qualified type

TyFun l (Type l) (Type l)

function type

TyTuple l Boxed [Type l]

tuple type, possibly boxed

TyList l (Type l)

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

TyApp l (Type l) (Type l)

application of a type constructor

TyVar l (Name l)

type variable

TyCon l (QName l)

named type or type constructor

TyParen l (Type l)

type surrounded by parentheses

TyInfix l (Type l) (QName l) (Type l)

infix type constructor

TyKind l (Type l) (Kind l)

type with explicit kind signature

Instances

Functor Type 
Typeable1 Type 
Annotated Type 
ExactP Type 
Eq l => Eq (Type l) 
Data l => Data (Type l) 
Ord l => Ord (Type l) 
Show l => Show (Type l) 
Pretty (Type l) 
SrcInfo loc => Parseable (Type loc) 

data Boxed Source

Flag denoting whether a tuple is boxed or unboxed.

Constructors

Boxed 
Unboxed 

data Kind l Source

An explicit kind annotation.

Constructors

KindStar l

*, the kind of types

KindBang l

!, the kind of unboxed types

KindFn l (Kind l) (Kind l)

->, the kind of a type constructor

KindParen l (Kind l)

a parenthesised kind

KindVar l (Name l)

a kind variable (as-of-yet unsupported by compilers)

Instances

Functor Kind 
Typeable1 Kind 
Annotated Kind 
ExactP Kind 
Eq l => Eq (Kind l) 
Data l => Data (Kind l) 
Ord l => Ord (Kind l) 
Show l => Show (Kind l) 
Pretty (Kind l) 

data TyVarBind l Source

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

Constructors

KindedVar l (Name l) (Kind l)

variable binding with kind annotation

UnkindedVar l (Name l)

ordinary variable binding

Expressions

data Exp l Source

Haskell expressions.

Constructors

Var l (QName l)

variable

IPVar l (IPName l)

implicit parameter variable

Con l (QName l)

data constructor

Lit l (Literal l)

literal constant

InfixApp l (Exp l) (QOp l) (Exp l)

infix application

App l (Exp l) (Exp l)

ordinary application

NegApp l (Exp l)

negation expression -exp (unary minus)

Lambda l [Pat l] (Exp l)

lambda expression

Let l (Binds l) (Exp l)

local declarations with let ... in ...

If l (Exp l) (Exp l) (Exp l)

if exp then exp else exp

Case l (Exp l) [Alt l]

case exp of alts

Do l [Stmt l]

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

MDo l [Stmt l]

mdo-expression

Tuple l [Exp l]

tuple expression

TupleSection l [Maybe (Exp l)]

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

List l [Exp l]

list expression

Paren l (Exp l)

parenthesised expression

LeftSection l (Exp l) (QOp l)

left section (exp qop)

RightSection l (QOp l) (Exp l)

right section (qop exp)

RecConstr l (QName l) [FieldUpdate l]

record construction expression

RecUpdate l (Exp l) [FieldUpdate l]

record update expression

EnumFrom l (Exp l)

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

EnumFromTo l (Exp l) (Exp l)

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

EnumFromThen l (Exp l) (Exp l)

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

EnumFromThenTo l (Exp l) (Exp l) (Exp l)

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

ListComp l (Exp l) [QualStmt l]

ordinary list comprehension

ParComp l (Exp l) [[QualStmt l]]

parallel list comprehension

ExpTypeSig l (Exp l) (Type l)

expression with explicit type signature

VarQuote l (QName l)

'x for template haskell reifying of expressions

TypQuote l (QName l)

''T for template haskell reifying of types

BracketExp l (Bracket l)

template haskell bracket expression

SpliceExp l (Splice l)

template haskell splice expression

QuasiQuote l String String

quasi-quotaion: [$name| string |]

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

xml element, with attributes and children

XETag l (XName l) [XAttr l] (Maybe (Exp l))

empty xml element, with attributes

XPcdata l String

PCDATA child element

XExpTag l (Exp l)

escaped haskell expression inside xml

CorePragma l String (Exp l)

CORE pragma

SCCPragma l String (Exp l)

SCC pragma

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

GENERATED pragma

Proc l (Pat l) (Exp l)

arrows proc: proc pat -> exp

LeftArrApp l (Exp l) (Exp l)

arrow application (from left): exp -< exp

RightArrApp l (Exp l) (Exp l)

arrow application (from right): exp >- exp

LeftArrHighApp l (Exp l) (Exp l)

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

RightArrHighApp l (Exp l) (Exp l)

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

Instances

Functor Exp 
Typeable1 Exp 
Annotated Exp 
ExactP Exp 
AppFixity Exp 
Eq l => Eq (Exp l) 
Data l => Data (Exp l) 
Ord l => Ord (Exp l) 
Show l => Show (Exp l) 
SrcInfo loc => Pretty (Exp loc) 
SrcInfo loc => Parseable (Exp loc) 

data Stmt l 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 l (Pat l) (Exp l)

a generator: pat <- exp

Qualifier l (Exp l)

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 l (Binds l)

local bindings

RecStmt l [Stmt l]

a recursive binding group for arrows

Instances

Functor Stmt 
Typeable1 Stmt 
Annotated Stmt 
ExactP Stmt 
AppFixity Stmt 
Eq l => Eq (Stmt l) 
Data l => Data (Stmt l) 
Ord l => Ord (Stmt l) 
Show l => Show (Stmt l) 
SrcInfo loc => Pretty (Stmt loc) 
SrcInfo loc => Parseable (Stmt loc) 

data QualStmt l Source

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

Constructors

QualStmt l (Stmt l)

an ordinary statement

ThenTrans l (Exp l)

then exp

ThenBy l (Exp l) (Exp l)

then exp by exp

GroupBy l (Exp l)

then group by exp

GroupUsing l (Exp l)

then group using exp

GroupByUsing l (Exp l) (Exp l)

then group by exp using exp

data FieldUpdate l Source

An fbind in a labeled construction or update expression.

Constructors

FieldUpdate l (QName l) (Exp l)

ordinary label-expresion pair

FieldPun l (Name l)

record field pun

FieldWildcard l

record field wildcard

data Alt l Source

An alt alternative in a case expression.

Constructors

Alt l (Pat l) (GuardedAlts l) (Maybe (Binds l)) 

Instances

Functor Alt 
Typeable1 Alt 
Annotated Alt 
ExactP Alt 
AppFixity Alt 
Eq l => Eq (Alt l) 
Data l => Data (Alt l) 
Ord l => Ord (Alt l) 
Show l => Show (Alt l) 
SrcInfo loc => Pretty (Alt loc) 

data GuardedAlts l 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 l (Exp l)

-> exp

GuardedAlts l [GuardedAlt l]

gdpat

data GuardedAlt l Source

A guarded case alternative | stmts -> exp.

Constructors

GuardedAlt l [Stmt l] (Exp l) 

data XAttr l Source

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

Constructors

XAttr l (XName l) (Exp l) 

Instances

Patterns

data Pat l Source

A pattern, to be matched against a value.

Constructors

PVar l (Name l)

variable

PLit l (Literal l)

literal constant

PNeg l (Pat l)

negated pattern

PNPlusK l (Name l) Integer

n+k pattern

PInfixApp l (Pat l) (QName l) (Pat l)

pattern with an infix data constructor

PApp l (QName l) [Pat l]

data constructor and argument patterns

PTuple l [Pat l]

tuple pattern

PList l [Pat l]

list pattern

PParen l (Pat l)

parenthesized pattern

PRec l (QName l) [PatField l]

labelled pattern, record style

PAsPat l (Name l) (Pat l)

@-pattern

PWildCard l

wildcard pattern: _

PIrrPat l (Pat l)

irrefutable pattern: ~pat

PatTypeSig l (Pat l) (Type l)

pattern with type signature

PViewPat l (Exp l) (Pat l)

view patterns of the form (exp -> pat)

PRPat l [RPat l]

regular list pattern

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

XML element pattern

PXETag l (XName l) [PXAttr l] (Maybe (Pat l))

XML singleton element pattern

PXPcdata l String

XML PCDATA pattern

PXPatTag l (Pat l)

XML embedded pattern

PXRPats l [RPat l]

XML regular list pattern

PExplTypeArg l (QName l) (Type l)

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

PQuasiQuote l String String

quasi quote pattern: [$name| string |]

PBangPat l (Pat l)

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

Instances

Functor Pat 
Typeable1 Pat 
Annotated Pat 
ExactP Pat 
AppFixity Pat 
Eq l => Eq (Pat l) 
Data l => Data (Pat l) 
Ord l => Ord (Pat l) 
Show l => Show (Pat l) 
SrcInfo loc => Pretty (Pat loc) 
SrcInfo loc => Parseable (Pat loc) 

data PatField l Source

An fpat in a labeled record pattern.

Constructors

PFieldPat l (QName l) (Pat l)

ordinary label-pattern pair

PFieldPun l (Name l)

record field pun

PFieldWildcard l

record field wildcard

data PXAttr l Source

An XML attribute in a pattern.

Constructors

PXAttr l (XName l) (Pat l) 

Instances

data RPat l Source

An entity in a regular pattern.

Constructors

RPOp l (RPat l) (RPatOp l)

operator pattern, e.g. pat*

RPEither l (RPat l) (RPat l)

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

RPSeq l [RPat l]

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

RPGuard l (Pat l) [Stmt l]

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

RPCAs l (Name l) (RPat l)

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

RPAs l (Name l) (RPat l)

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

RPParen l (RPat l)

parenthesised pattern, e.g. (2*)

RPPat l (Pat l)

an ordinary pattern

Instances

Functor RPat 
Typeable1 RPat 
Annotated RPat 
ExactP RPat 
AppFixity RPat 
Eq l => Eq (RPat l) 
Data l => Data (RPat l) 
Ord l => Ord (RPat l) 
Show l => Show (RPat l) 
SrcInfo loc => Pretty (RPat loc) 

data RPatOp l Source

A regular pattern operator.

Constructors

RPStar l

* = 0 or more

RPStarG l

*! = 0 or more, greedy

RPPlus l

+ = 1 or more

RPPlusG l

+! = 1 or more, greedy

RPOpt l

? = 0 or 1

RPOptG l

?! = 0 or 1, greedy

Instances

Literals

data Literal l Source

literal Values of this type hold the abstract value of the literal, along with the precise string representation used. For example, 10, 0o12 and 0xa have the same value representation, but each carry a different string representation.

Constructors

Char l Char String

character literal

String l String String

string literal

Int l Integer String

integer literal

Frac l Rational String

floating point literal

PrimInt l Integer String

unboxed integer literal

PrimWord l Integer String

unboxed word literal

PrimFloat l Rational String

unboxed float literal

PrimDouble l Rational String

unboxed double literal

PrimChar l Char String

unboxed character literal

PrimString l String String

unboxed string literal

Variables, Constructors and Operators

data ModuleName l Source

The name of a Haskell module.

Constructors

ModuleName l String 

data QName l Source

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

Constructors

Qual l (ModuleName l) (Name l)

name qualified with a module name

UnQual l (Name l)

unqualified local name

Special l (SpecialCon l)

built-in constructor with special syntax

Instances

data Name l Source

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

Constructors

Ident l String

varid or conid.

Symbol l String

varsym or consym

Instances

Functor Name 
Typeable1 Name 
Annotated Name 
ExactP Name 
Eq l => Eq (Name l) 
Data l => Data (Name l) 
Ord l => Ord (Name l) 
Show l => Show (Name l) 
Pretty (Name l) 

data QOp l Source

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

Constructors

QVarOp l (QName l)

variable operator (qvarop)

QConOp l (QName l)

constructor operator (qconop)

Instances

Functor QOp 
Typeable1 QOp 
Annotated QOp 
ExactP QOp 
Eq l => Eq (QOp l) 
Data l => Data (QOp l) 
Ord l => Ord (QOp l) 
Show l => Show (QOp l) 
Pretty (QOp l) 

data Op l Source

Operators appearing in infix declarations are never qualified.

Constructors

VarOp l (Name l)

variable operator (varop)

ConOp l (Name l)

constructor operator (conop)

Instances

Functor Op 
Typeable1 Op 
Annotated Op 
ExactP Op 
Eq l => Eq (Op l) 
Data l => Data (Op l) 
Ord l => Ord (Op l) 
Show l => Show (Op l) 
Pretty (Op l) 

data SpecialCon l Source

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

Constructors

UnitCon l

unit type and data constructor ()

ListCon l

list type constructor []

FunCon l

function type constructor ->

TupleCon l Boxed Int

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

Cons l

list data constructor (:)

UnboxedSingleCon l

unboxed singleton tuple constructor (# #)

data CName l Source

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

Constructors

VarName l (Name l)

name of a method or field

ConName l (Name l)

name of a data constructor

Instances

data IPName l Source

An implicit parameter name.

Constructors

IPDup l String

?ident, non-linear implicit parameter

IPLin l String

%ident, linear implicit parameter

Instances

data XName l Source

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

Constructors

XName l String 
XDomName l String String 

Instances

Template Haskell

data Bracket l Source

A template haskell bracket expression.

Constructors

ExpBracket l (Exp l)

expression bracket: [| ... |]

PatBracket l (Pat l)

pattern bracket: [p| ... |]

TypeBracket l (Type l)

type bracket: [t| ... |]

DeclBracket l [Decl l]

declaration bracket: [d| ... |]

data Splice l Source

A template haskell splice expression

Constructors

IdSplice l String

variable splice: $var

ParenSplice l (Exp l)

parenthesised expression splice: $(exp)

Instances

FFI

data Safety l Source

The safety of a foreign function call.

Constructors

PlayRisky l

unsafe

PlaySafe l Bool

safe (False) or threadsafe (True)

Instances

data CallConv l Source

The calling convention of a foreign function call.

Constructors

StdCall l 
CCall l 

Pragmas

data OptionPragma l Source

A top level options pragma, preceding the module header.

Constructors

LanguagePragma l [Name l]

LANGUAGE pragma | IncludePragma l String -- ^ INCLUDE pragma | CFilesPragma l String -- ^ CFILES pragma

OptionsPragma l (Maybe Tool) String

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

data Tool Source

Recognised tools for OPTIONS pragmas.

data Rule l Source

The body of a RULES pragma.

Constructors

Rule l String (Maybe (Activation l)) (Maybe [RuleVar l]) (Exp l) (Exp l) 

Instances

Functor Rule 
Typeable1 Rule 
Annotated Rule 
ExactP Rule 
Eq l => Eq (Rule l) 
Data l => Data (Rule l) 
Ord l => Ord (Rule l) 
Show l => Show (Rule l) 
SrcInfo loc => Pretty (Rule loc) 

data RuleVar l Source

Variables used in a RULES pragma, optionally annotated with types

Constructors

RuleVar l (Name l) 
TypedRuleVar l (Name l) (Type l) 

data Activation l Source

Activation clause of a RULES pragma.

Constructors

ActiveFrom l Int 
ActiveUntil l Int 

data Annotation l Source

An annotation through an ANN pragma.

Constructors

Ann l (Name l) (Exp l)

An annotation for a declared name.

TypeAnn l (Name l) (Exp l)

An annotation for a declared type.

ModuleAnn l (Exp l)

An annotation for the defining module.

Builtin names

Modules

Main function of a program

Constructors

tuple_con :: l -> Boxed -> Int -> Exp lSource

Special identifiers

Type constructors

Source coordinates

Annotated trees

class Functor ast => Annotated ast whereSource

AST nodes are annotated, and this class allows manipulation of the annotations.

Methods

ann :: ast l -> lSource

Retrieve the annotation of an AST node.

amap :: (l -> l) -> ast l -> ast lSource

Change the annotation of an AST node. Note that only the annotation of the node itself is affected, and not the annotations of any child nodes. if all nodes in the AST tree are to be affected, use fmap.

(=~=) :: (Annotated a, Eq (a ())) => a l1 -> a l2 -> BoolSource

Test if two AST elements are equal modulo annotations.