Haskell Core Libraries (haskell-src package)ParentContentsIndex
Language.Haskell.Syntax
Portability portable
Stability experimental
Maintainer libraries@haskell.org
Contents
Modules
Declarations
Class Assertions and Contexts
Types
Expressions
Patterns
Literals
Variables, Constructors and Operators
Builtin names
Modules
Main function of a program
Constructors
Special identifiers
Type constructors
Source coordinates
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

Synopsis
data HsModule = HsModule SrcLoc Module (Maybe [HsExportSpec]) [HsImportDecl] [HsDecl]
data HsExportSpec
= HsEVar HsQName
| HsEAbs HsQName
| HsEThingAll HsQName
| HsEThingWith HsQName [HsCName]
| HsEModuleContents Module
data HsImportDecl = HsImportDecl SrcLoc Module Bool (Maybe Module) (Maybe (Bool, [HsImportSpec]))
data HsImportSpec
= HsIVar HsName
| HsIAbs HsName
| HsIThingAll HsName
| HsIThingWith HsName [HsCName]
data HsAssoc
= HsAssocNone
| HsAssocLeft
| HsAssocRight
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]
data HsConDecl
= HsConDecl SrcLoc HsName [HsBangType]
| HsRecDecl SrcLoc HsName [([HsName], HsBangType)]
data HsBangType
= HsBangedTy HsType
| HsUnBangedTy HsType
data HsMatch = HsMatch SrcLoc HsName [HsPat] HsRhs [HsDecl]
data HsRhs
= HsUnGuardedRhs HsExp
| HsGuardedRhss [HsGuardedRhs]
data HsGuardedRhs = HsGuardedRhs SrcLoc HsExp HsExp
data HsQualType = HsQualType HsContext HsType
type HsContext = [HsAsst]
type HsAsst = (HsQName, [HsType])
data HsType
= HsTyFun HsType HsType
| HsTyTuple [HsType]
| HsTyApp HsType HsType
| HsTyVar HsName
| HsTyCon HsQName
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
= HsGenerator SrcLoc HsPat HsExp
| HsQualifier HsExp
| HsLetStmt [HsDecl]
data HsFieldUpdate = HsFieldUpdate HsQName HsExp
data HsAlt = HsAlt SrcLoc HsPat HsGuardedAlts [HsDecl]
data HsGuardedAlts
= HsUnGuardedAlt HsExp
| HsGuardedAlts [HsGuardedAlt]
data HsGuardedAlt = HsGuardedAlt SrcLoc HsExp HsExp
data HsPat
= HsPVar HsName
| HsPLit HsLiteral
| HsPNeg HsPat
| HsPInfixApp HsPat HsQName HsPat
| HsPApp HsQName [HsPat]
| HsPTuple [HsPat]
| HsPList [HsPat]
| HsPParen HsPat
| HsPRec HsQName [HsPatField]
| HsPAsPat HsName HsPat
| HsPWildCard
| HsPIrrPat HsPat
data HsPatField = HsPFieldPat HsQName HsPat
data HsLiteral
= HsInt Integer
| HsChar Char
| HsString String
| HsFrac Rational
| HsCharPrim Char
| HsStringPrim String
| HsIntPrim Integer
| HsFloatPrim Rational
| HsDoublePrim Rational
data Module = Module String
data HsQName
= Qual Module HsName
| UnQual HsName
| Special HsSpecialCon
data HsName
= HsIdent String
| HsSymbol String
data HsQOp
= HsQVarOp HsQName
| HsQConOp HsQName
data HsOp
= HsVarOp HsName
| HsConOp HsName
data HsSpecialCon
= HsUnitCon
| HsListCon
| HsFunCon
| HsTupleCon Int
| HsCons
data HsCName
= HsVarName HsName
| HsConName HsName
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
as_name :: HsName
qualified_name :: HsName
hiding_name :: HsName
minus_name :: HsName
pling_name :: HsName
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 {
srcFilename :: String
srcLine :: Int
srcColumn :: Int
}
Modules
data HsModule
Constructors
HsModule SrcLoc Module (Maybe [HsExportSpec]) [HsImportDecl] [HsDecl]
Instances
Pretty HsModule
data HsExportSpec
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
Pretty HsExportSpec
data HsImportDecl
Import declaration.
Constructors
HsImportDecl SrcLoc Module Bool (Maybe Module) (Maybe (Bool, [HsImportSpec]))
Instances
Pretty HsImportDecl
data HsImportSpec
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
Pretty HsImportSpec
data HsAssoc
Constructors
HsAssocNone
HsAssocLeft
HsAssocRight
Instances
Pretty HsAssoc
Declarations
data HsDecl
Constructors
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]
Instances
Pretty HsDecl
data HsConDecl
Constructors
HsConDecl SrcLoc HsName [HsBangType]
HsRecDecl SrcLoc HsName [([HsName], HsBangType)]
Instances
Pretty HsConDecl
data HsBangType
Constructors
HsBangedTy HsType
HsUnBangedTy HsType
Instances
Pretty HsBangType
data HsMatch
Constructors
HsMatch SrcLoc HsName [HsPat] HsRhs [HsDecl]
Instances
Pretty HsMatch
data HsRhs
Constructors
HsUnGuardedRhs HsExp
HsGuardedRhss [HsGuardedRhs]
Instances
Pretty HsRhs
data HsGuardedRhs
Constructors
HsGuardedRhs SrcLoc HsExp HsExp
Instances
Pretty HsGuardedRhs
Class Assertions and Contexts
data HsQualType
A type qualified with a context. An unqualified type has an empty context.
Constructors
HsQualType HsContext HsType
Instances
Pretty HsQualType
type HsContext = [HsAsst]
type HsAsst = (HsQName, [HsType])
Class assertions. In Haskell 98, the argument would be a tyvar, but this definition allows multiple parameters, and allows them to be types.
Types
data HsType
Constructors
HsTyFun HsType HsType
HsTyTuple [HsType]
HsTyApp HsType HsType
HsTyVar HsName
HsTyCon HsQName
Instances
Pretty HsType
Expressions
data HsExp
Haskell expressions. 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.
Constructors
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] Do expression: The last statement in the list should be an expression.
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 patterns only
HsWildCard patterns only
HsIrrPat HsExp patterns only
Instances
Pretty HsExp
data HsStmt
This type represents both stmt in a do-expression, and qual in a list comprehension.
Constructors
HsGenerator SrcLoc HsPat HsExp
HsQualifier HsExp
HsLetStmt [HsDecl]
Instances
Pretty HsStmt
data HsFieldUpdate
An fbind in a labeled construction or update.
Constructors
HsFieldUpdate HsQName HsExp
Instances
Pretty HsFieldUpdate
data HsAlt
Constructors
HsAlt SrcLoc HsPat HsGuardedAlts [HsDecl]
Instances
Pretty HsAlt
data HsGuardedAlts
Constructors
HsUnGuardedAlt HsExp
HsGuardedAlts [HsGuardedAlt]
Instances
Pretty HsGuardedAlts
data HsGuardedAlt
Constructors
HsGuardedAlt SrcLoc HsExp HsExp
Instances
Pretty HsGuardedAlt
Patterns
data HsPat
Constructors
HsPVar HsName
HsPLit HsLiteral
HsPNeg HsPat
HsPInfixApp HsPat HsQName HsPat
HsPApp HsQName [HsPat]
HsPTuple [HsPat]
HsPList [HsPat]
HsPParen HsPat
HsPRec HsQName [HsPatField]
HsPAsPat HsName HsPat
HsPWildCard
HsPIrrPat HsPat
Instances
Pretty HsPat
data HsPatField
Constructors
HsPFieldPat HsQName HsPat
Instances
Pretty HsPatField
Literals
data HsLiteral
literal
Constructors
HsInt Integer
HsChar Char
HsString String
HsFrac Rational
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
Pretty HsLiteral
Variables, Constructors and Operators
data Module
Constructors
Module String
Instances
Pretty Module
data HsQName
This type is used to represent qualified variables, and also qualified constructors.
Constructors
Qual Module HsName
UnQual HsName
Special HsSpecialCon
Instances
Pretty HsQName
Show HsQName
data HsName
This type is used to represent variables, and also constructors.
Constructors
HsIdent String varid or conid.
HsSymbol String varsym or consym
Instances
Pretty HsName
Show HsName
data HsQOp
Possibly qualified infix operators (qop), appearing in expressions.
Constructors
HsQVarOp HsQName
HsQConOp HsQName
Instances
Pretty HsQOp
Show HsQOp
data HsOp
Operators, appearing in infix declarations.
Constructors
HsVarOp HsName
HsConOp HsName
Instances
Pretty HsOp
Show HsOp
data HsSpecialCon
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
Show HsSpecialCon
data HsCName
Constructors
HsVarName HsName
HsConName HsName
Instances
Pretty HsCName
Show HsCName
Builtin names
Modules
prelude_mod :: Module
main_mod :: Module
Main function of a program
main_name :: HsName
Constructors
unit_con_name :: HsQName
tuple_con_name :: Int -> HsQName
list_cons_name :: HsQName
unit_con :: HsExp
tuple_con :: Int -> HsExp
Special identifiers
as_name :: HsName
qualified_name :: HsName
hiding_name :: HsName
minus_name :: HsName
pling_name :: HsName
Type constructors
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
Source coordinates
data SrcLoc
A position in the source.
Constructors
SrcLoc
srcFilename :: String
srcLine :: Int
srcColumn :: Int
Produced by Haddock version 0.4