Copyright | (c) 2012--2021 The University of Kansas |
---|---|
License | BSD3 |
Maintainer | Neil Sculthorpe <neil.sculthorpe@ntu.ac.uk> |
Stability | beta |
Portability | ghc |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- idR :: Monad m => Rewrite c m a
- successT :: Monad m => Transform c m a ()
- contextT :: Monad m => Transform c m a c
- exposeT :: Monad m => Transform c m a (c, a)
- liftContext :: (c -> c') -> Transform c' m a b -> Transform c m a b
- readerT :: (a -> Transform c m a b) -> Transform c m a b
- resultT :: (m b -> n d) -> Transform c m a b -> Transform c n a d
- catchesT :: MonadCatch m => [Transform c m a b] -> Transform c m a b
- mapT :: (Traversable t, Monad m) => Transform c m a b -> Transform c m (t a) (t b)
- joinT :: Transform c m (m a) a
- guardT :: MonadFail m => Transform c m Bool ()
- tryR :: MonadCatch m => Rewrite c m a -> Rewrite c m a
- andR :: (Foldable f, Monad m) => f (Rewrite c m a) -> Rewrite c m a
- orR :: (Functor f, Foldable f, MonadCatch m) => f (Rewrite c m a) -> Rewrite c m a
- (>+>) :: MonadCatch m => Rewrite c m a -> Rewrite c m a -> Rewrite c m a
- repeatR :: MonadCatch m => Rewrite c m a -> Rewrite c m a
- acceptR :: MonadFail m => (a -> Bool) -> Rewrite c m a
- acceptWithFailMsgR :: MonadFail m => (a -> Bool) -> String -> Rewrite c m a
- accepterR :: MonadFail m => Transform c m a Bool -> Rewrite c m a
- changedR :: (MonadCatch m, Eq a) => Rewrite c m a -> Rewrite c m a
- changedByR :: MonadCatch m => (a -> a -> Bool) -> Rewrite c m a -> Rewrite c m a
- sideEffectR :: Monad m => (c -> a -> m ()) -> Rewrite c m a
- data AnyR m a
- wrapAnyR :: MonadCatch m => Rewrite c m a -> Rewrite c (AnyR m) a
- unwrapAnyR :: MonadFail m => Rewrite c (AnyR m) a -> Rewrite c m a
- data OneR m a
- wrapOneR :: MonadCatch m => Rewrite c m g -> Rewrite c (OneR m) g
- unwrapOneR :: MonadFail m => Rewrite c (OneR m) a -> Rewrite c m a
Transformation Combinators
liftContext :: (c -> c') -> Transform c' m a b -> Transform c m a b Source #
Lift a transformation to operate on a derived context.
readerT :: (a -> Transform c m a b) -> Transform c m a b Source #
Look at the argument to the transformation before choosing which Transform
to use.
resultT :: (m b -> n d) -> Transform c m a b -> Transform c n a d Source #
Convert the monadic result of a transformation into a result in another monad.
catchesT :: MonadCatch m => [Transform c m a b] -> Transform c m a b Source #
Deprecated: Please use catchesM
instead.
Attempt each transformation until one succeeds, then return that result and discard the rest of the transformations.
mapT :: (Traversable t, Monad m) => Transform c m a b -> Transform c m (t a) (t b) Source #
Map a transformation over a list.
guardT :: MonadFail m => Transform c m Bool () Source #
Fail if the Boolean is False, succeed if the Boolean is True.
Rewrite Combinators
tryR :: MonadCatch m => Rewrite c m a -> Rewrite c m a Source #
Catch a failing rewrite, making it into an identity.
andR :: (Foldable f, Monad m) => f (Rewrite c m a) -> Rewrite c m a Source #
Perform a collection of rewrites in sequence, requiring all to succeed.
orR :: (Functor f, Foldable f, MonadCatch m) => f (Rewrite c m a) -> Rewrite c m a Source #
Perform a collection of rewrites in sequence, succeeding if any succeed.
(>+>) :: MonadCatch m => Rewrite c m a -> Rewrite c m a -> Rewrite c m a Source #
Perform two rewrites in sequence, succeeding if one or both succeed.
repeatR :: MonadCatch m => Rewrite c m a -> Rewrite c m a Source #
Repeat a rewrite until it fails, then return the result before the failure. Requires at least the first attempt to succeed.
acceptR :: MonadFail m => (a -> Bool) -> Rewrite c m a Source #
Look at the argument to a rewrite, and choose to be either idR
or a failure.
acceptWithFailMsgR :: MonadFail m => (a -> Bool) -> String -> Rewrite c m a Source #
As acceptR
, but takes a custom failure message.
changedR :: (MonadCatch m, Eq a) => Rewrite c m a -> Rewrite c m a Source #
Makes an rewrite fail if the result value equals the argument value.
changedByR :: MonadCatch m => (a -> a -> Bool) -> Rewrite c m a -> Rewrite c m a Source #
sideEffectR :: Monad m => (c -> a -> m ()) -> Rewrite c m a Source #
An identity rewrite with side-effects.
Monad Transformers
anyR Support
These are useful when defining congruence combinators that succeed if any child rewrite succeeds. See the "Expr" example, or the HERMIT package.
The AnyR
transformer, in combination with wrapAnyR
and unwrapAnyR
,
causes a sequence of rewrites to succeed if at least one succeeds, converting failures to
identity rewrites.
oneR Support
These are useful when defining congruence combinators that succeed if one child rewrite succeeds (and the remainder are then discarded). See the "Expr" example, or the HERMIT package.
The OneR
transformer, in combination with wrapOneR
and unwrapOneR
,
causes a sequence of rewrites to only apply the first success, converting the remainder (and failures) to identity rewrites.