Safe Haskell | None |
---|
All of the functions below work only on «interesting» subterms It is up to the instance writer to decide which subterms are
interesting and which subterms should count as immediate. This can
also depend on the context c
.
The context, denoted c
, is a constraint (of kind * -> Constraint
)
that provides additional facilities to work with the data. Most
functions take an implicit parameter ?c :: p c
; it's
used to disambugate which context you are referring to. p
can be
Proxy
from the tagged
package or any other suitable type
constructor.
For more information, see:
- Scrap your boilerplate with class
- http://research.microsoft.com/en-us/um/people/simonpj/papers/hmap/
- Generalizing generic fold
- http://ro-che.info/articles/2013-03-11-generalizing-gfoldl.html
- class GTraversable c a where
- gtraverse :: (Applicative f, [c :: p c]) => (forall d. c d => d -> f d) -> a -> f a
- gmap :: (GTraversable c a, [c :: p c]) => (forall d. c d => d -> d) -> a -> a
- gmapM :: (Monad m, GTraversable c a, [c :: p c]) => (forall d. c d => d -> m d) -> a -> m a
- gfoldMap :: (Monoid r, GTraversable c a, [c :: p c]) => (forall d. c d => d -> r) -> a -> r
- gfoldr :: (GTraversable c a, [c :: p c]) => (forall d. c d => d -> r -> r) -> r -> a -> r
- gfoldl' :: (GTraversable c a, [c :: p c]) => (forall d. c d => r -> d -> r) -> r -> a -> r
- class (GTraversable (Rec c) a, c a) => Rec c a
- everywhere :: forall a c p. (Rec c a, [c :: p c]) => (forall d. Rec c d => d -> d) -> a -> a
- everywhere' :: forall a c p. (Rec c a, [c :: p c]) => (forall d. Rec c d => d -> d) -> a -> a
- everywhereM :: forall m a c p. (Monad m, Rec c a, [c :: p c]) => (forall d. Rec c d => d -> m d) -> a -> m a
- everything :: forall r a c p. (Rec c a, [c :: p c]) => (r -> r -> r) -> (forall d. Rec c d => d -> r) -> a -> r
Open recursion combinators
class GTraversable c a whereSource
gtraverse :: (Applicative f, [c :: p c]) => (forall d. c d => d -> f d) -> a -> f aSource
Applicative traversal over (a subset of) immediate subterms. This is
a generic version of traverse
from Data.Traversable.
The supplied function is applied only to the «interesting» subterms
Other subterms are lifted using pure
, and the whole structure is
folded back using <*>
.
gtraverse
has a default implementation const pure
, which works for
types without interesting subterms (in particular, atomic types).
GTraversable c Ordering | |
GTraversable c Char | |
GTraversable c Double | |
GTraversable c Float | |
GTraversable c Integer | |
GTraversable c Int | |
GTraversable c Bool | |
GTraversable c () | |
GTraversable c (Ratio n) | |
c0 a0 => GTraversable c0 (Maybe a0) | |
c a => GTraversable c [a] | |
(c0 a0, c0 b0) => GTraversable c0 (Either a0 b0) | |
(c0 a0, c0 b0) => GTraversable c0 (a0, b0) | |
(c0 a0, c0 b0, c0 c1) => GTraversable c0 (a0, b0, c1) |
gmap :: (GTraversable c a, [c :: p c]) => (forall d. c d => d -> d) -> a -> aSource
Generic map over the immediate subterms
gmapM :: (Monad m, GTraversable c a, [c :: p c]) => (forall d. c d => d -> m d) -> a -> m aSource
Generic monadic map over the immediate subterms
gfoldMap :: (Monoid r, GTraversable c a, [c :: p c]) => (forall d. c d => d -> r) -> a -> rSource
Generic monoidal fold over the immediate subterms (cf. foldMap
from
Data.Foldable)
gfoldr :: (GTraversable c a, [c :: p c]) => (forall d. c d => d -> r -> r) -> r -> a -> rSource
Generic right fold over the immediate subterms
gfoldl' :: (GTraversable c a, [c :: p c]) => (forall d. c d => r -> d -> r) -> r -> a -> rSource
Generic strict left fold over the immediate subterms
Closed recursion combinators
class (GTraversable (Rec c) a, c a) => Rec c a Source
Rec
enables "deep traversals".
It is satisfied automatically when its superclass constraints are satisfied — you are not supposed to declare new instances of this class.
(GTraversable (Rec c) a, c a) => Rec c a |
everywhere :: forall a c p. (Rec c a, [c :: p c]) => (forall d. Rec c d => d -> d) -> a -> aSource
Apply a transformation everywhere in bottom-up manner
everywhere' :: forall a c p. (Rec c a, [c :: p c]) => (forall d. Rec c d => d -> d) -> a -> aSource
Apply a transformation everywhere in top-down manner
everywhereM :: forall m a c p. (Monad m, Rec c a, [c :: p c]) => (forall d. Rec c d => d -> m d) -> a -> m aSource
Monadic variation on everywhere
everything :: forall r a c p. (Rec c a, [c :: p c]) => (r -> r -> r) -> (forall d. Rec c d => d -> r) -> a -> rSource
Strict left fold over all elements, top-down