Annotations-0.2.2: Constructing, analyzing and destructing annotated trees

Safe HaskellSafe
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) Source # 

Methods

fmap :: (a -> b) -> Ann x f a -> Ann x f b #

(<$) :: a -> Ann x f b -> Ann x f a #

Foldable f => Foldable (Ann x f) Source # 

Methods

fold :: Monoid m => Ann x f m -> m #

foldMap :: Monoid m => (a -> m) -> Ann x f a -> m #

foldr :: (a -> b -> b) -> b -> Ann x f a -> b #

foldr' :: (a -> b -> b) -> b -> Ann x f a -> b #

foldl :: (b -> a -> b) -> b -> Ann x f a -> b #

foldl' :: (b -> a -> b) -> b -> Ann x f a -> b #

foldr1 :: (a -> a -> a) -> Ann x f a -> a #

foldl1 :: (a -> a -> a) -> Ann x f a -> a #

toList :: Ann x f a -> [a] #

null :: Ann x f a -> Bool #

length :: Ann x f a -> Int #

elem :: Eq a => a -> Ann x f a -> Bool #

maximum :: Ord a => Ann x f a -> a #

minimum :: Ord a => Ann x f a -> a #

sum :: Num a => Ann x f a -> a #

product :: Num a => Ann x f a -> a #

Traversable f => Traversable (Ann x f) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Ann x f a -> f (Ann x f b) #

sequenceA :: Applicative f => Ann x f (f a) -> f (Ann x f a) #

mapM :: Monad m => (a -> m b) -> Ann x f a -> m (Ann x f b) #

sequence :: Monad m => Ann x f (m a) -> m (Ann x f a) #

(Eq (f a), Eq x) => Eq (Ann x f a) Source # 

Methods

(==) :: Ann x f a -> Ann x f a -> Bool #

(/=) :: Ann x f a -> Ann x f a -> Bool #

(Show (f a), Show x) => Show (Ann x f a) Source # 

Methods

showsPrec :: Int -> Ann x f a -> ShowS #

show :: Ann x f a -> String #

showList :: [Ann x f a] -> ShowS #

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.