|
Data.Generics.Reify | Portability | non-portable | Stability | experimental | Maintainer | libraries@haskell.org |
|
|
|
|
|
Description |
"Scrap your boilerplate" --- Generic programming in Haskell
See http://www.cs.vu.nl/boilerplate/. The present module provides
some preliminary support some sort of structural reflection. This
module is presumably less common sense that most other boilerplate
modules. Also, it is a bit less easy-going.
|
|
Synopsis |
|
|
|
|
Types as values |
|
type TypeVal a = a -> () |
Type as values to stipulate use of undefineds |
|
typeVal :: TypeVal a |
The value that denotes a type |
|
sameType :: (Typeable a, Typeable b) => TypeVal a -> TypeVal b -> Bool |
Test for type equivalence |
|
val2type :: a -> TypeVal a |
Map a value to its type |
|
type2val :: TypeVal a -> a |
Stipulate this idiom! |
|
withType :: a -> TypeVal a -> a |
Constrain a type |
|
argType :: (a -> b) -> TypeVal a |
The argument type of a function |
|
resType :: (a -> b) -> TypeVal b |
The result type of a function |
|
paraType :: t a -> TypeVal a |
The parameter type of type constructor |
|
type TypeFun a r = TypeVal a -> r |
|
type GTypeFun r = forall a . Data a => TypeFun a r |
|
extType :: (Data a, Typeable r) => GTypeFun r -> TypeFun a r -> GTypeFun r |
Extend a type function |
|
Generic operations to reify terms |
|
glength :: GenericQ Int |
Count the number of immediate subterms of the given term |
|
gcount :: GenericQ Bool -> GenericQ Int |
Determine the number of all suitable nodes in a given term |
|
gnodecount :: GenericQ Int |
Determine the number of all nodes in a given term |
|
gtypecount :: Typeable a => (a -> ()) -> GenericQ Int |
Determine the number of nodes of a given type in a given term |
|
gfindtype :: (Data x, Data y) => x -> Maybe y |
Find (unambiguously) an immediate subterm of a given type |
|
Generic operations to reify types |
|
gmapType :: ([(Constr, r')] -> r) -> GTypeFun (Constr -> r') -> GTypeFun r |
Query all constructors of a given type |
|
gmapConstr :: ([r] -> r') -> GTypeFun r -> GTypeFun (Constr -> r') |
Query all subterm types of a given constructor |
|
constrArity :: GTypeFun (Constr -> Int) |
Compute arity of a given constructor |
|
gmapSubtermTypes :: (Data a, Typeable r) => (r -> r -> r) -> r -> GTypeFun r -> TypeVal a -> r |
Query all immediate subterm types of a given type |
|
gmapSubtermTypesConst :: (Data a, Typeable r) => (r -> r -> r) -> r -> GTypeFun r -> TypeVal a -> r |
Query all immediate subterm types.
There is an extra argument to "constant out" the type at hand.
This can be used to avoid cycles. |
|
gcountSubtermTypes :: Data a => TypeVal a -> Int |
|
reachableType :: (Data a, Data b) => TypeVal a -> TypeVal b -> Bool |
Reachability relation on types, i.e.,
test if nodes of type a are reachable from nodes of type b.
The relation is defined to be reflexive. |
|
depthOfType :: GTypeFun Bool -> GTypeFun (Maybe (Constr, Maybe Int)) |
Depth of a datatype as the constructor with the minimum depth.
The outermost Nothing denotes a type without constructors.
The innermost Nothing denotes potentially infinite. |
|
depthOfConstr :: GTypeFun Bool -> GTypeFun (Constr -> Maybe Int) |
Depth of a constructor.
Depth is viewed as the maximum depth of all subterm types + 1.
Nothing denotes potentially infinite. |
|
Produced by Haddock version 0.6 |