Strafunski-StrategyLib-5.0.0.2: Library for strategic programming

Portabilityportable
Stabilityexperimental
MaintainerRalf Laemmel, Joost Visser
Safe HaskellNone

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 whereSource

Overload completely unconstrained strategy combinators

Methods

voidS :: s m -> TU () mSource

seqS :: TP m -> s m -> s mSource

Sequential composition

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

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 whereSource

Overload apply and adhoc combinators

Methods

applyS :: s m -> t -> m xSource

Strategy application

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

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 whereSource

Overload basic combinators which might involve a monoid

Methods

skipS :: s mSource

Identity (success)

allS :: s m -> s mSource

Push down to all children

combS :: s m -> s m -> s mSource

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 whereSource

Overload basic combinators which involve MonadPlus

Methods

failS :: s mSource

Failure

choiceS :: s m -> s m -> s mSource

Choice

oneS :: s m -> s mSource

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 mSource

Overloaded lifting with failure

Effect substitution (see EffectTheme).

class StrategyMSubst s whereSource

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