Copyright | (c) The University of Glasgow CWI 2001--2003 |
---|---|
License | BSD-style (see the LICENSE file) |
Maintainer | generics@haskell.org |
Stability | experimental |
Portability | non-portable (local universal quantification) |
Safe Haskell | Safe-Inferred |
Language | Haskell98 |
"Scrap your boilerplate" --- Generic programming in Haskell See http://www.cs.uu.nl/wiki/GenericProgramming/SYB. The present module provides frequently used generic traversal schemes.
Synopsis
- everywhere :: (forall a. Data a => a -> a) -> forall a. Data a => a -> a
- everywhere' :: (forall a. Data a => a -> a) -> forall a. Data a => a -> a
- everywhereBut :: GenericQ Bool -> GenericT -> GenericT
- everywhereM :: forall m. Monad m => GenericM m -> GenericM m
- somewhere :: forall m. MonadPlus m => GenericM m -> GenericM m
- everything :: forall r. (r -> r -> r) -> GenericQ r -> GenericQ r
- everythingBut :: forall r. (r -> r -> r) -> GenericQ (r, Bool) -> GenericQ r
- everythingWithContext :: forall s r. s -> (r -> r -> r) -> GenericQ (s -> (r, s)) -> GenericQ r
- listify :: Typeable r => (r -> Bool) -> GenericQ [r]
- something :: GenericQ (Maybe u) -> GenericQ (Maybe u)
- synthesize :: forall s t. s -> (t -> s -> s) -> GenericQ (s -> t) -> GenericQ t
- gsize :: Data a => a -> Int
- glength :: GenericQ Int
- gdepth :: GenericQ Int
- gcount :: GenericQ Bool -> GenericQ Int
- gnodecount :: GenericQ Int
- gtypecount :: Typeable a => a -> GenericQ Int
- gfindtype :: (Data x, Typeable y) => x -> Maybe y
Documentation
everywhere :: (forall a. Data a => a -> a) -> forall a. Data a => a -> a Source #
Apply a transformation everywhere in bottom-up manner
Since: 0.1.0.0
everywhere' :: (forall a. Data a => a -> a) -> forall a. Data a => a -> a Source #
Apply a transformation everywhere in top-down manner
Since: 0.1.0.0
everywhereBut :: GenericQ Bool -> GenericT -> GenericT Source #
Variation on everywhere with an extra stop condition
Since: 0.1.0.0
everywhereM :: forall m. Monad m => GenericM m -> GenericM m Source #
Monadic variation on everywhere
Since: 0.1.0.0
somewhere :: forall m. MonadPlus m => GenericM m -> GenericM m Source #
Apply a monadic transformation at least somewhere
Since: 0.1.0.0
everything :: forall r. (r -> r -> r) -> GenericQ r -> GenericQ r Source #
Summarise all nodes in top-down, left-to-right order
Since: 0.1.0.0
everythingBut :: forall r. (r -> r -> r) -> GenericQ (r, Bool) -> GenericQ r Source #
Variation of "everything" with an added stop condition
Since: 0.3
everythingWithContext :: forall s r. s -> (r -> r -> r) -> GenericQ (s -> (r, s)) -> GenericQ r Source #
Summarise all nodes in top-down, left-to-right order, carrying some state down the tree during the computation, but not left-to-right to siblings.
Since: 0.3.7
listify :: Typeable r => (r -> Bool) -> GenericQ [r] Source #
Get a list of all entities that meet a predicate
Since: 0.1.0.0
something :: GenericQ (Maybe u) -> GenericQ (Maybe u) Source #
Look up a subterm by means of a maybe-typed filter
Since: 0.1.0.0
synthesize :: forall s t. s -> (t -> s -> s) -> GenericQ (s -> t) -> GenericQ t Source #
Bottom-up synthesis of a data structure; 1st argument z is the initial element for the synthesis; 2nd argument o is for reduction of results from subterms; 3rd argument f updates the synthesised data according to the given term
Since: 0.1.0.0
glength :: GenericQ Int Source #
Count the number of immediate subterms of the given term
Since: 0.1.0.0
gcount :: GenericQ Bool -> GenericQ Int Source #
Determine the number of all suitable nodes in a given term
Since: 0.1.0.0
gnodecount :: GenericQ Int Source #
Determine the number of all nodes in a given term
Since: 0.1.0.0