 | haskell-src-exts-1.3.5: Manipulating Haskell source: abstract syntax, lexer, parser, and pretty-printer | Source code | Contents | Index |
|
Language.Haskell.Exts.Annotated.Syntax | |
|
|
|
|
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
|
|
|
A complete Haskell source module.
| Constructors | | Instances | |
|
|
|
The head of a module, including the name and export specification.
| Constructors | | Instances | |
|
|
|
Warning text to optionally use in the module header of e.g.
a deprecated module.
| Constructors | | Instances | |
|
|
|
An explicit export specification.
| Constructors | | Instances | |
|
|
|
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.
|
| Instances | |
|
|
|
An import declaration.
| Constructors | ImportDecl | | 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.
|
|
| Instances | |
|
|
|
An explicit import specification list.
| Constructors | | Instances | |
|
|
|
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.
|
| Instances | |
|
|
|
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
|
|
|
A top-level declaration.
| Constructors | | Instances | |
|
|
|
The head of a type or class declaration.
| Constructors | | Instances | |
|
|
|
The head of an instance declaration.
| Constructors | | Instances | |
|
|
|
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 | |
|
|
|
A binding of an implicit parameter.
| Constructors | | Instances | |
|
|
Type classes and instances
|
|
|
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
|
| Instances | |
|
|
|
Declarations inside an instance declaration.
| Constructors | | Instances | |
|
|
|
A deriving clause following a data type declaration.
| Constructors | | Instances | |
|
|
Data type declarations
|
|
|
A flag stating whether a declaration is a data or newtype declaration.
| Constructors | | Instances | |
|
|
|
Declaration of an ordinary data constructor.
| Constructors | | Instances | |
|
|
|
Declaration of a (list of) named field(s).
| Constructors | | Instances | |
|
|
|
A single constructor declaration within a data type declaration,
which may have an existential quantification binding.
| Constructors | | Instances | |
|
|
|
A single constructor declaration in a GADT data type declaration.
| Constructors | | Instances | |
|
|
|
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
|
| Instances | |
|
|
Function bindings
|
|
|
Clauses of a function binding.
| Constructors | | Instances | |
|
|
|
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 | |
|
|
|
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 | | Instances | |
|
|
Class Assertions and Contexts
|
|
|
A context is a set of assertions
| Constructors | | Instances | |
|
|
|
A functional dependency, given on the form
l1 l2 ... ln -> r2 r3 .. rn
| Constructors | | Instances | |
|
|
|
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 | |
|
|
Types
|
|
|
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 | |
|
|
|
Flag denoting whether a tuple is boxed or unboxed.
| Constructors | | Instances | |
|
|
|
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 | |
|
|
|
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
|
| Instances | |
|
|
Expressions
|
|
|
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 | |
|
|
|
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 | |
|
|
|
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
|
| Instances | |
|
|
|
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
|
| Instances | |
|
|
|
An alt alternative in a case expression.
| Constructors | | Instances | |
|
|
|
The right-hand sides of a case alternative,
which may be a single right-hand side or a
set of guarded ones.
| Constructors | | Instances | |
|
|
|
A guarded case alternative | stmts -> exp.
| Constructors | | Instances | |
|
|
|
An xml attribute, which is a name-expression pair.
| Constructors | | Instances | |
|
|
Patterns
|
|
|
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 | |
|
|
|
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
|
| Instances | |
|
|
|
An XML attribute in a pattern.
| Constructors | | Instances | |
|
|
|
An entity in a regular pattern.
| Constructors | | Instances | |
|
|
|
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
|
|
|
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 | | Instances | |
|
|
Variables, Constructors and Operators
|
|
|
The name of a Haskell module.
| Constructors | | Instances | |
|
|
|
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 | |
|
|
|
This type is used to represent variables, and also constructors.
| Constructors | Ident l String | varid or conid.
| Symbol l String | varsym or consym
|
| Instances | |
|
|
|
Possibly qualified infix operators (qop), appearing in expressions.
| Constructors | QVarOp l (QName l) | variable operator (qvarop)
| QConOp l (QName l) | constructor operator (qconop)
|
| Instances | |
|
|
|
Operators appearing in infix declarations are never qualified.
| Constructors | VarOp l (Name l) | variable operator (varop)
| ConOp l (Name l) | constructor operator (conop)
|
| Instances | |
|
|
|
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 (# #)
|
| Instances | |
|
|
|
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 | |
|
|
|
An implicit parameter name.
| Constructors | IPDup l String | ?ident, non-linear implicit parameter
| IPLin l String | %ident, linear implicit parameter
|
| Instances | |
|
|
|
The name of an xml element or attribute,
possibly qualified with a namespace.
| Constructors | | Instances | |
|
|
Template Haskell
|
|
|
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| ... |]
|
| Instances | |
|
|
|
A template haskell splice expression
| Constructors | IdSplice l String | variable splice: $var
| ParenSplice l (Exp l) | parenthesised expression splice: $(exp)
|
| Instances | |
|
|
FFI
|
|
|
The safety of a foreign function call.
| Constructors | PlayRisky l | unsafe
| PlaySafe l Bool | safe (False) or threadsafe (True)
|
| Instances | |
|
|
|
The calling convention of a foreign function call.
| Constructors | | Instances | |
|
|
Pragmas
|
|
|
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
|
| Instances | |
|
|
|
Recognised tools for OPTIONS pragmas.
| Constructors | GHC | | HUGS | | NHC98 | | YHC | | HADDOCK | | UnknownTool String | |
| Instances | |
|
|
|
The body of a RULES pragma.
| Constructors | | Instances | |
|
|
|
Variables used in a RULES pragma, optionally annotated with types
| Constructors | | Instances | |
|
|
|
Activation clause of a RULES pragma.
| Constructors | ActiveFrom l Int | | ActiveUntil l Int | |
| Instances | |
|
|
Builtin names
|
|
Modules
|
|
|
|
|
|
Main function of a program
|
|
|
|
Constructors
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
Special identifiers
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
Type constructors
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
Source coordinates
|
|
Annotated trees
|
|
|
AST nodes are annotated, and this class allows manipulation of the annotations.
| | Methods | | Retrieve the annotation of an AST node.
| | amap :: (l -> l) -> ast l -> ast l | Source |
| 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.
|
| | Instances | |
|
|
|
Test if two AST elements are equal modulo annotations.
|
|
Produced by Haddock version 2.6.0 |