Maintainer | Ralf Laemmel, Joost Visser |
---|---|
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
- Try: recover from failure
- Test: ignore result, but retain effects
- If-then-else: pass value from condition to then-clause
- If-then: disciplined form of a guarding
- Not: negation by failure
- Exclusive choice
- Generic filter, derived from monomorphic predicate
- Generic ticker, derived from monomorphic predicate
- Type guards
- Generic ticker, derived from type guard
- Generic filters, derived from type guard
This module is part of StrategyLib
, a library of functional strategy
combinators, including combinators for generic traversal. This module
defines combinators to wire up control and data flow. Whenever possible,
we define the combinators in an overloaded fashion but we provide
type-specialised variants for TP and TU for convenience.
- tryS :: (StrategyPlus s m, StrategyMonoid s m) => s m -> s m
- tryTP :: MonadPlus m => TP m -> TP m
- tryTU :: (MonadPlus m, Monoid u) => TU u m -> TU u m
- testS :: Strategy s m => s m -> TP m
- testTP :: Monad m => TP m -> TP m
- testTU :: Monad m => TU a m -> TP m
- ifS :: StrategyPlus s m => TU u m -> (u -> s m) -> s m -> s m
- ifTP :: MonadPlus m => TU u m -> (u -> TP m) -> TP m -> TP m
- ifTU :: MonadPlus m => TU u m -> (u -> TU u' m) -> TU u' m -> TU u' m
- ifthenS :: Strategy s m => TU () m -> s m -> s m
- ifthenTP :: Monad m => TU () m -> TP m -> TP m
- ifthenTU :: Monad m => TU () m -> TU u m -> TU u m
- notS :: StrategyPlus s m => s m -> TP m
- notTP :: MonadPlus m => TP m -> TP m
- notTU :: MonadPlus m => TU u m -> TP m
- xchoiceS :: StrategyPlus s m => s m -> s m -> s m
- xchoiceTP :: MonadPlus m => TP m -> TP m -> TP m
- xchoiceTU :: MonadPlus m => TU u m -> TU u m -> TU u m
- filterTP :: (Term t, MonadPlus m) => (t -> Bool) -> TP m
- filterTU :: (Term t, MonadPlus m) => (t -> Bool) -> TU t m
- tickTU :: (Monad m, Term t, Num n) => (t -> Bool) -> TU n m
- type TypeGuard a = a -> ()
- typeGuard :: TypeGuard a
- typeTickTU :: (Term t, Monad m, Num n) => TypeGuard t -> TU n m
- typeFilterTP :: (Term t, MonadPlus m) => TypeGuard t -> TP m
- typeFilterTU :: (Term t, MonadPlus m) => TypeGuard t -> TU t m
Try: recover from failure
tryS :: (StrategyPlus s m, StrategyMonoid s m) => s m -> s m Source #
Attempt a strategy s
, but recover if it fails.
tryTP :: MonadPlus m => TP m -> TP m Source #
Attempt a type-preserving strategy s
, but if it fails, return the
input term unchanged.
Test: ignore result, but retain effects
testS :: Strategy s m => s m -> TP m Source #
Test for a strategy's success in a type-preserving context.
testTP :: Monad m => TP m -> TP m Source #
Test for a type-preserving strategy's success in a type-preserving context.
testTU :: Monad m => TU a m -> TP m Source #
Test for a type-unifying strategy's success in a type-preserving context.
If-then-else: pass value from condition to then-clause
ifS :: StrategyPlus s m => TU u m -> (u -> s m) -> s m -> s m Source #
If c
succeeds, pass its value to the then-clause t
,
otherwise revert to the else-clause e
.
ifTP :: MonadPlus m => TU u m -> (u -> TP m) -> TP m -> TP m Source #
If c
succeeds, pass its value to the then-clause t
,
otherwise revert to the else-clause e
.
ifTU :: MonadPlus m => TU u m -> (u -> TU u' m) -> TU u' m -> TU u' m Source #
If c
succeeds, pass its value to the then-clause t
,
otherwise revert to the else-clause e
.
If-then: disciplined form of a guarding
ifthenS :: Strategy s m => TU () m -> s m -> s m Source #
Guard then-clause t
by the void-valued type-unifying
condition c
.
ifthenTP :: Monad m => TU () m -> TP m -> TP m Source #
Guard type-preserving then-clause t
by the void-valued type-unifying
condition c
.
ifthenTU :: Monad m => TU () m -> TU u m -> TU u m Source #
Guard type-unifying then-clause t
by the void-valued type-unifying
condition c
.
Not: negation by failure
notS :: StrategyPlus s m => s m -> TP m Source #
Invert the success-value of strategy s
.
notTP :: MonadPlus m => TP m -> TP m Source #
Invert the success-value of type-preserving strategy s
. Its output
term (in case of success) will be ignored.
notTU :: MonadPlus m => TU u m -> TP m Source #
Invert the success-value of type-unifying strategy s
. Its output
value (in case of success) will be ignored.
Exclusive choice
xchoiceS :: StrategyPlus s m => s m -> s m -> s m Source #
Succeed if exactly one argument strategy succeeds.
xchoiceTP :: MonadPlus m => TP m -> TP m -> TP m Source #
Succeed if exactly one argument strategy succeeds.
xchoiceTU :: MonadPlus m => TU u m -> TU u m -> TU u m Source #
Succeed if exactly one argument strategy succeeds.
Generic filter, derived from monomorphic predicate
filterTP :: (Term t, MonadPlus m) => (t -> Bool) -> TP m Source #
If predicate g
holds for the input term, return it as output term,
otherwise fail.
filterTU :: (Term t, MonadPlus m) => (t -> Bool) -> TU t m Source #
If predicate g
holds for the input term, return it as output value,
otherwise fail.
Generic ticker, derived from monomorphic predicate
tickTU :: (Monad m, Term t, Num n) => (t -> Bool) -> TU n m Source #
If predicate g
holds for the input term,
return 1 otherwise return 0.
Type guards
type TypeGuard a = a -> () Source #
Type guard (function type), i.e., guard that does not observe values
typeGuard :: TypeGuard a Source #
Type guard (function). Typical usage:
full_tdTU (typeTickTU (typeGuard::TypeGuard MyType))
Generic ticker, derived from type guard
typeTickTU :: (Term t, Monad m, Num n) => TypeGuard t -> TU n m Source #
If type guard holds for the input term, return 1 otherwise return 0.