|
Language.Haskell.Syntax | Portability | portable | Stability | experimental | Maintainer | libraries@haskell.org |
|
|
|
|
|
Description |
A suite of datatypes describing the abstract syntax of Haskell 98
http://www.haskell.org/onlinereport/ plus a few extensions:
- multi-parameter type classes
- parameters of type class assertions are unrestricted
This module has been changed so that show is a real show.
For GHC, we also derive Typeable and Data for all types.
|
|
Synopsis |
|
|
|
|
Modules
|
|
|
A Haskell source module.
| Constructors | | Instances | |
|
|
|
Export specification.
| Constructors | HsEVar HsQName | variable
| HsEAbs HsQName | T:
a class or datatype exported abstractly,
or a type synonym.
| HsEThingAll HsQName | T(..):
a class exported with all of its methods, or
a datatype exported with all of its constructors.
| HsEThingWith HsQName [HsCName] | T(C_1,...,C_n):
a class exported with some of its methods, or
a datatype exported with some of its constructors.
| HsEModuleContents Module | module M:
re-export a module.
|
| Instances | |
|
|
|
Import declaration.
| Constructors | HsImportDecl | | importLoc :: SrcLoc | position of the import keyword.
| importModule :: Module | name of the module imported.
| importQualified :: Bool | imported qualified?
| importAs :: Maybe Module | optional alias name in an
as clause.
| importSpecs :: Maybe (Bool, [HsImportSpec]) | optional list of import specifications.
The Bool is True if the names are excluded
by hiding.
|
|
| Instances | |
|
|
|
Import specification.
| Constructors | HsIVar HsName | variable
| HsIAbs HsName | T:
the name of a class, datatype or type synonym.
| HsIThingAll HsName | T(..):
a class imported with all of its methods, or
a datatype imported with all of its constructors.
| HsIThingWith HsName [HsCName] | 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 | HsAssocNone | non-associative operator (declared with infix)
| HsAssocLeft | left-associative operator (declared with infixl).
| HsAssocRight | right-associative operator (declared with infixr)
|
| Instances | |
|
|
Declarations
|
|
|
Constructors | | Instances | |
|
|
|
Declaration of a data constructor.
| Constructors | | Instances | |
|
|
|
The type of a constructor argument or field, optionally including
a strictness annotation.
| Constructors | HsBangedTy HsType | strict component, marked with "!"
| HsUnBangedTy HsType | non-strict component
|
| Instances | |
|
|
|
Clauses of a function binding.
| Constructors | | Instances | |
|
|
|
The right hand side of a function or pattern binding.
| Constructors | HsUnGuardedRhs HsExp | unguarded right hand side (exp)
| HsGuardedRhss [HsGuardedRhs] | guarded right hand side (gdrhs)
|
| Instances | |
|
|
|
A guarded right hand side | exp = exp.
The first expression will be Boolean-valued.
| Constructors | | Instances | |
|
|
|
Safety level for invoking a foreign entity
| Constructors | HsSafe | call may generate callbacks
| HsUnsafe | call will not generate callbacks
|
| Instances | |
|
|
Class Assertions and Contexts
|
|
|
A type qualified with a context.
An unqualified type has an empty context.
| 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.
|
|
Types
|
|
|
Haskell types and type constructors.
| Constructors | | Instances | |
|
|
Expressions
|
|
|
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 HsInfixApps associated to the left.
- The Language.Haskell.Pretty.Pretty instance for HsExp does not
add parentheses in printing.
| Constructors | | Instances | |
|
|
|
This type represents both stmt in a do-expression,
and qual in a list comprehension.
| Constructors | HsGenerator SrcLoc HsPat HsExp | a generator pat <- exp
| HsQualifier HsExp | an exp by itself: in a do-expression,
an action whose result is discarded;
in a list comprehension, a guard expression
| HsLetStmt [HsDecl] | local bindings
|
| Instances | |
|
|
|
An fbind in a labeled record construction or update expression.
| Constructors | | Instances | |
|
|
|
An alt in a case expression.
| Constructors | | Instances | |
|
|
|
Constructors | | Instances | |
|
|
|
A guarded alternative | exp -> exp.
The first expression will be Boolean-valued.
| Constructors | | Instances | |
|
|
Patterns
|
|
|
A pattern, to be matched against a value.
| Constructors | | Instances | |
|
|
|
An fpat in a labeled record pattern.
| Constructors | | 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 | HsChar Char | character literal
| HsString String | string literal
| HsInt Integer | integer literal
| HsFrac Rational | floating point literal
| HsCharPrim Char | GHC unboxed character literal
| HsStringPrim String | GHC unboxed string literal
| HsIntPrim Integer | GHC unboxed integer literal
| HsFloatPrim Rational | GHC unboxed float literal
| HsDoublePrim Rational | GHC unboxed double 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 | | Instances | |
|
|
|
This type is used to represent variables, and also constructors.
| Constructors | HsIdent String | varid or conid
| HsSymbol String | varsym or consym
|
| Instances | |
|
|
|
Possibly qualified infix operators (qop), appearing in expressions.
| Constructors | HsQVarOp HsQName | variable operator (qvarop)
| HsQConOp HsQName | constructor operator (qconop)
|
| Instances | |
|
|
|
Operators, appearing in infix declarations.
| Constructors | HsVarOp HsName | variable operator (varop)
| HsConOp HsName | constructor operator (conop)
|
| Instances | |
|
|
|
Constructors with special syntax.
These names are never qualified, and always refer to builtin type or
data constructors.
| Constructors | HsUnitCon | unit type and data constructor ()
| HsListCon | list type constructor []
| HsFunCon | function type constructor ->
| HsTupleCon Int | n-ary tuple type and data
constructors (,) etc
| HsCons | list data constructor (:)
|
| Instances | |
|
|
|
A name (cname) of a component of a class or data type in an import
or export specification.
| Constructors | HsVarName HsName | name of a method or field
| HsConName HsName | name of a data constructor
|
| Instances | |
|
|
Builtin names
|
|
Modules
|
|
|
|
|
|
Main function of a program
|
|
|
|
Constructors
|
|
|
|
|
|
|
|
|
|
|
|
Type constructors
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
Source coordinates
|
|
|
A position in the source.
| Constructors | | Instances | |
|
|
Produced by Haddock version 2.4.2 |