kure-2.0.0: Combinators for Strategic Programming

Portabilityghc
Stabilitybeta
MaintainerNeil Sculthorpe <neil@ittc.ku.edu>
Safe HaskellSafe-Infered

Language.KURE.Utilities

Contents

Description

This module contains several utility functions that can be useful to users of KURE, when definining instances of the KURE classes.

Synopsis

Generic Combinators

These functions are to aid with defining Walker instances for the Generic type. See the "Expr" example.

allTgeneric :: (Walker c m a, Monoid b) => Translate c m (Generic a) b -> c -> a -> m bSource

allRgeneric :: Walker c m a => Rewrite c m (Generic a) -> c -> a -> m (Generic a)Source

anyRgeneric :: Walker c m a => Rewrite c m (Generic a) -> c -> a -> m (Generic a)Source

childLgeneric :: Walker c m a => Int -> c -> a -> m ((c, Generic a), Generic a -> m (Generic a))Source

Attempt Combinators

These are useful when defining congruence combinators that succeed if any child rewrite succeeds. As well as being generally useful, such combinators are helpful when defining anyR instances. See the "Lam" or "Expr" examples, or the HERMIT package.

attemptAny2 :: Monad m => (a1 -> a2 -> r) -> m (Bool, a1) -> m (Bool, a2) -> m rSource

attemptAny3 :: Monad m => (a1 -> a2 -> a3 -> r) -> m (Bool, a1) -> m (Bool, a2) -> m (Bool, a3) -> m rSource

attemptAnyN :: Monad m => ([a] -> b) -> [m (Bool, a)] -> m bSource

attemptAny1N :: Monad m => (a1 -> [a2] -> r) -> m (Bool, a1) -> [m (Bool, a2)] -> m rSource

Error Messages

missingChildL :: Monad m => Int -> Lens c m a bSource

A failing Lens with a standard error message for when the child index is out of bounds.

Child Combinators

These functions are helpful when defining childL instances in combination with congruence combinators. See the "Lam" and "Expr" examples, or the HERMIT package.

Unfortunately they increase quadratically with the number of fields of the constructor. It would be nice if they were further expanded to include the calls of idR and exposeT; however this would create a plethora of additional cases as the number (and positions) of interesting children would be additional dimensions.

Note that the numbering scheme MofN is that N is the number of children (including uninteresting children) and M is the index of the chosen child, starting with index 0. Thus M ranges from 0 to (n-1).

TO DO: use Template Haskell to generate these.

In the mean time, if you need a few more than provided here, drop me an email and I'll add them.

childLaux :: (MonadPlus m, Term b) => (c, b) -> (b -> a) -> ((c, Generic b), Generic b -> m a)Source

childL0of1 :: (MonadPlus m, Term b) => (b -> a) -> (c, b) -> ((c, Generic b), Generic b -> m a)Source

childL0of2 :: (MonadPlus m, Term b0) => (b0 -> b1 -> a) -> (c, b0) -> b1 -> ((c, Generic b0), Generic b0 -> m a)Source

childL1of2 :: (MonadPlus m, Term b1) => (b0 -> b1 -> a) -> b0 -> (c, b1) -> ((c, Generic b1), Generic b1 -> m a)Source

childL0of3 :: (MonadPlus m, Term b0) => (b0 -> b1 -> b2 -> a) -> (c, b0) -> b1 -> b2 -> ((c, Generic b0), Generic b0 -> m a)Source

childL1of3 :: (MonadPlus m, Term b1) => (b0 -> b1 -> b2 -> a) -> b0 -> (c, b1) -> b2 -> ((c, Generic b1), Generic b1 -> m a)Source

childL2of3 :: (MonadPlus m, Term b2) => (b0 -> b1 -> b2 -> a) -> b0 -> b1 -> (c, b2) -> ((c, Generic b2), Generic b2 -> m a)Source

childL0of4 :: (MonadPlus m, Term b0) => (b0 -> b1 -> b2 -> b3 -> a) -> (c, b0) -> b1 -> b2 -> b3 -> ((c, Generic b0), Generic b0 -> m a)Source

childL1of4 :: (MonadPlus m, Term b1) => (b0 -> b1 -> b2 -> b3 -> a) -> b0 -> (c, b1) -> b2 -> b3 -> ((c, Generic b1), Generic b1 -> m a)Source

childL2of4 :: (MonadPlus m, Term b2) => (b0 -> b1 -> b2 -> b3 -> a) -> b0 -> b1 -> (c, b2) -> b3 -> ((c, Generic b2), Generic b2 -> m a)Source

childL3of4 :: (MonadPlus m, Term b3) => (b0 -> b1 -> b2 -> b3 -> a) -> b0 -> b1 -> b2 -> (c, b3) -> ((c, Generic b3), Generic b3 -> m a)Source

childLMofN :: (MonadPlus m, Term b) => Int -> ([b] -> a) -> [(c, b)] -> ((c, Generic b), Generic b -> m a)Source