kure-2.4.10: Combinators for Strategic Programming

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

Language.KURE.Walker

Contents

Description

This module provides combinators that traverse a tree.

Note that all traversals take place on the node, its children, or its descendents. Deliberately, there is no mechanism for "ascending" the tree.

Synopsis

Nodes

class (Injection a (Generic a), Generic a ~ Generic (Generic a)) => Node a whereSource

A Node is any node in the tree that you wish to be able to traverse.

Associated Types

type Generic a :: *Source

Generic is a sum of all the types of the sub-nodes, transitively, of a. We use Generic a ~ a to signify that something is its own Generic. Simple expression types might be their own sole Generic, more complex examples will have a new datatype for the Generic, which will also be an instance of class Node.

Methods

numChildren :: a -> IntSource

Count the number of immediate child Nodes.

numChildrenT :: (Monad m, Node a) => Translate c m a IntSource

Lifted version of numChildren.

hasChild :: Node a => Int -> a -> BoolSource

Check if a Node has a child of the specified index.

hasChildT :: (Monad m, Node a) => Int -> Translate c m a BoolSource

Lifted version of hasChild.

Tree Walkers

class (MonadCatch m, Node a) => Walker c m a whereSource

Walker captures the ability to walk over a tree of Nodes, using a specific context c and a MonadCatch m.

Minimal complete definition: childL.

Default definitions are provided for allT, oneT, allR, anyR and oneR, but they may be overridden for efficiency. For small numbers of interesting children this will not be an issue, but for a large number, say for a list of children, it may be.

Methods

childL :: Int -> Lens c m a (Generic a)Source

Construct a Lens to the n-th child Node.

allT :: Monoid b => Translate c m (Generic a) b -> Translate c m a bSource

Apply a Generic Translate to all immediate children, succeeding if they all succeed. The results are combined in a Monoid.

oneT :: Translate c m (Generic a) b -> Translate c m a bSource

Apply a Generic Translate to the first immediate child for which it can succeed.

allR :: Rewrite c m (Generic a) -> Rewrite c m aSource

Apply a Generic Rewrite to all immediate children, succeeding if they all succeed.

anyR :: Rewrite c m (Generic a) -> Rewrite c m aSource

Apply a Generic Rewrite to all immediate children, suceeding if any succeed.

oneR :: Rewrite c m (Generic a) -> Rewrite c m aSource

Apply a Generic Rewrite to the first immediate child for which it can succeed.

Rewrite Traversals

childR :: Walker c m a => Int -> Rewrite c m (Generic a) -> Rewrite c m aSource

Apply a Rewrite to a specified child.

alltdR :: (Walker c m a, a ~ Generic a) => Rewrite c m (Generic a) -> Rewrite c m (Generic a)Source

Apply a Rewrite in a top-down manner, succeeding if they all succeed.

allbuR :: (Walker c m a, a ~ Generic a) => Rewrite c m (Generic a) -> Rewrite c m (Generic a)Source

Apply a Rewrite in a bottom-up manner, succeeding if they all succeed.

allduR :: (Walker c m a, a ~ Generic a) => Rewrite c m (Generic a) -> Rewrite c m (Generic a)Source

Apply a Rewrite twice, in a top-down and bottom-up way, using one single tree traversal, succeeding if they all succeed.

anytdR :: (Walker c m a, a ~ Generic a) => Rewrite c m (Generic a) -> Rewrite c m (Generic a)Source

Apply a Rewrite in a top-down manner, succeeding if any succeed.

anybuR :: (Walker c m a, a ~ Generic a) => Rewrite c m (Generic a) -> Rewrite c m (Generic a)Source

Apply a Rewrite in a bottom-up manner, succeeding if any succeed.

anyduR :: (Walker c m a, a ~ Generic a) => Rewrite c m (Generic a) -> Rewrite c m (Generic a)Source

Apply a Rewrite twice, in a top-down and bottom-up way, using one single tree traversal, succeeding if any succeed.

onetdR :: (Walker c m a, a ~ Generic a) => Rewrite c m (Generic a) -> Rewrite c m (Generic a)Source

Apply a Rewrite to the first Node for which it can succeed, in a top-down traversal.

onebuR :: (Walker c m a, a ~ Generic a) => Rewrite c m (Generic a) -> Rewrite c m (Generic a)Source

Apply a Rewrite to the first Node for which it can succeed, in a bottom-up traversal.

prunetdR :: (Walker c m a, a ~ Generic a) => Rewrite c m (Generic a) -> Rewrite c m (Generic a)Source

Attempt to apply a Rewrite in a top-down manner, pruning at successful rewrites.

innermostR :: (Walker c m a, Generic a ~ a) => Rewrite c m (Generic a) -> Rewrite c m (Generic a)Source

A fixed-point traveral, starting with the innermost term.

Translate Traversals

childT :: Walker c m a => Int -> Translate c m (Generic a) b -> Translate c m a bSource

Apply a Translate to a specified child.

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

Fold a tree in a top-down manner, using a single Translate for each Node.

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

Fold a tree in a bottom-up manner, using a single Translate for each Node.

onetdT :: (Walker c m a, a ~ Generic a) => Translate c m (Generic a) b -> Translate c m (Generic a) bSource

Apply a Translate to the first Node for which it can succeed, in a top-down traversal.

onebuT :: (Walker c m a, a ~ Generic a) => Translate c m (Generic a) b -> Translate c m (Generic a) bSource

Apply a Translate to the first Node for which it can succeed, in a bottom-up traversal.

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

Attempt to apply a Translate in a top-down manner, pruning at successes.

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

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

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

An always successful bottom-up fold, replacing failures with mempty.

collectT :: (Walker c m a, a ~ Generic a) => Translate c m (Generic a) b -> Translate c m (Generic a) [b]Source

An always successful traversal that collects the results of all successful applications of a Translate in a list.

collectPruneT :: (Walker c m a, a ~ Generic a) => Translate c m (Generic a) b -> Translate c m (Generic a) [b]Source

Like collectT, but does not traverse below successes.

Paths

Absolute Paths

data AbsolutePath Source

A path from the root.

Instances

Show AbsolutePath 
PathContext AbsolutePath

The simplest instance of PathContext is AbsolutePath itself.

rootAbsPath :: AbsolutePathSource

The (empty) AbsolutePath to the root.

extendAbsPath :: Int -> AbsolutePath -> AbsolutePathSource

Extend an AbsolutePath by one descent.

class PathContext c whereSource

Contexts that are instances of PathContext contain the current AbsolutePath. Any user-defined combinators (typically childL and congruence combinators) should update the AbsolutePath using extendAbsPath.

Methods

contextPath :: c -> AbsolutePathSource

Find the current path.

Instances

PathContext AbsolutePath

The simplest instance of PathContext is AbsolutePath itself.

absPathT :: (PathContext c, Monad m) => Translate c m a AbsolutePathSource

Find the AbsolutePath to the current Node.

Relative Paths

type Path = [Int]Source

A path is a route to descend the tree from an arbitrary Node.

rootPath :: AbsolutePath -> PathSource

Convert an AbsolutePath into a Path starting at the root.

pathsToT :: (PathContext c, Walker c m a, a ~ Generic a) => (Generic a -> Bool) -> Translate c m (Generic a) [Path]Source

Find the Paths to every Node that satisfies the predicate.

onePathToT :: (PathContext c, Walker c m a, a ~ Generic a) => (Generic a -> Bool) -> Translate c m (Generic a) PathSource

Find the Path to the first Node that satisfies the predicate (in a pre-order traversal).

oneNonEmptyPathToT :: (PathContext c, Walker c m a, a ~ Generic a) => (Generic a -> Bool) -> Translate c m (Generic a) PathSource

Find the Path to the first descendent Node that satisfies the predicate (in a pre-order traversal).

prunePathsToT :: (PathContext c, Walker c m a, a ~ Generic a) => (Generic a -> Bool) -> Translate c m (Generic a) [Path]Source

Find the Paths to every Node that satisfies the predicate, ignoring Nodes below successes.

uniquePathToT :: (PathContext c, Walker c m a, a ~ Generic a) => (Generic a -> Bool) -> Translate c m (Generic a) PathSource

Find the Path to the Node that satisfies the predicate, failing if that does not uniquely identify a Node.

uniquePrunePathToT :: (PathContext c, Walker c m a, a ~ Generic a) => (Generic a -> Bool) -> Translate c m (Generic a) PathSource

Build a Path to the Node that satisfies the predicate, failing if that does not uniquely identify a Node (ignoring Nodes below successes).

Using Paths

Building Lenses from Paths

pathL :: (Walker c m a, a ~ Generic a) => Path -> Lens c m (Generic a) (Generic a)Source

Construct a Lens by following a Path.

exhaustPathL :: (Walker c m a, a ~ Generic a) => Path -> Lens c m (Generic a) (Generic a)Source

Construct a Lens that points to the last Node at which the Path can be followed.

repeatPathL :: (Walker c m a, a ~ Generic a) => Path -> Lens c m (Generic a) (Generic a)Source

Repeat as many iterations of the Path as possible.

rootL :: (Walker c m a, a ~ Generic a) => AbsolutePath -> Lens c m (Generic a) (Generic a)Source

Build a Lens from the root to a point specified by an AbsolutePath.

Applying transformations at the end of Paths

pathR :: (Walker c m a, a ~ Generic a) => Path -> Rewrite c m (Generic a) -> Rewrite c m (Generic a)Source

Apply a Rewrite at a point specified by a Path.

pathT :: (Walker c m a, a ~ Generic a) => Path -> Translate c m (Generic a) b -> Translate c m (Generic a) bSource

Apply a Translate at a point specified by a Path.

Testing Paths

testPathT :: (Walker c m a, a ~ Generic a) => Path -> Translate c m a BoolSource

Check if it is possible to construct a Lens along this path from the current Node.