compstrat-0.1.0.2: Strategy combinators for compositional data types

Safe HaskellNone
LanguageHaskell98

Data.Comp.Multi.Strategic

Contents

Synopsis

Rewrites

type RewriteM m f l = f l -> m (f l) Source

type GRewriteM m f = forall l. RewriteM m f l Source

addFail :: Monad m => TranslateM m f l t -> TranslateM (MaybeT m) f l t Source

Lifts a translation into the Maybe monad, allowing it to fail

tryR :: Monad m => RewriteM (MaybeT m) f l -> RewriteM m f l Source

promoteR :: (DynCase f l, Monad m) => RewriteM (MaybeT m) f l -> GRewriteM m f Source

promoteRF :: (DynCase f l, Monad m) => RewriteM (MaybeT m) f l -> GRewriteM (MaybeT m) f Source

allR :: (Monad m, HTraversable f) => GRewriteM m (Term f) -> RewriteM m (Term f) l Source

Applies a rewrite to all immediate subterms of the current term

(>+>) :: (Applicative m, MonadPlus m) => GRewriteM m f -> GRewriteM m f -> GRewriteM m f Source

Applies two rewrites in suceesion, succeeding if one or both succeed

(+>) :: MonadPlus m => RewriteM m f l -> RewriteM m f l -> RewriteM m f l Source

Left-biased choice -- (f +> g) runs f, and, if it fails, then runs g

anyR :: (Applicative m, MonadPlus m, HTraversable f) => GRewriteM m (Term f) -> RewriteM m (Term f) l Source

Applies a rewrite to all immediate subterms of the current term, succeeding if any succeed

oneR :: (Applicative m, MonadPlus m, HTraversable f) => GRewriteM m (Term f) -> RewriteM m (Term f) l Source

Applies a rewrite to the first immediate subterm of the current term where it can succeed

alltdR :: (Monad m, HTraversable f) => GRewriteM m (Term f) -> GRewriteM m (Term f) Source

Runs a rewrite in a top-down traversal

allbuR :: (Monad m, HTraversable f) => GRewriteM m (Term f) -> GRewriteM m (Term f) Source

Runs a rewrite in a bottom-up traversal

anytdR :: (Applicative m, MonadPlus m, HTraversable f) => GRewriteM m (Term f) -> GRewriteM m (Term f) Source

Runs a rewrite in a top-down traversal, succeeding if any succeed

anybuR :: (Applicative m, MonadPlus m, HTraversable f) => GRewriteM m (Term f) -> GRewriteM m (Term f) Source

Runs a rewrite in a bottom-up traversal, succeeding if any succeed

prunetdR :: (Applicative m, MonadPlus m, HTraversable f) => GRewriteM m (Term f) -> GRewriteM m (Term f) Source

Runs a rewrite in a top-down traversal, succeeding if any succeed, and pruning below successes

onetdR :: (Applicative m, MonadPlus m, HTraversable f) => GRewriteM m (Term f) -> GRewriteM m (Term f) Source

Applies a rewrite to the first node where it can succeed in a top-down traversal

onebuR :: (Applicative m, MonadPlus m, HTraversable f) => GRewriteM m (Term f) -> GRewriteM m (Term f) Source

Applies a rewrite to the first node where it can succeed in a bottom-up traversal

Translations

type Translate f l t = TranslateM Identity f l t Source

A single-sorted translation in the Identity monad

type TranslateM m f l t = f l -> m t Source

A monadic translation for a single sort

type GTranslateM m f t = forall l. TranslateM m f l t Source

A monadic translation for all sorts

promoteTF :: (DynCase f l, MonadPlus m) => TranslateM m f l t -> GTranslateM m f t Source

Allows a one-sorted translation to be applied to any sort, failing at sorts different form the original

mtryM :: (Monad m, Monoid a) => MaybeT m a -> m a Source

Runs a failable computation, replacing failure with mempty

onetdT :: (MonadPlus m, HFoldable f) => GTranslateM m (Term f) t -> GTranslateM m (Term f) t Source

Runs a translation in a top-down manner, combining its When run using MaybeT, returns its result for the last node where it succeded

foldtdT :: (HFoldable f, Monoid t, Monad m) => GTranslateM m (Term f) t -> GTranslateM m (Term f) t Source

Fold a tree in a top-down manner

crushtdT :: (HFoldable f, Monoid t, Monad m) => GTranslateM (MaybeT m) (Term f) t -> GTranslateM m (Term f) t Source

An always successful top-down fold, replacing failures with mempty.