syntax-tree-0.1.0.1: Typed ASTs

Safe HaskellNone
LanguageHaskell2010

AST.Recurse

Description

Combinators for processing/constructing trees recursively

Synopsis

Documentation

fold :: Recursively KFunctor k => (forall n. KRecWitness k n -> Tree n (Const a) -> a) -> Tree Pure k -> a Source #

Recursively fold up a tree to produce a result (aka catamorphism)

unfold :: Recursively KFunctor k => (forall n. KRecWitness k n -> a -> Tree n (Const a)) -> a -> Tree Pure k Source #

Build/load a tree from a seed value (aka anamorphism)

wrap :: forall k w. Recursively KFunctor k => (forall n. KRecWitness k n -> Tree n w -> Tree w n) -> Tree Pure k -> Tree w k Source #

Wrap a Pure Tree to a different Knot from the bottom up

wrapM :: forall m k w. (Monad m, RTraversable k) => (forall n. KRecWitness k n -> Tree n w -> m (Tree w n)) -> Tree Pure k -> m (Tree w k) Source #

Monadically convert a Pure Tree to a different Knot from the bottom up

unwrap :: forall k w. Recursively KFunctor k => (forall n. KRecWitness k n -> Tree w n -> Tree n w) -> Tree w k -> Tree Pure k Source #

Unwrap a Tree from the top down, replacing its Knot with Pure

unwrapM :: forall m k w. (Monad m, RTraversable k) => (forall n. KRecWitness k n -> Tree w n -> m (Tree n w)) -> Tree w k -> m (Tree Pure k) Source #

Monadically unwrap a Tree from the top down, replacing its Knot with Pure

foldMapRecursive :: forall k p a. (Recursively KFoldable k, Recursively KFoldable p, Monoid a) => (forall n q. KRecWitness k n -> Tree n q -> a) -> Tree k p -> a Source #

Fold over all of the recursive child nodes of a Tree in pre-order

data KRecWitness k n where Source #

KRecWitness k n is a witness that n is a recursive node of k

Constructors

KRecSelf :: KRecWitness k k 
KRecSub :: KWitness k c -> KRecWitness c n -> KRecWitness k n 

(#>>) :: forall c k n r. (Recursive c, c k, RNodes k) => Proxy c -> (c n => r) -> KRecWitness k n -> r infixr 0 Source #

Proxy c #> r replaces a recursive witness parameter of r@ with a constraint on the witnessed node

(#**#) :: (Recursive c, c k, RNodes k) => Proxy c -> (KRecWitness k n -> c n => r) -> KRecWitness k n -> r infixr 0 Source #

A variant of #>> which does not consume the witness parameter.

Proxy c0 Proxy c1 #>> r brings into context both the c0 n and c1 n constraints.

(##>>) :: forall c k n r. Recursively c k => Proxy c -> (c n => r) -> KRecWitness k n -> r infixr 0 Source #

Proxy c #> r replaces a recursive witness parameter of r with a Recursively c@ constraint on the witnessed node