| Safe Haskell | None |
|---|
Language.Haskell.FreeTheorems.Syntax
Contents
Description
Declars data types describing the abstract syntax of a subset of Haskell in the FreeTheorems library. Only declarations and type expressions are covered by these data types.
Note that the data types of this module do not reflect Haskell98.
This is because they are able to express higher-rank functions which are
not part of Haskell98.
Also, in type expressions, a type variable must not be applied to any type
expression. Thus, for example, the type m a, as occuring in the functions
of the Monad type class, is not expressable.
The reason for this restriction is that the FreeTheorems library cannot
handle such types.
- data Declaration
- getDeclarationName :: Declaration -> Identifier
- getDeclarationArity :: Declaration -> Maybe Int
- data DataDeclaration = Data {}
- data NewtypeDeclaration = Newtype {}
- data TypeDeclaration = Type {}
- data ClassDeclaration = Class {
- superClasses :: [TypeClass]
- className :: Identifier
- classVar :: TypeVariable
- classFuns :: [Signature]
- data Signature = Signature {}
- data DataConstructorDeclaration = DataCon {}
- data BangTypeExpression
- data TypeExpression
- data TypeConstructor
- newtype TypeClass = TC Identifier
- newtype TypeVariable = TV Identifier
- newtype FixedTypeExpression = TF Identifier
- newtype Identifier = Ident {}
Declarations
data Declaration Source
A Haskell declaration which corresponds to a type, data, newtype,
class or type signature declaration.
In type expressions, type variables must not be applied to type
expressions. Thus, for example, the functions of the Monad class are not
expressible.
However, in extension to Haskell98, higher-rank types can be expressed.
This data type does not reflect all information of a declaration. Only the aspects needed by the FreeTheorems library are covered.
Constructors
| TypeDecl TypeDeclaration | A |
| DataDecl DataDeclaration | A |
| NewtypeDecl NewtypeDeclaration | A |
| ClassDecl ClassDeclaration | A |
| TypeSig Signature | A type signature. |
Instances
getDeclarationName :: Declaration -> IdentifierSource
Gets the name of the item declared by a declaration.
This is the type constructor for data, newtype and type declarations,
the name of a class for a class declaration or the name of a type
signature.
getDeclarationArity :: Declaration -> Maybe IntSource
Gets the arity of a type constructor or Nothing if this is not a
data, newtype or type declaration.
data DataDeclaration Source
A data declaration for an algebraic data type.
Note that the context and the deriving parts of a data declaration are
ignored.
Constructors
| Data | |
Fields
| |
data NewtypeDeclaration Source
A newtype declaration for a type renaming.
Note that the context and the deriving parts of a newtype declaration are
ignored.
Constructors
| Newtype | |
Fields
| |
data TypeDeclaration Source
A type declaration for a type synonym.
Constructors
| Type | |
Fields
| |
data ClassDeclaration Source
A class declaration for a type class.
Note that, except of type signatures of class methods, all other declarations inside the class are ignored.
Constructors
| Class | |
Fields
| |
A type signature.
Constructors
| Signature | |
Fields
| |
data DataConstructorDeclaration Source
A data constructor declaration.
Constructors
| DataCon | |
Fields
| |
data BangTypeExpression Source
Indicates whether in an algebraic data type declaration a strictness annotation is used.
Type expressions
data TypeExpression Source
A Haskell type expression. This data type supports also higher-rank functions. Unlike in Haskell98, a type variable must not be applied to type expressions.
Constructors
| TypeVar TypeVariable | A type variable. |
| TypeCon TypeConstructor [TypeExpression] | A type constructor. This covers algebraic data types, type synonyms, and type renamings as well as predefined standard data types like lists and tuples. |
| TypeFun TypeExpression TypeExpression | The function type constructor |
| TypeFunLab TypeExpression TypeExpression | The function type constructor |
| TypeAbs TypeVariable [TypeClass] TypeExpression | The type abstraction constructor |
| TypeAbsLab TypeVariable [TypeClass] TypeExpression | The type abstraction constructor |
| TypeExp FixedTypeExpression | A variable representing a fixed type expression. |
data TypeConstructor Source
The data type for type constructors.
Constructors
| ConUnit | The unit type constructor |
| ConList | The list type constructor |
| ConTuple Int | The tuple type constructors with given arity. |
| ConInt | The Haskell type |
| ConInteger | The Haskell type |
| ConFloat | The Haskell type |
| ConDouble | The Haskell type |
| ConChar | The Haskell type |
| Con Identifier | Any other type constructor with a given name. |
Identifies a Haskell type class.
Constructors
| TC Identifier |
newtype FixedTypeExpression Source
Represents an abbreviation for some fixed type expression. It does not occur in Haskell98 source code, but it can occur in generated theorems.
Constructors
| TF Identifier |
Identifiers
newtype Identifier Source
An identifier.
This data type tags every String occurring in a declaration or a type
expression.
Constructors
| Ident | |
Fields | |
Instances