syb-0.1.0.1: Scrap Your BoilerplateSource codeContentsIndex
Data.Generics.Aliases
Portabilitynon-portable (local universal quantification)
Stabilityexperimental
Maintainergenerics@haskell.org
Contents
Combinators to "make" generic functions via cast
Type synonyms for generic function types
Inredients of generic functions
Function combinators on generic functions
Type extension for unary type constructors
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' {
unGeneric' :: Generic c
}
newtype GenericT' = GT {
unGT :: Data a => a -> a
}
newtype GenericQ' r = GQ {
unGQ :: GenericQ r
}
newtype GenericM' m = GM {
unGM :: Data a => a -> m a
}
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 e. Data e => e -> e) -> (forall f. Data f => t f -> t f) -> d -> d
ext1M :: (Monad m, Data d, Typeable1 t) => (forall e. Data e => e -> m e) -> (forall f. Data f => t f -> m (t f)) -> d -> m d
ext1Q :: (Data d, Typeable1 t) => (d -> q) -> (forall e. Data e => t e -> q) -> d -> q
ext1R :: (Monad m, Data d, Typeable1 t) => m d -> (forall e. Data e => m (t e)) -> m d
Combinators to "make" generic functions via cast
mkT :: (Typeable a, Typeable b) => (b -> b) -> a -> aSource
Make a generic transformation; start from a type-specific case; preserve the term otherwise
mkQ :: (Typeable a, Typeable b) => r -> (b -> r) -> a -> rSource
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 aSource
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 aSource
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 aSource
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 aSource
Flexible type extension
extT :: (Typeable a, Typeable b) => (a -> a) -> (b -> b) -> a -> aSource
Extend a generic transformation by a type-specific case
extQ :: (Typeable a, Typeable b) => (a -> q) -> (b -> q) -> a -> qSource
Extend a generic query by a type-specific case
extM :: (Monad m, Typeable a, Typeable b) => (a -> m a) -> (b -> m b) -> a -> m aSource
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 aSource
Extend a generic MonadPlus transformation by a type-specific case
extB :: (Typeable a, Typeable b) => a -> b -> aSource
Extend a generic builder
extR :: (Monad m, Typeable a, Typeable b) => m a -> m b -> m aSource
Extend a generic reader
Type synonyms for generic function types
type GenericT = forall a. Data a => a -> aSource
Generic transformations, i.e., take an "a" and return an "a"
type GenericQ r = forall a. Data a => a -> rSource
Generic queries of type "r", i.e., take any "a" and return an "r"
type GenericM m = forall a. Data a => a -> m aSource
Generic monadic transformations, i.e., take an "a" and compute an "a"
type GenericB = forall a. Data a => aSource
Generic builders i.e., produce an "a".
type GenericR m = forall a. Data a => m aSource
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 aSource
The general scheme underlying generic functions assumed by gfoldl; there are isomorphisms such as GenericT = Generic T.
data Generic' c Source
Wrapped generic functions; recall: [Generic c] would be legal but [Generic' c] not.
Constructors
Generic'
unGeneric' :: Generic c
newtype GenericT' Source
Other first-class polymorphic wrappers
Constructors
GT
unGT :: Data a => a -> a
newtype GenericQ' r Source
Constructors
GQ
unGQ :: GenericQ r
newtype GenericM' m Source
Constructors
GM
unGM :: Data a => a -> m a
Inredients of generic functions
orElse :: Maybe a -> Maybe a -> Maybe aSource
Left-biased choice on maybies
Function combinators on generic functions
recoverMp :: MonadPlus m => GenericM m -> GenericM mSource
Recover from the failure of monadic transformation by identity
recoverQ :: MonadPlus m => r -> GenericQ (m r) -> GenericQ (m r)Source
Recover from the failure of monadic query by a constant
choiceMp :: MonadPlus m => GenericM m -> GenericM m -> GenericM mSource
Choice for monadic transformations
choiceQ :: MonadPlus m => GenericQ (m r) -> GenericQ (m r) -> GenericQ (m r)Source
Choice for monadic queries
Type extension for unary type constructors
ext1T :: (Data d, Typeable1 t) => (forall e. Data e => e -> e) -> (forall f. Data f => t f -> t f) -> d -> dSource
Type extension of transformations for unary type constructors
ext1M :: (Monad m, Data d, Typeable1 t) => (forall e. Data e => e -> m e) -> (forall f. Data f => t f -> m (t f)) -> d -> m dSource
Type extension of monadic transformations for type constructors
ext1Q :: (Data d, Typeable1 t) => (d -> q) -> (forall e. Data e => t e -> q) -> d -> qSource
Type extension of queries for type constructors
ext1R :: (Monad m, Data d, Typeable1 t) => m d -> (forall e. Data e => m (t e)) -> m dSource
Type extension of readers for type constructors
Produced by Haddock version 2.4.2