kure-2.16.8: Combinators for Strategic Programming

Copyright(c) 2012--2014 The University of Kansas
LicenseBSD3
MaintainerNeil Sculthorpe <neil@ittc.ku.edu>
Stabilitybeta
Portabilityghc
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.KURE.Combinators.Transform

Contents

Description

This module provides a variety of combinators over Transform and Rewrite.

Synopsis

Transformation Combinators

idR :: Monad m => Rewrite c m a Source

The identity rewrite.

successT :: Monad m => Transform c m a () Source

An always successful transformation.

contextT :: Monad m => Transform c m a c Source

Extract the current context.

exposeT :: Monad m => Transform c m a (c, a) Source

Expose the current context and value.

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

Attempt each trransformation 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.

joinT :: Transform c m (m a) a Source

An identity transformation that resembles a monadic join.

guardT :: Monad 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 :: Monad 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 :: Monad m => (a -> Bool) -> String -> Rewrite c m a Source

As acceptR, but takes a custom failure message.

accepterR :: Monad m => Transform c m a Bool -> Rewrite c m a Source

A generalisation of acceptR where the predicate is a Transform.

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

Makes a rewrite fail if the result value and the argument value satisfy the equality predicate. This is a generalisation of changedR. changedR = changedByR (==)

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.

data AnyR m a Source

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.

Instances

Monad m => Monad (AnyR m) 
Monad m => Functor (AnyR m) 
Monad m => Applicative (AnyR m) 
MonadCatch m => MonadCatch (AnyR m) 

wrapAnyR :: MonadCatch m => Rewrite c m a -> Rewrite c (AnyR m) a Source

Wrap a Rewrite using the AnyR monad transformer.

unwrapAnyR :: Monad m => Rewrite c (AnyR m) a -> Rewrite c m a Source

Unwrap a Rewrite from the AnyR monad transformer.

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.

data OneR m a Source

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.

Instances

Monad m => Monad (OneR m) 
Monad m => Functor (OneR m) 
Monad m => Applicative (OneR m) 
MonadCatch m => MonadCatch (OneR m) 

wrapOneR :: MonadCatch m => Rewrite c m g -> Rewrite c (OneR m) g Source

Wrap a Rewrite using the OneR monad transformer.

unwrapOneR :: Monad m => Rewrite c (OneR m) a -> Rewrite c m a Source

Unwrap a Rewrite from the OneR monad transformer.