Strafunski-StrategyLib-5.0.1.0: 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

Minimal complete definition

voidS, seqS, passS

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

Methods

voidS :: TP m -> TU () m Source #

seqS :: TP m -> TP m -> TP m Source #

passS :: TU a m -> (a -> TP m) -> TP m Source #

Monad m => Strategy (TU a) m Source # 

Methods

voidS :: TU a m -> TU () m Source #

seqS :: TP m -> TU a m -> TU a m Source #

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

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

Overload apply and adhoc combinators

Minimal complete definition

applyS, adhocS

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

Methods

applyS :: TP m -> t -> m t Source #

adhocS :: TP m -> (t -> m t) -> TP m Source #

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

Methods

applyS :: TU a m -> t -> m a Source #

adhocS :: TU a m -> (t -> m a) -> TU a m Source #

Involving Monoid, MonadPlus,

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

Overload basic combinators which might involve a monoid

Minimal complete definition

skipS, allS, combS

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

Methods

skipS :: TP m Source #

allS :: TP m -> TP m Source #

combS :: TP m -> TP m -> TP m Source #

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

Methods

skipS :: TU u m Source #

allS :: TU u m -> TU u m Source #

combS :: TU u m -> TU u m -> TU u m Source #

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

Overload basic combinators which involve MonadPlus

Minimal complete definition

failS, choiceS, oneS

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

Methods

failS :: TP m Source #

choiceS :: TP m -> TP m -> TP m Source #

oneS :: TP m -> TP m Source #

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

Methods

failS :: TU u m Source #

choiceS :: TU u m -> TU u m -> TU u m Source #

oneS :: TU u m -> TU u m Source #

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)

Minimal complete definition

msubstS

Methods

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

Substitute one monad for another

Instances

StrategyMSubst TP Source # 

Methods

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

StrategyMSubst (TU a) Source # 

Methods

msubstS :: (Monad m, Monad m') => (forall t. m t -> m' t) -> TU a m -> TU a m' Source #