Annotations-0.2.1: Constructing, analyzing and destructing annotated trees

Safe HaskellSafe-Inferred
LanguageHaskell98

Annotations.F.Annotated

Contents

Synopsis

Annotations

data Ann x f a Source

Lifted annotation of functors.

Constructors

Ann x (f a) 

Instances

Functor f => Functor (Ann x f) 
Foldable f => Foldable (Ann x f) 
Traversable f => Traversable (Ann x f) 
(Eq x, Eq (f a)) => Eq (Ann x f a) 
(Show x, Show (f a)) => Show (Ann x f a) 

type AnnFix xT fT = Fix (Ann xT fT) Source

A fully annotated tree.

rootAnn :: AnnFix x f -> x Source

Yields the annotation at the root of the tree.

type AnnFix1 xT fT = fT (AnnFix xT fT) Source

A functor with fully annotated children.

mkAnnFix :: x -> AnnFix1 x f -> AnnFix x f Source

Supply a tree with an annotation at the top level.

unannotate :: Functor f => AnnFix x f -> Fix f Source

Recursively discard annotations.

errorCata :: Traversable fT => ErrorAlgebra fT eT aT -> AnnFix xT fT -> Except [(eT, xT)] aT Source

Reduces a tree to a value according to the algebra, collecting potential errors. The errors are combined with the annotations in the tree at the positions at which the errors occurred.

Exploring annotated trees using zippers

explore :: Foldable f => (x -> ExploreHints) -> AnnFix x f -> [Zipper (AnnFix x f)] Source

Explore an annotated tree. Starting with the root of the tree, at each position the annotation at that position is matched against the ExploreHints predicates and all the selections where matchHere was positive are collected. The exploreRight and exploreDown allow pruning of the tree, preventing entire parts from being visited.

findLeftmostDeepest :: Foldable f => (x -> Bool) -> AnnFix x f -> Maybe (Zipper (AnnFix x f)) Source

Find the deepest node in an annotated tree that matches the predicate. Starting with the root, the predicate tells whether a node's annotation matches. If so, the search continues at the node's children and the node's siblings to the right are excluded from further exploration. If no child matches, the node itself is returned.