| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell98 | 
Language.Haskell.FreeTheorems.BasicSyntax
Description
Declares the basic syntax of a Haskell98 subset enriched with higher-ranked functions. Additionally, it defines small convenience functions.
Synopsis
- data Declaration
- getDeclarationName :: Declaration -> Identifier
- getDeclarationArity :: Declaration -> Maybe Int
- data TypeDeclaration = Type {}
- data DataDeclaration = Data {}
- data NewtypeDeclaration = Newtype {}
- data ClassDeclaration = Class {- superClasses :: [TypeClass]
- className :: Identifier
- classVar :: TypeVariable
- classFuns :: [Signature]
 
- data Signature = Signature {}
- newtype Identifier = Ident {}
- data DataConstructorDeclaration = DataCon {}
- data BangTypeExpression
- data TypeExpression
- data TypeConstructor
- newtype TypeClass = TC Identifier
- newtype TypeVariable = TV Identifier
- newtype FixedTypeExpression = TF Identifier
Documentation
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
| Data Declaration Source # | |
| Defined in Language.Haskell.FreeTheorems.BasicSyntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Declaration -> c Declaration # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Declaration # toConstr :: Declaration -> Constr # dataTypeOf :: Declaration -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Declaration) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Declaration) # gmapT :: (forall b. Data b => b -> b) -> Declaration -> Declaration # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Declaration -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Declaration -> r # gmapQ :: (forall d. Data d => d -> u) -> Declaration -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Declaration -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Declaration -> m Declaration # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Declaration -> m Declaration # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Declaration -> m Declaration # | |
| Show Declaration Source # | |
| Defined in Language.Haskell.FreeTheorems.PrettyTypes Methods showsPrec :: Int -> Declaration -> ShowS # show :: Declaration -> String # showList :: [Declaration] -> ShowS # | |
| Eq Declaration Source # | |
| Defined in Language.Haskell.FreeTheorems.BasicSyntax | |
getDeclarationName :: Declaration -> Identifier Source #
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 Int Source #
Gets the arity of a type constructor or Nothing if this is not a
   data, newtype or type declaration.
data TypeDeclaration Source #
A type declaration for a type synonym.
Constructors
| Type | |
| Fields 
 | |
Instances
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 
 | |
Instances
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 
 | |
Instances
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 
 | |
Instances
A type signature.
Constructors
| Signature | |
| Fields 
 | |
Instances
| Data Signature Source # | |
| Defined in Language.Haskell.FreeTheorems.BasicSyntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Signature -> c Signature # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Signature # toConstr :: Signature -> Constr # dataTypeOf :: Signature -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Signature) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Signature) # gmapT :: (forall b. Data b => b -> b) -> Signature -> Signature # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Signature -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Signature -> r # gmapQ :: (forall d. Data d => d -> u) -> Signature -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Signature -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Signature -> m Signature # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Signature -> m Signature # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Signature -> m Signature # | |
| Show Signature Source # | |
| Eq Signature Source # | |
newtype Identifier Source #
An identifier.
   This data type tags every String occurring in a declaration or a type
   expression.
Constructors
| Ident | |
| Fields | |
Instances
data DataConstructorDeclaration Source #
A data constructor declaration.
Constructors
| DataCon | |
| Fields 
 | |
Instances
data BangTypeExpression Source #
Indicates whether in an algebraic data type declaration a strictness annotation is used.
Constructors
| Banged | A type expression with a strictness flag " | 
| Fields | |
| Unbanged | A type expression without a strictness flag. | 
| Fields | |
Instances
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. | 
Instances
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. | 
Instances
| Data TypeConstructor Source # | |
| Defined in Language.Haskell.FreeTheorems.BasicSyntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeConstructor -> c TypeConstructor # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeConstructor # toConstr :: TypeConstructor -> Constr # dataTypeOf :: TypeConstructor -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TypeConstructor) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeConstructor) # gmapT :: (forall b. Data b => b -> b) -> TypeConstructor -> TypeConstructor # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeConstructor -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeConstructor -> r # gmapQ :: (forall d. Data d => d -> u) -> TypeConstructor -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeConstructor -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeConstructor -> m TypeConstructor # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeConstructor -> m TypeConstructor # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeConstructor -> m TypeConstructor # | |
| Eq TypeConstructor Source # | |
| Defined in Language.Haskell.FreeTheorems.BasicSyntax Methods (==) :: TypeConstructor -> TypeConstructor -> Bool # (/=) :: TypeConstructor -> TypeConstructor -> Bool # | |
Identifies a Haskell type class.
Constructors
| TC Identifier | 
Instances
| Data TypeClass Source # | |
| Defined in Language.Haskell.FreeTheorems.BasicSyntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeClass -> c TypeClass # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeClass # toConstr :: TypeClass -> Constr # dataTypeOf :: TypeClass -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TypeClass) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeClass) # gmapT :: (forall b. Data b => b -> b) -> TypeClass -> TypeClass # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeClass -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeClass -> r # gmapQ :: (forall d. Data d => d -> u) -> TypeClass -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeClass -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeClass -> m TypeClass # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeClass -> m TypeClass # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeClass -> m TypeClass # | |
| Show TypeClass Source # | |
| Eq TypeClass Source # | |
newtype TypeVariable Source #
Identifies a Haskell type variable
Constructors
| TV Identifier | 
Instances
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 |