 | haskell-src-exts-1.3.5: Manipulating Haskell source: abstract syntax, lexer, parser, and pretty-printer | Source code | Contents | Index |
|
Language.Haskell.Exts.Syntax | |
|
|
|
|
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
|
|
|
A complete Haskell source module.
| Constructors | | Instances | |
|
|
|
Warning text to optionally use in the module header of e.g.
a deprecated module.
| Constructors | | Instances | |
|
|
|
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.
|
| Instances | |
|
|
|
An import declaration.
| Constructors | ImportDecl | | 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.
|
|
| Instances | |
|
|
|
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.
|
| Instances | |
|
|
|
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)
|
| Instances | |
|
|
Declarations
|
|
|
A top-level declaration.
| Constructors | | Instances | |
|
|
|
A binding group inside a let or where clause.
| Constructors | BDecls [Decl] | An ordinary binding group
| IPBinds [IPBind] | 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 | | Instances | |
|
|
|
Declarations inside an instance declaration.
| Constructors | | Instances | |
|
|
|
A single derived instance, which may have arguments since it may be a MPTC.
|
|
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 | |
|
|
|
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 Type | strict component, marked with "!"
| UnBangedTy Type | non-strict component
| UnpackedTy Type | 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 Exp | unguarded right hand side (exp)
| GuardedRhss [GuardedRhs] | 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
|
|
|
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 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
|
| Instances | |
|
|
Types
|
|
|
A type qualified with a context.
An unqualified type has an empty context.
| Constructors | | Instances | |
|
|
|
Flag denoting whether a tuple is boxed or unboxed.
| Constructors | | Instances | |
|
|
|
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)
|
| Instances | |
|
|
|
A type variable declaration, optionally with an explicit kind annotation.
| Constructors | KindedVar Name Kind | variable binding with kind annotation
| UnkindedVar Name | ordinary variable binding
|
| Instances | |
|
|
Expressions
|
|
|
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
| CorePragma String Exp | CORE pragma
| SCCPragma String Exp | SCC pragma
| GenPragma String (Int, Int) (Int, Int) Exp | GENERATED pragma
| Proc 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
|
| 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 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
|
| Instances | |
|
|
|
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
|
| Instances | |
|
|
|
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
|
| 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 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 = ...
|
| Instances | |
|
|
|
An fpat in a labeled record pattern.
| Constructors | PFieldPat QName Pat | ordinary label-pattern pair
| PFieldPun Name | record field pun
| PFieldWildcard | 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 | * = 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
|
| 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 | 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
|
| 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 ModuleName Name | name qualified with a module name
| UnQual Name | unqualified local name
| Special SpecialCon | built-in constructor with special syntax
|
| Instances | |
|
|
|
This type is used to represent variables, and also constructors.
| Constructors | | Instances | |
|
|
|
Possibly qualified infix operators (qop), appearing in expressions.
| Constructors | QVarOp QName | variable operator (qvarop)
| QConOp QName | constructor operator (qconop)
|
| Instances | |
|
|
|
Operators appearing in infix declarations are never qualified.
| Constructors | VarOp Name | variable operator (varop)
| ConOp Name | constructor operator (conop)
|
| Instances | |
|
|
|
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 (# #)
|
| Instances | |
|
|
|
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
|
| Instances | |
|
|
|
An implicit parameter name.
| Constructors | IPDup String | ?ident, non-linear implicit parameter
| IPLin 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 Exp | expression bracket: [| ... |]
| PatBracket Pat | pattern bracket: [p| ... |]
| TypeBracket Type | type bracket: [t| ... |]
| DeclBracket [Decl] | declaration bracket: [d| ... |]
|
| Instances | |
|
|
|
A template haskell splice expression
| Constructors | IdSplice String | variable splice: $var
| ParenSplice Exp | parenthesised expression splice: $(exp)
|
| Instances | |
|
|
FFI
|
|
|
The safety of a foreign function call.
| Constructors | | Instances | |
|
|
|
The calling convention of a foreign function call.
| Constructors | | Instances | |
|
|
Pragmas
|
|
|
A top level options pragma, preceding the module header.
| Constructors | | 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 | AlwaysActive | | ActiveFrom Int | | ActiveUntil Int | |
| Instances | |
|
|
Builtin names
|
|
Modules
|
|
|
|
|
|
Main function of a program
|
|
|
|
Constructors
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
Special identifiers
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
Type constructors
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
Source coordinates
|
|
|
A single position in the source.
| Constructors | | Instances | |
|
|
Produced by Haddock version 2.6.0 |