Maintainer | Ralf Laemmel, Joost Visser |
---|---|
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
This module is part of StrategyLib
, a library of functional strategy
combinators, including combinators for generic traversal. This module
is basically a wrapper for the strategy primitives plus some extra
basic strategy combinators that can be defined immediately in terms
of the primitive ones.
- module Data.Generics.Strafunski.StrategyLib.Models.Deriving.StrategyPrimitives
- idTP :: Monad m => TP m
- failTP :: MonadPlus m => TP m
- failTU :: MonadPlus m => TU a m
- constTU :: Monad m => a -> TU a m
- compTU :: Monad m => m a -> TU a m
- monoTP :: (Term a, MonadPlus m) => (a -> m a) -> TP m
- monoTU :: (Term a, MonadPlus m) => (a -> m b) -> TU b m
- dotTU :: Monad m => (a -> b) -> TU a m -> TU b m
- op2TU :: Monad m => (a -> b -> c) -> TU a m -> TU b m -> TU c m
- voidTP :: Monad m => TP m -> TU () m
- voidTU :: Monad m => TU u m -> TU () m
- con :: MonadPlus m => TP m
- com :: MonadPlus m => TP m
Documentation
Useful defaults for strategy update (see adhocTU
and adhocTP
).
failTP :: MonadPlus m => TP m Source
Type-preserving failure. Always fails, independent of the incoming
term. Uses MonadPlus
to model partiality.
failTU :: MonadPlus m => TU a m Source
Type-unifying failure. Always fails, independent of the incoming
term. Uses MonadPlus
to model partiality.
constTU :: Monad m => a -> TU a m Source
Type-unifying constant strategy. Always returns the argument value a
,
independent of the incoming term.
compTU :: Monad m => m a -> TU a m Source
Type-unifying monadic constant strategy. Always performs the argument
computation a
, independent of the incoming term. This is a monadic
variation of constTU
.
Lift a function to a strategy type with failure as default
monoTP :: (Term a, MonadPlus m) => (a -> m a) -> TP m Source
Apply the monomorphic, type-preserving argument function, if its input type matches the input term's type. Otherwise, fail.
monoTU :: (Term a, MonadPlus m) => (a -> m b) -> TU b m Source
Apply the monomorphic, type-unifying argument function, if its input type matches the input term's type. Otherwise, fail.
Function composition
dotTU :: Monad m => (a -> b) -> TU a m -> TU b m Source
Sequential ccomposition of monomorphic function and type-unifying strategy.
In other words, after the type-unifying strategy s
has been applied,
the monomorphic function f
is applied to the resulting value.
op2TU :: Monad m => (a -> b -> c) -> TU a m -> TU b m -> TU c m Source
Parallel combination of two type-unifying strategies with a binary
combinator. In other words, the values resulting from applying the
type-unifying strategies are combined to a final value by applying
the combinator o
.
Reduce a strategy's performance to its effects
voidTP :: Monad m => TP m -> TU () m Source
Reduce a type-preserving strategy to a type-unifying one that ignores its result term and returns void, but retains its monadic effects.
voidTU :: Monad m => TU u m -> TU () m Source
Reduce a type-unifying strategy to a type-unifying one that ignores its result value and returns void, but retains its monadic effects.