|
Data.Generics | Portability | non-portable | Stability | experimental | Maintainer | libraries@haskell.org |
|
|
|
|
Contents |
- Typeable and types-save cast
- The Data class and related types
- Transformations (T), queries (Q), monadic transformations (Q),
- Traversal combinators
- Generic operations: equality, zip, read, show
- Miscellaneous
|
|
Description |
Data types for generic definitions (GHC only).
|
|
Synopsis |
|
class Typeable a where | | | cast :: (Typeable a, Typeable b) => a -> Maybe b | | sameType :: (Typeable a, Typeable b) => a -> b -> Bool | | class (Typeable a) => Data a where | gmapT :: (forall b . (Data b) => b -> b) -> a -> a | gmapQ :: (forall a . (Data a) => a -> u) -> a -> [u] | gmapM :: (Monad m) => (forall a . (Data a) => a -> m a) -> a -> m a | gfoldl :: (forall a b . (Data a) => c (a -> b) -> a -> c b) -> (forall g . g -> c g) -> a -> c a | gfoldr :: (forall a b . (Data a) => a -> c (a -> b) -> c b) -> (forall g . g -> c g) -> a -> c a | conOf :: a -> Constr | consOf :: a -> [Constr] | gunfold :: (forall a b . (Data a) => c (a -> b) -> c b) -> (forall g . g -> c g) -> c a -> Constr -> c a |
| | data Constr = Constr {} | | 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 | | mkT :: (Typeable a, Typeable b) => (b -> b) -> a -> a | | mkQ :: (Typeable a, Typeable b) => r -> (b -> r) -> a -> r | | mkM :: (Typeable a, Typeable b, Typeable (m a), Typeable (m b), Monad m) => (b -> m b) -> a -> m a | | extT :: (Typeable a, Typeable b) => (a -> a) -> (b -> b) -> a -> a | | extQ :: (Typeable a, Typeable b) => (a -> q) -> (b -> q) -> a -> q | | extM :: (Typeable a, Typeable b, Typeable (m a), Typeable (m b), Monad m) => (a -> m a) -> (b -> m b) -> a -> m a | | mkTT :: (Typeable a, Typeable b, Typeable c) => (a -> a -> a) -> b -> c -> Maybe c | | everything :: (Data a) => (r -> r -> r) -> (forall a . (Data a) => a -> r) -> a -> r | | something :: (forall a . (Data a) => a -> Maybe u) -> forall a . (Data a) => a -> Maybe u | | everywhere :: (forall a . (Data a) => a -> a) -> forall a . (Data a) => a -> a | | everywhereBut :: GenericQ Bool -> GenericT -> GenericT | | synthesize :: (forall a . (Data a) => a -> s -> s) -> (s -> s -> s) -> s -> forall a . (Data a) => a -> s | | branches :: (Data a) => a -> Int | | undefineds :: (Data a) => Constr -> Maybe a | | geq :: forall a . (Data a) => a -> a -> Bool | | gzip :: (forall a b . (Data a, Data b) => a -> b -> Maybe b) -> forall a b . (Data a, Data b) => a -> b -> Maybe b | | gshow :: (Data a) => a -> String | | gread :: (Data a) => String -> Maybe (a, String) | | match :: (Typeable a, Typeable b) => (a -> Bool) -> b -> Maybe a | | tick :: (Typeable a, Typeable b) => (a -> Bool) -> b -> Int | | count :: (Typeable a, Data b) => (a -> Bool) -> b -> Int | | alike :: (Typeable a, Typeable b) => (a -> Bool) -> b -> Bool |
|
|
|
Typeable and types-save cast |
|
class Typeable a where |
The class Typeable allows a concrete representation of a type to
be calculated. | | Methods | typeOf :: a -> TypeRep | Takes a value of type a and returns a concrete representation
of that type. The value of the argument should be ignored by
any instance of Typeable, so that it is safe to pass undefined as
the argument. |
| | Instances | Typeable Exception | Typeable IOException | Typeable ArithException | Typeable ArrayException | Typeable AsyncException | (Typeable a, Typeable b) => Typeable (ST a b) | (Typeable a, Typeable b) => Typeable (Array a b) | (Typeable a, Typeable b) => Typeable (UArray a b) | (Typeable a, Typeable b, Typeable c) => Typeable (STArray a b c) | (Typeable a, Typeable b, Typeable c) => Typeable (STUArray a b c) | (Typeable a, Typeable b) => Typeable (IOArray a b) | (Typeable a, Typeable b) => Typeable (IOUArray a b) | (Typeable a) => Typeable (Complex a) | (Typeable a) => Typeable [a] | Typeable () | (Typeable a, Typeable b) => Typeable (a, b) | (Typeable a, Typeable b, Typeable c) => Typeable (a, b, c) | (Typeable a, Typeable b, Typeable c, Typeable d) => Typeable (a, b, c, d) | (Typeable a, Typeable b, Typeable c, Typeable d, Typeable e) => Typeable (a, b, c, d, e) | (Typeable a, Typeable b) => Typeable (a -> b) | Typeable Bool | Typeable Char | Typeable Float | Typeable Double | Typeable Int | Typeable Integer | (Typeable a, Typeable b) => Typeable (Either a b) | (Typeable a) => Typeable (IO a) | (Typeable a) => Typeable (Maybe a) | Typeable Ordering | Typeable Handle | (Typeable a) => Typeable (Ptr a) | (Typeable a) => Typeable (StablePtr a) | Typeable Int8 | Typeable Int16 | Typeable Int32 | Typeable Int64 | Typeable Word8 | Typeable Word16 | Typeable Word32 | Typeable Word64 | Typeable TyCon | Typeable TypeRep | Typeable Dynamic | (Typeable a) => Typeable (IORef a) | Typeable PackedString | (Typeable a, Typeable b) => Typeable (STRef a b) | Typeable CChar | Typeable CSChar | Typeable CUChar | Typeable CShort | Typeable CUShort | Typeable CInt | Typeable CUInt | Typeable CLong | Typeable CULong | Typeable CLLong | Typeable CULLong | Typeable CFloat | Typeable CDouble | Typeable CLDouble | Typeable CPtrdiff | Typeable CSize | Typeable CWchar | Typeable CSigAtomic | Typeable CClock | Typeable CTime | (Typeable a) => Typeable (ForeignPtr a) | (Typeable a) => Typeable (StableName a) | (Typeable a) => Typeable (Weak a) | Typeable CDev | Typeable CIno | Typeable CMode | Typeable COff | Typeable CPid | Typeable CSsize | Typeable CGid | Typeable CNlink | Typeable CUid | Typeable CCc | Typeable CSpeed | Typeable CTcflag | Typeable CRLim | Typeable Fd |
|
|
|
cast :: (Typeable a, Typeable b) => a -> Maybe b |
The type-safe cast operation |
|
sameType :: (Typeable a, Typeable b) => a -> b -> Bool |
Test two entities to be of the same type |
|
The Data class and related types |
|
class (Typeable a) => Data a where |
| Methods | gmapT :: (forall b . (Data b) => b -> b) -> a -> a | | gmapQ :: (forall a . (Data a) => a -> u) -> a -> [u] | | gmapM :: (Monad m) => (forall a . (Data a) => a -> m a) -> a -> m a | | gfoldl :: (forall a b . (Data a) => c (a -> b) -> a -> c b) -> (forall g . g -> c g) -> a -> c a | | gfoldr :: (forall a b . (Data a) => a -> c (a -> b) -> c b) -> (forall g . g -> c g) -> a -> c a | | conOf :: a -> Constr | Find the constructor | | consOf :: a -> [Constr] | Does not look at a; Could live in Typeable as well maybe | | gunfold :: (forall a b . (Data a) => c (a -> b) -> c b) -> (forall g . g -> c g) -> c a -> Constr -> c a |
| | Instances | |
|
|
data Constr |
Describes a constructor | Constructors | |
|
|
Transformations (T), queries (Q), monadic transformations (Q), |
|
type GenericT = forall a . (Data a) => a -> a |
Instructive type synonyms |
|
type GenericQ r = forall a . (Data a) => a -> r |
|
type GenericM m = forall a . (Data a) => a -> m a |
|
mkT :: (Typeable a, Typeable b) => (b -> b) -> a -> a |
Apply a function if appropriate or preserve term |
|
mkQ :: (Typeable a, Typeable b) => r -> (b -> r) -> a -> r |
Apply a function if appropriate or return a constant |
|
mkM :: (Typeable a, Typeable b, Typeable (m a), Typeable (m b), Monad m) => (b -> m b) -> a -> m a |
Apply a monadic transformation if appropriate; resort to return otherwise |
|
extT :: (Typeable a, Typeable b) => (a -> a) -> (b -> b) -> a -> a |
Extend a transformation |
|
extQ :: (Typeable a, Typeable b) => (a -> q) -> (b -> q) -> a -> q |
Extend a query |
|
extM :: (Typeable a, Typeable b, Typeable (m a), Typeable (m b), Monad m) => (a -> m a) -> (b -> m b) -> a -> m a |
Extend a monadic transformation |
|
mkTT :: (Typeable a, Typeable b, Typeable c) => (a -> a -> a) -> b -> c -> Maybe c |
Make a twin transformation
Note: Should be worked on |
|
Traversal combinators |
|
everything :: (Data a) => (r -> r -> r) -> (forall a . (Data a) => a -> r) -> a -> r |
Summarise all nodes in top-down, left-to-right |
|
something :: (forall a . (Data a) => a -> Maybe u) -> forall a . (Data a) => a -> Maybe u |
Look up something by means of a recognizer |
|
everywhere :: (forall a . (Data a) => a -> a) -> forall a . (Data a) => a -> a |
Apply a transformation everywhere in bottom-up manner |
|
everywhereBut :: GenericQ Bool -> GenericT -> GenericT |
Variation with stop condition |
|
synthesize :: (forall a . (Data a) => a -> s -> s) -> (s -> s -> s) -> s -> forall a . (Data a) => a -> s |
Bottom-up synthesis of a data structure |
|
branches :: (Data a) => a -> Int |
Count immediate subterms |
|
undefineds :: (Data a) => Constr -> Maybe a |
Construct term with undefined subterms |
|
Generic operations: equality, zip, read, show |
|
geq :: forall a . (Data a) => a -> a -> Bool |
Generic equality |
|
gzip :: (forall a b . (Data a, Data b) => a -> b -> Maybe b) -> forall a b . (Data a, Data b) => a -> b -> Maybe b |
Generic zip |
|
gshow :: (Data a) => a -> String |
|
gread :: (Data a) => String -> Maybe (a, String) |
|
Miscellaneous |
|
match :: (Typeable a, Typeable b) => (a -> Bool) -> b -> Maybe a |
Turn a predicate into a filter |
|
tick :: (Typeable a, Typeable b) => (a -> Bool) -> b -> Int |
Turn a predicate into a ticker |
|
count :: (Typeable a, Data b) => (a -> Bool) -> b -> Int |
Turn a ticker into a counter |
|
alike :: (Typeable a, Typeable b) => (a -> Bool) -> b -> Bool |
Lift a monomorphic predicate to the polymorphic level |
|
Produced by Haddock version 0.4 |