Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Ctx a
- = Top
- | L (Ctx a) a (BinaryTree a)
- | R (BinaryTree a) a (Ctx a)
- data BinaryTreeZipper a = Loc (BinaryTree a) (Ctx a)
- top :: BinaryTree a -> BinaryTreeZipper a
- left :: BinaryTreeZipper a -> Maybe (BinaryTreeZipper a)
- right :: BinaryTreeZipper a -> Maybe (BinaryTreeZipper a)
- up :: BinaryTreeZipper a -> Maybe (BinaryTreeZipper a)
- toRoot :: BinaryTreeZipper a -> BinaryTreeZipper a
- visitAll :: BinaryTree a -> [BinaryTreeZipper a]
- accessZ :: BinaryTreeZipper a -> Maybe a
- subTrees :: BinaryTree a -> [BinaryTree a]
- splitTree :: BinaryTreeZipper a -> (BinaryTree a, BinaryTree a)
Documentation
Top | |
L (Ctx a) a (BinaryTree a) | |
R (BinaryTree a) a (Ctx a) |
Instances
Functor Ctx Source # | |
Foldable Ctx Source # | |
Defined in Data.BinaryTree.Zipper fold :: Monoid m => Ctx m -> m # foldMap :: Monoid m => (a -> m) -> Ctx a -> m # foldr :: (a -> b -> b) -> b -> Ctx a -> b # foldr' :: (a -> b -> b) -> b -> Ctx a -> b # foldl :: (b -> a -> b) -> b -> Ctx a -> b # foldl' :: (b -> a -> b) -> b -> Ctx a -> b # foldr1 :: (a -> a -> a) -> Ctx a -> a # foldl1 :: (a -> a -> a) -> Ctx a -> a # elem :: Eq a => a -> Ctx a -> Bool # maximum :: Ord a => Ctx a -> a # | |
Traversable Ctx Source # | |
Eq a => Eq (Ctx a) Source # | |
Ord a => Ord (Ctx a) Source # | |
Read a => Read (Ctx a) Source # | |
Show a => Show (Ctx a) Source # | |
data BinaryTreeZipper a Source #
Loc (BinaryTree a) (Ctx a) |
Instances
top :: BinaryTree a -> BinaryTreeZipper a Source #
Focus on the root
left :: BinaryTreeZipper a -> Maybe (BinaryTreeZipper a) Source #
Go to the left child
right :: BinaryTreeZipper a -> Maybe (BinaryTreeZipper a) Source #
Go to the right child
up :: BinaryTreeZipper a -> Maybe (BinaryTreeZipper a) Source #
Move to the parent
toRoot :: BinaryTreeZipper a -> BinaryTreeZipper a Source #
Navigate to the root
visitAll :: BinaryTree a -> [BinaryTreeZipper a] Source #
Returns a list of zippers; one focussed on each node in the tree
accessZ :: BinaryTreeZipper a -> Maybe a Source #
Get the value stored at the current node
subTrees :: BinaryTree a -> [BinaryTree a] Source #
Returns all subtrees; i.e. every node with all its decendents
splitTree :: BinaryTreeZipper a -> (BinaryTree a, BinaryTree a) Source #
Splits the tree here, returns a pair (innerTree,outerTree)