Strafunski-StrategyLib-5.0.0.5: Library for strategic programming

MaintainerRalf Laemmel, Joost Visser
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Data.Generics.Strafunski.StrategyLib.OverloadingTheme

Contents

Description

This module is part of StrategyLib, a library of functional strategy combinators, including combinators for generic traversal. This module overloads basic combinators to enable uniform treatment of TU and TP strategies. The overloading scheme is motivated in the "... Polymorphic Symphony" paper. The names in the present module deviate from the paper in that they are postfixed by an "...S" in order to rule out name clashes and to avoid labour-intensive resolution. The class constraints in this module seem to be outrageous but this has to do with a type inferencing bug for class hierarchies in hugs. This bug is removed in the October 2002 release.

Synopsis

Unconstrained

class Monad m => Strategy s m where Source

Overload completely unconstrained strategy combinators

Methods

voidS :: s m -> TU () m Source

seqS :: TP m -> s m -> s m Source

Sequential composition

passS :: TU a m -> (a -> s m) -> s m Source

Sequential composition with value passing

Instances

Monad m => Strategy TP m 
Monad m => Strategy (TU a) m 

class (Strategy s m, Monad m, Term t) => StrategyApply s m t x | s t -> x where Source

Overload apply and adhoc combinators

Methods

applyS :: s m -> t -> m x Source

Strategy application

adhocS :: s m -> (t -> m x) -> s m Source

Dynamic type case

Instances

(Monad m, Term t) => StrategyApply TP m t t 
(Monad m, Term t) => StrategyApply (TU a) m t a 

Involving Monoid, MonadPlus,

class (Monad m, Strategy s m) => StrategyMonoid s m where Source

Overload basic combinators which might involve a monoid

Methods

skipS :: s m Source

Identity (success)

allS :: s m -> s m Source

Push down to all children

combS :: s m -> s m -> s m Source

Combine sequentially

Instances

(Monad m, Strategy TP m) => StrategyMonoid TP m 
(Monad m, Monoid u, Strategy (TU u) m) => StrategyMonoid (TU u) m 

class (Strategy s m, Monad m, MonadPlus m) => StrategyPlus s m where Source

Overload basic combinators which involve MonadPlus

Methods

failS :: s m Source

Failure

choiceS :: s m -> s m -> s m Source

Choice

oneS :: s m -> s m Source

Push down to a single child

Instances

(Monad m, MonadPlus m, Strategy TP m) => StrategyPlus TP m 
(Monad m, MonadPlus m, Strategy (TU u) m) => StrategyPlus (TU u) m 

monoS :: (StrategyApply s m t x, StrategyPlus s m) => (t -> m x) -> s m Source

Overloaded lifting with failure

Effect substitution (see EffectTheme).

class StrategyMSubst s where Source

Overload msubst combinator (Experimental)

Methods

msubstS :: (Monad m, Monad m') => (forall t. m t -> m' t) -> s m -> s m' Source

Substitute one monad for another