Copyright | (c) The GHC Team, 1997-2000 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | libraries@haskell.org |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
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.
- data HsModule = HsModule SrcLoc Module (Maybe [HsExportSpec]) [HsImportDecl] [HsDecl]
- data HsExportSpec
- data HsImportDecl = HsImportDecl {
- importLoc :: SrcLoc
- importModule :: Module
- importQualified :: Bool
- importAs :: Maybe Module
- importSpecs :: Maybe (Bool, [HsImportSpec])
- data HsImportSpec
- data HsAssoc
- data HsDecl
- = HsTypeDecl SrcLoc HsName [HsName] HsType
- | HsDataDecl SrcLoc HsContext HsName [HsName] [HsConDecl] [HsQName]
- | HsInfixDecl SrcLoc HsAssoc Int [HsOp]
- | HsNewTypeDecl SrcLoc HsContext HsName [HsName] HsConDecl [HsQName]
- | HsClassDecl SrcLoc HsContext HsName [HsName] [HsDecl]
- | HsInstDecl SrcLoc HsContext HsQName [HsType] [HsDecl]
- | HsDefaultDecl SrcLoc [HsType]
- | HsTypeSig SrcLoc [HsName] HsQualType
- | HsFunBind [HsMatch]
- | HsPatBind SrcLoc HsPat HsRhs [HsDecl]
- | HsForeignImport SrcLoc String HsSafety String HsName HsType
- | HsForeignExport SrcLoc String String HsName HsType
- data HsConDecl
- = HsConDecl SrcLoc HsName [HsBangType]
- | HsRecDecl SrcLoc HsName [([HsName], HsBangType)]
- data HsBangType
- data HsMatch = HsMatch SrcLoc HsName [HsPat] HsRhs [HsDecl]
- data HsRhs
- data HsGuardedRhs = HsGuardedRhs SrcLoc HsExp HsExp
- data HsSafety
- data HsQualType = HsQualType HsContext HsType
- type HsContext = [HsAsst]
- type HsAsst = (HsQName, [HsType])
- data HsType
- data HsExp
- = HsVar HsQName
- | HsCon HsQName
- | HsLit HsLiteral
- | HsInfixApp HsExp HsQOp HsExp
- | HsApp HsExp HsExp
- | HsNegApp HsExp
- | HsLambda SrcLoc [HsPat] HsExp
- | HsLet [HsDecl] HsExp
- | HsIf HsExp HsExp HsExp
- | HsCase HsExp [HsAlt]
- | HsDo [HsStmt]
- | HsTuple [HsExp]
- | HsList [HsExp]
- | HsParen HsExp
- | HsLeftSection HsExp HsQOp
- | HsRightSection HsQOp HsExp
- | HsRecConstr HsQName [HsFieldUpdate]
- | HsRecUpdate HsExp [HsFieldUpdate]
- | HsEnumFrom HsExp
- | HsEnumFromTo HsExp HsExp
- | HsEnumFromThen HsExp HsExp
- | HsEnumFromThenTo HsExp HsExp HsExp
- | HsListComp HsExp [HsStmt]
- | HsExpTypeSig SrcLoc HsExp HsQualType
- | HsAsPat HsName HsExp
- | HsWildCard
- | HsIrrPat HsExp
- data HsStmt
- data HsFieldUpdate = HsFieldUpdate HsQName HsExp
- data HsAlt = HsAlt SrcLoc HsPat HsGuardedAlts [HsDecl]
- data HsGuardedAlts
- data HsGuardedAlt = HsGuardedAlt SrcLoc HsExp HsExp
- data HsPat
- data HsPatField = HsPFieldPat HsQName HsPat
- data HsLiteral
- newtype Module = Module String
- data HsQName
- data HsName
- data HsQOp
- data HsOp
- data HsSpecialCon
- data HsCName
- prelude_mod :: Module
- main_mod :: Module
- main_name :: HsName
- unit_con_name :: HsQName
- tuple_con_name :: Int -> HsQName
- list_cons_name :: HsQName
- unit_con :: HsExp
- tuple_con :: Int -> HsExp
- unit_tycon_name :: HsQName
- fun_tycon_name :: HsQName
- list_tycon_name :: HsQName
- tuple_tycon_name :: Int -> HsQName
- unit_tycon :: HsType
- fun_tycon :: HsType
- list_tycon :: HsType
- tuple_tycon :: Int -> HsType
- data SrcLoc = SrcLoc {}
Modules
A Haskell source module.
HsModule SrcLoc Module (Maybe [HsExportSpec]) [HsImportDecl] [HsDecl] |
data HsExportSpec Source
Export specification.
HsEVar HsQName | variable |
HsEAbs HsQName |
|
HsEThingAll HsQName |
|
HsEThingWith HsQName [HsCName] |
|
HsEModuleContents Module |
|
data HsImportDecl Source
Import declaration.
HsImportDecl | |
|
data HsImportSpec Source
Import specification.
HsIVar HsName | variable |
HsIAbs HsName |
|
HsIThingAll HsName |
|
HsIThingWith HsName [HsCName] |
|
Associativity of an operator.
HsAssocNone | non-associative operator (declared with |
HsAssocLeft | left-associative operator (declared with |
HsAssocRight | right-associative operator (declared with |
Declarations
Declaration of a data constructor.
HsConDecl SrcLoc HsName [HsBangType] | ordinary data constructor |
HsRecDecl SrcLoc HsName [([HsName], HsBangType)] | record constructor |
data HsBangType Source
The type of a constructor argument or field, optionally including a strictness annotation.
HsBangedTy HsType | strict component, marked with " |
HsUnBangedTy HsType | non-strict component |
Clauses of a function binding.
The right hand side of a function or pattern binding.
HsUnGuardedRhs HsExp | unguarded right hand side (exp) |
HsGuardedRhss [HsGuardedRhs] | guarded right hand side (gdrhs) |
data HsGuardedRhs Source
A guarded right hand side |
exp =
exp.
The first expression will be Boolean-valued.
Safety level for invoking a foreign entity
Class Assertions and Contexts
data HsQualType Source
A type qualified with a context. An unqualified type has an empty context.
type HsAsst = (HsQName, [HsType]) Source
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.
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
HsInfixApp
s associated to the left. - The
Pretty
instance forHsExp
does not add parentheses in printing.
HsVar HsQName | variable |
HsCon HsQName | data constructor |
HsLit HsLiteral | literal constant |
HsInfixApp HsExp HsQOp HsExp | infix application |
HsApp HsExp HsExp | ordinary application |
HsNegApp HsExp | negation expression |
HsLambda SrcLoc [HsPat] HsExp | lambda expression |
HsLet [HsDecl] HsExp | local declarations with |
HsIf HsExp HsExp HsExp |
|
HsCase HsExp [HsAlt] |
|
HsDo [HsStmt] |
|
HsTuple [HsExp] | tuple expression |
HsList [HsExp] | list expression |
HsParen HsExp | parenthesized expression |
HsLeftSection HsExp HsQOp | left section |
HsRightSection HsQOp HsExp | right section |
HsRecConstr HsQName [HsFieldUpdate] | record construction expression |
HsRecUpdate HsExp [HsFieldUpdate] | record update expression |
HsEnumFrom HsExp | unbounded arithmetic sequence, incrementing by 1 |
HsEnumFromTo HsExp HsExp | bounded arithmetic sequence, incrementing by 1 |
HsEnumFromThen HsExp HsExp | unbounded arithmetic sequence, with first two elements given |
HsEnumFromThenTo HsExp HsExp HsExp | bounded arithmetic sequence, with first two elements given |
HsListComp HsExp [HsStmt] | list comprehension |
HsExpTypeSig SrcLoc HsExp HsQualType | expression type signature |
HsAsPat HsName HsExp | patterns only |
HsWildCard | patterns only |
HsIrrPat HsExp | patterns only |
This type represents both stmt in a do
-expression,
and qual in a list comprehension.
HsGenerator SrcLoc HsPat HsExp | a generator pat |
HsQualifier HsExp | an exp by itself: in a |
HsLetStmt [HsDecl] | local bindings |
data HsFieldUpdate Source
An fbind in a labeled record construction or update expression.
An alt in a case
expression.
data HsGuardedAlts Source
HsUnGuardedAlt HsExp |
|
HsGuardedAlts [HsGuardedAlt] | gdpat |
data HsGuardedAlt Source
A guarded alternative |
exp ->
exp.
The first expression will be Boolean-valued.
Patterns
A pattern, to be matched against a value.
HsPVar HsName | variable |
HsPLit HsLiteral | literal constant |
HsPNeg HsPat | negated pattern |
HsPInfixApp HsPat HsQName HsPat | pattern with infix data constructor |
HsPApp HsQName [HsPat] | data constructor and argument patterns |
HsPTuple [HsPat] | tuple pattern |
HsPList [HsPat] | list pattern |
HsPParen HsPat | parenthesized pattern |
HsPRec HsQName [HsPatField] | labelled pattern |
HsPAsPat HsName HsPat |
|
HsPWildCard | wildcard pattern ( |
HsPIrrPat HsPat | irrefutable pattern ( |
data HsPatField Source
An fpat in a labeled record pattern.
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.
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 |
Variables, Constructors and Operators
The name of a Haskell module.
This type is used to represent qualified variables, and also qualified constructors.
This type is used to represent variables, and also constructors.
Possibly qualified infix operators (qop), appearing in expressions.
Operators, appearing in infix
declarations.
data HsSpecialCon Source
Constructors with special syntax. These names are never qualified, and always refer to builtin type or data constructors.
A name (cname) of a component of a class or data type in an import
or export specification.
Builtin names
Modules
Main function of a program
Constructors
tuple_con_name :: Int -> HsQName Source
Type constructors
tuple_tycon_name :: Int -> HsQName Source
tuple_tycon :: Int -> HsType Source