StrategyLib-4.0.0.0ContentsIndex
Data.Generics.Strafunski.StrategyLib.TraversalTheme
Portabilityportable
Stabilityexperimental
MaintainerRalf Laemmel, Joost Visser
Contents
Recursive traversal
Full traversals
Traversals with stop conditions
Single hit traversal
Traversal with environment propagation
One-layer traversal
Defined versions of some primitive one-layer traversal combinators
Recursive completion of one-layer traversal
Overloading and synonyms
Overloaded schemes for traversal
Some synonyms for convenience
Description
This module is part of StrategyLib, a library of functional strategy combinators, including combinators for generic traversal. This module defines traversal schemes. Such schemes have formed the core of StrategyLib since its first release. The portfolio as it stands now captures part of the design in the paper ... Polymorphic Symphony.
Synopsis
full_tdTP :: Monad m => TP m -> TP m
full_buTP :: Monad m => TP m -> TP m
full_tdTU :: (Monad m, Monoid a) => TU a m -> TU a m
stop_tdTP :: MonadPlus m => TP m -> TP m
stop_tdTU :: (MonadPlus m, Monoid a) => TU a m -> TU a m
once_tdTP :: MonadPlus m => TP m -> TP m
once_tdTU :: MonadPlus m => TU a m -> TU a m
once_buTP :: MonadPlus m => TP m -> TP m
once_buTU :: MonadPlus m => TU a m -> TU a m
once_peTU :: MonadPlus m => e -> (e -> TU e m) -> (e -> TU a m) -> TU a m
anyTP' :: MonadPlus m => TP m -> TP m
someTP' :: MonadPlus m => TP m -> TP m
all_recTU :: (Monoid a, Monad m) => (t -> TU a m -> TU a m) -> t -> TU a m
one_recTU :: MonadPlus m => (t -> TU a m -> TU a m) -> t -> TU a m
full_td :: StrategyMonoid s m => s m -> s m
once_td :: StrategyPlus s m => s m -> s m
once_bu :: StrategyPlus s m => s m -> s m
once_pe :: StrategyPlus s m => (e -> s m) -> (e -> TU e m) -> e -> s m
topdown :: Monad m => TP m -> TP m
crush :: (Monad m, Monoid u) => TU u m -> TU u m
collect :: Monad m => TU [a] m -> TU [a] m
select :: MonadPlus m => TU u m -> TU u m
selectenv :: MonadPlus m => e -> (e -> TU e m) -> (e -> TU a m) -> TU a m
Recursive traversal
Full traversals
full_tdTP :: Monad m => TP m -> TP m
Full type-preserving traversal in top-down order.
full_buTP :: Monad m => TP m -> TP m
Full type-preserving traversal in bottom-up order.
full_tdTU :: (Monad m, Monoid a) => TU a m -> TU a m
Full type-unifying traversal in top-down order.
Traversals with stop conditions
stop_tdTP :: MonadPlus m => TP m -> TP m
Top-down type-preserving traversal that is cut of below nodes where the argument strategy succeeds.
stop_tdTU :: (MonadPlus m, Monoid a) => TU a m -> TU a m
Top-down type-unifying traversal that is cut of below nodes where the argument strategy succeeds.
Single hit traversal
once_tdTP :: MonadPlus m => TP m -> TP m
Top-down type-preserving traversal that performs its argument strategy at most once.
once_tdTU :: MonadPlus m => TU a m -> TU a m
Top-down type-unifying traversal that performs its argument strategy at most once.
once_buTP :: MonadPlus m => TP m -> TP m
Bottom-up type-preserving traversal that performs its argument strategy at most once.
once_buTU :: MonadPlus m => TU a m -> TU a m
Bottom-up type-unifying traversal that performs its argument strategy at most once.
Traversal with environment propagation
once_peTU
:: MonadPlus m
=> einitial environment
-> (e -> TU e m)environment modification at downward step
-> (e -> TU a m)extraction of value, dependent on environment
-> TU a m
Top-down type-unifying traversal with propagation of an environment.
One-layer traversal
Defined versions of some primitive one-layer traversal combinators
anyTP' :: MonadPlus m => TP m -> TP m
Use anyTP instead.
someTP' :: MonadPlus m => TP m -> TP m
Use someTP instead.
Recursive completion of one-layer traversal
all_recTU
:: (Monoid a, Monad m)
=> (t -> TU a m -> TU a m)binary strategy combinator
-> targument strategy
-> TU a mresult strategy
Recursive completion of full type-preserving one-layer traverasal
one_recTU
:: MonadPlus m
=> (t -> TU a m -> TU a m)binary strategy combinator
-> targument strategy
-> TU a mresult strategy
Recursive completion of type-preserving one-layer traversal that succeeds exactly once.
Overloading and synonyms
Overloaded schemes for traversal
full_td :: StrategyMonoid s m => s m -> s m
Full top-down traversal (overloaded between TU and TP).
once_td :: StrategyPlus s m => s m -> s m
One-hit top-down traversal (overloaded between TU and TP).
once_bu :: StrategyPlus s m => s m -> s m
One-hit bottom-up traversal (overloaded between TU and TP).
once_pe :: StrategyPlus s m => (e -> s m) -> (e -> TU e m) -> e -> s m
One-hit top-down traversal with environment propagation (overloaded between TU and TP).
Some synonyms for convenience
topdown :: Monad m => TP m -> TP m
See full_tdTP.
crush :: (Monad m, Monoid u) => TU u m -> TU u m
See full_tdTU.
collect :: Monad m => TU [a] m -> TU [a] m
Type-specialised version of crush, which works with lists instead of any arbitrary monoid.
select :: MonadPlus m => TU u m -> TU u m
See once_tdTU.
selectenv :: MonadPlus m => e -> (e -> TU e m) -> (e -> TU a m) -> TU a m
See once_peTU.
Produced by Haddock version 0.8