|
Data.Generics.Aliases | Portability | non-portable (local universal quantification) | 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
a number of declarations for typical generic function types,
corresponding type case, and others.
|
|
Synopsis |
|
mkT :: (Typeable a, Typeable b) => (b -> b) -> a -> a | | mkQ :: (Typeable a, Typeable b) => r -> (b -> r) -> a -> r | | mkM :: (Monad m, Typeable a, Typeable b) => (b -> m b) -> a -> m a | | mkMp :: (MonadPlus m, Typeable a, Typeable b) => (b -> m b) -> a -> m a | | mkR :: (MonadPlus m, Typeable a, Typeable b) => m b -> m a | | ext0 :: (Typeable a, Typeable b) => c a -> c b -> c a | | extT :: (Typeable a, Typeable b) => (a -> a) -> (b -> b) -> a -> a | | extQ :: (Typeable a, Typeable b) => (a -> q) -> (b -> q) -> a -> q | | extM :: (Monad m, Typeable a, Typeable b) => (a -> m a) -> (b -> m b) -> a -> m a | | extMp :: (MonadPlus m, Typeable a, Typeable b) => (a -> m a) -> (b -> m b) -> a -> m a | | extB :: (Typeable a, Typeable b) => a -> b -> a | | extR :: (Monad m, Typeable a, Typeable b) => m a -> m b -> m a | | type GenericT = forall a . Data a => a -> a | | type GenericQ r = forall a . Data a => a -> r | | type GenericM m = forall a . Data a => a -> m a | | type GenericB = forall a . Data a => a | | type GenericR m = forall a . Data a => m a | | type Generic c = forall a . Data a => a -> c a | | data Generic' c = Generic' {} | | newtype GenericT' = GT {} | | newtype GenericQ' r = GQ {} | | newtype GenericM' m = GM {} | | orElse :: Maybe a -> Maybe a -> Maybe a | | recoverMp :: MonadPlus m => GenericM m -> GenericM m | | recoverQ :: MonadPlus m => r -> GenericQ (m r) -> GenericQ (m r) | | choiceMp :: MonadPlus m => GenericM m -> GenericM m -> GenericM m | | choiceQ :: MonadPlus m => GenericQ (m r) -> GenericQ (m r) -> GenericQ (m r) | | ext1T :: (Data d, Typeable1 t) => (forall d . Data d => d -> d) -> (forall d . Data d => t d -> t d) -> d -> d | | ext1M :: (Monad m, Data d, Typeable1 t) => (forall d . Data d => d -> m d) -> (forall d . Data d => t d -> m (t d)) -> d -> m d | | ext1Q :: (Data d, Typeable1 t) => (d -> q) -> (forall d . Data d => t d -> q) -> d -> q | | ext1R :: (Monad m, Data d, Typeable1 t) => m d -> (forall d . Data d => m (t d)) -> m d |
|
|
|
Combinators to "make" generic functions via cast
|
|
mkT :: (Typeable a, Typeable b) => (b -> b) -> a -> a |
Make a generic transformation;
start from a type-specific case;
preserve the term otherwise
|
|
mkQ :: (Typeable a, Typeable b) => r -> (b -> r) -> a -> r |
Make a generic query;
start from a type-specific case;
return a constant otherwise
|
|
mkM :: (Monad m, Typeable a, Typeable b) => (b -> m b) -> a -> m a |
Make a generic monadic transformation;
start from a type-specific case;
resort to return otherwise
|
|
mkMp :: (MonadPlus m, Typeable a, Typeable b) => (b -> m b) -> a -> m a |
Make a generic monadic transformation for MonadPlus;
use "const mzero" (i.e., failure) instead of return as default.
|
|
mkR :: (MonadPlus m, Typeable a, Typeable b) => m b -> m a |
Make a generic builder;
start from a type-specific ase;
resort to no build (i.e., mzero) otherwise
|
|
ext0 :: (Typeable a, Typeable b) => c a -> c b -> c a |
Flexible type extension
|
|
extT :: (Typeable a, Typeable b) => (a -> a) -> (b -> b) -> a -> a |
Extend a generic transformation by a type-specific case
|
|
extQ :: (Typeable a, Typeable b) => (a -> q) -> (b -> q) -> a -> q |
Extend a generic query by a type-specific case
|
|
extM :: (Monad m, Typeable a, Typeable b) => (a -> m a) -> (b -> m b) -> a -> m a |
Extend a generic monadic transformation by a type-specific case
|
|
extMp :: (MonadPlus m, Typeable a, Typeable b) => (a -> m a) -> (b -> m b) -> a -> m a |
Extend a generic MonadPlus transformation by a type-specific case
|
|
extB :: (Typeable a, Typeable b) => a -> b -> a |
Extend a generic builder
|
|
extR :: (Monad m, Typeable a, Typeable b) => m a -> m b -> m a |
Extend a generic reader
|
|
Type synonyms for generic function types
|
|
type GenericT = forall a . Data a => a -> a |
Generic transformations,
i.e., take an "a" and return an "a"
|
|
type GenericQ r = forall a . Data a => a -> r |
Generic queries of type "r",
i.e., take any "a" and return an "r"
|
|
type GenericM m = forall a . Data a => a -> m a |
Generic monadic transformations,
i.e., take an "a" and compute an "a"
|
|
type GenericB = forall a . Data a => a |
Generic builders
i.e., produce an "a".
|
|
type GenericR m = forall a . Data a => m a |
Generic readers, say monadic builders,
i.e., produce an "a" with the help of a monad "m".
|
|
type Generic c = forall a . Data a => a -> c a |
The general scheme underlying generic functions
assumed by gfoldl; there are isomorphisms such as
GenericT = Generic T.
|
|
data Generic' c |
Wrapped generic functions;
recall: [Generic c] would be legal but [Generic' c] not.
| Constructors | |
|
|
newtype GenericT' |
Other first-class polymorphic wrappers
| Constructors | GT | | unGT :: (Data a => a -> a) | |
|
|
|
|
newtype GenericQ' r |
|
|
newtype GenericM' m |
Constructors | GM | | unGM :: (Data a => a -> m a) | |
|
|
|
|
Inredients of generic functions
|
|
orElse :: Maybe a -> Maybe a -> Maybe a |
Left-biased choice on maybies
|
|
Function combinators on generic functions
|
|
recoverMp :: MonadPlus m => GenericM m -> GenericM m |
Recover from the failure of monadic transformation by identity
|
|
recoverQ :: MonadPlus m => r -> GenericQ (m r) -> GenericQ (m r) |
Recover from the failure of monadic query by a constant
|
|
choiceMp :: MonadPlus m => GenericM m -> GenericM m -> GenericM m |
Choice for monadic transformations
|
|
choiceQ :: MonadPlus m => GenericQ (m r) -> GenericQ (m r) -> GenericQ (m r) |
Choice for monadic queries
|
|
Type extension for unary type constructors
|
|
ext1T :: (Data d, Typeable1 t) => (forall d . Data d => d -> d) -> (forall d . Data d => t d -> t d) -> d -> d |
Type extension of transformations for unary type constructors
|
|
ext1M :: (Monad m, Data d, Typeable1 t) => (forall d . Data d => d -> m d) -> (forall d . Data d => t d -> m (t d)) -> d -> m d |
Type extension of monadic transformations for type constructors
|
|
ext1Q :: (Data d, Typeable1 t) => (d -> q) -> (forall d . Data d => t d -> q) -> d -> q |
Type extension of queries for type constructors
|
|
ext1R :: (Monad m, Data d, Typeable1 t) => m d -> (forall d . Data d => m (t d)) -> m d |
Type extension of readers for type constructors
|
|
Produced by Haddock version 0.8 |