Strafunski-StrategyLib-5.0.1.0: Library for strategic programming

MaintainerRalf Laemmel, Joost Visser
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Data.Generics.Strafunski.StrategyLib.TraversalTheme

Contents

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

Recursive traversal

Full traversals

full_tdTP :: Monad m => TP m -> TP m Source #

Full type-preserving traversal in top-down order.

full_buTP :: Monad m => TP m -> TP m Source #

Full type-preserving traversal in bottom-up order.

full_tdTU :: (Monad m, Monoid a) => TU a m -> TU a m Source #

Full type-unifying traversal in top-down order.

Traversals with stop conditions

stop_tdTP :: MonadPlus m => TP m -> TP m Source #

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 Source #

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 Source #

Top-down type-preserving traversal that performs its argument strategy at most once.

once_tdTU :: MonadPlus m => TU a m -> TU a m Source #

Top-down type-unifying traversal that performs its argument strategy at most once.

once_buTP :: MonadPlus m => TP m -> TP m Source #

Bottom-up type-preserving traversal that performs its argument strategy at most once.

once_buTU :: MonadPlus m => TU a m -> TU a m Source #

Bottom-up type-unifying traversal that performs its argument strategy at most once.

Traversal with environment propagation

once_peTU Source #

Arguments

:: MonadPlus m 
=> e

initial 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 Source #

Use anyTP instead.

someTP' :: MonadPlus m => TP m -> TP m Source #

Use someTP instead.

Recursive completion of one-layer traversal

all_recTU Source #

Arguments

:: (Monoid a, Monad m) 
=> (t -> TU a m -> TU a m)

binary strategy combinator

-> t

argument strategy

-> TU a m

result strategy

Recursive completion of full type-preserving one-layer traverasal

one_recTU Source #

Arguments

:: MonadPlus m 
=> (t -> TU a m -> TU a m)

binary strategy combinator

-> t

argument strategy

-> TU a m

result 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 Source #

Full top-down traversal (overloaded between TU and TP).

once_td :: StrategyPlus s m => s m -> s m Source #

One-hit top-down traversal (overloaded between TU and TP).

once_bu :: StrategyPlus s m => s m -> s m Source #

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 Source #

One-hit top-down traversal with environment propagation (overloaded between TU and TP).

Some synonyms for convenience

topdown :: Monad m => TP m -> TP m Source #

crush :: (Monad m, Monoid u) => TU u m -> TU u m Source #

collect :: Monad m => TU [a] m -> TU [a] m Source #

Type-specialised version of crush, which works with lists instead of any arbitrary monoid.

select :: MonadPlus m => TU u m -> TU u m Source #

selectenv :: MonadPlus m => e -> (e -> TU e m) -> (e -> TU a m) -> TU a m Source #