hypertypes-0.2.2: Typed ASTs
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hyper.Recurse

Description

Combinators for processing/constructing trees recursively

Synopsis

Documentation

fold :: Recursively HFunctor h => (forall n. HRecWitness h n -> (n # Const a) -> a) -> (Pure # h) -> a Source #

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

unfold :: Recursively HFunctor h => (forall n. HRecWitness h n -> a -> n # Const a) -> a -> Pure # h Source #

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

wrap :: forall h w. Recursively HFunctor h => (forall n. HRecWitness h n -> (n # w) -> w # n) -> (Pure # h) -> w # h Source #

Wrap a Pure to a different HyperType from the bottom up

wrapM :: forall m h w. (Monad m, RTraversable h) => (forall n. HRecWitness h n -> (n # w) -> m (w # n)) -> (Pure # h) -> m (w # h) Source #

Monadically convert a Pure to a different HyperType from the bottom up

unwrap :: forall h w. Recursively HFunctor h => (forall n. HRecWitness h n -> (w # n) -> n # w) -> (w # h) -> Pure # h Source #

Unwrap a tree from the top down, replacing its HyperType with Pure

unwrapM :: forall m h w. (Monad m, RTraversable h) => (forall n. HRecWitness h n -> (w # n) -> m (n # w)) -> (w # h) -> m (Pure # h) Source #

Monadically unwrap a tree from the top down, replacing its HyperType with Pure

foldMapRecursive :: forall h p a. (Recursively HFoldable h, Recursively HFoldable p, Monoid a) => (forall n q. HRecWitness h n -> (n # q) -> a) -> (h # p) -> a Source #

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

data HRecWitness h n where Source #

HRecWitness h n is a witness that n is a recursive node of h

Constructors

HRecSelf :: HRecWitness h h 
HRecSub :: HWitness h c -> HRecWitness c n -> HRecWitness h n 

(#>>) :: forall c h n r. (Recursive c, c h, RNodes h) => Proxy c -> (c n => r) -> HRecWitness h 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 h, RNodes h) => Proxy c -> (c n => HRecWitness h n -> r) -> HRecWitness h 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 h n r. Recursively c h => Proxy c -> (c n => r) -> HRecWitness h n -> r infixr 0 Source #

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