avl-static-0.1.0.0: A compile-time balanced AVL tree.

Safe HaskellSafe-Inferred

Data.Tree.AVL.Static.Internal

Synopsis

Documentation

data Nat Source

A natural number datatype, hoisted to a Kind using DataKinds.

Constructors

Zero 
Succ Nat 

Instances

Eq Nat 
Ord Nat 
Show Nat 

data AVLNode whereSource

An AVLNode n a is a node whose subtree has height n, and values of type a.

Constructors

Nil :: AVLNode Zero a 
Leftie :: a -> AVLNode (Succ n) a -> AVLNode n a -> AVLNode (Succ (Succ n)) a 
Rightie :: a -> AVLNode n a -> AVLNode (Succ n) a -> AVLNode (Succ (Succ n)) a 
Balanced :: a -> AVLNode n a -> AVLNode n a -> AVLNode (Succ n) a 

Instances

Show a => Show (AVLNode n a) 

data AVLTree a Source

An AVLTree a is a statically balanced tree, whose non-nil values have type a.

Constructors

forall n . T (AVLNode n a) Integer 

Instances

Functor AVLTree 
Foldable AVLTree 
Traversable AVLTree 
Show a => Show (AVLTree a) 

foldNode :: (b -> b -> a -> b) -> b -> AVLNode n a -> bSource

fmapNode :: (a -> b) -> AVLNode n a -> AVLNode n bSource

traverseNode :: Applicative f => (a -> f b) -> AVLNode n a -> f (AVLNode n b)Source

data Context whereSource

The context for an 'AVLTree'\'s Zipper. The idea is that it represents an entire AVLTree, save for a hole in it. A Context n a means an entire AVLTree a, with a hole of height n. Its use is that, in a Zipper, we have a simple way to move around in the tree, starting at that hole.

See this paper by Conor McBride for more information.

Constructors

BC :: Bool -> a -> AVLNode n a -> Context (Succ n) a -> Context n a 
LRC :: a -> AVLNode (Succ n) a -> Context (Succ (Succ n)) a -> Context n a 
LLC :: a -> AVLNode n a -> Context (Succ (Succ n)) a -> Context (Succ n) a 
RLC :: a -> AVLNode (Succ n) a -> Context (Succ (Succ n)) a -> Context n a 
RRC :: a -> AVLNode n a -> Context (Succ (Succ n)) a -> Context (Succ n) a 
Root :: Integer -> Context n a 

Instances

Show a => Show (Context n a) 

data Zipper a Source

A Zipper is a useful construct for functional datastructure traversals. For us, it can be thought of as a pointer to a subtree in an AVLTree.

See Functional Pearls: Zippers for more information.

Constructors

forall n . Zipper (AVLNode n a) (Context n a) 

Instances

Show a => Show (Zipper a) 

value :: Zipper a -> aSource

Gets the value at the root of the subtree pointed by that Zipper.

unZip :: AVLTree a -> Zipper aSource

Constructs a Zipper to the root of the given tree.

zipUp :: (Integer -> Integer) -> Zipper a -> AVLTree aSource

Given a function that manipulates the tree size (number of nodes), and a Zipper, constructs an AVLTree with the new height, by zipping up to the root of the tree pointed to by the Zipper.

up :: Zipper a -> Zipper aSource

Navigates up in a Zipper.

canGoUp :: Zipper a -> BoolSource

Returns whether we can navigate up.

left :: Zipper a -> Zipper aSource

Navigates left in a Zipper.

canGoLeft :: Zipper a -> BoolSource

Returns whether we can navigate left.

right :: Zipper a -> Zipper aSource

Navigates right in a Zipper.

canGoRight :: Zipper a -> BoolSource

Returns whether we can navigate right.

isLeft :: Zipper a -> BoolSource

Returns whether the pointed to subtree is a left child of its parent.

isRight :: Zipper a -> BoolSource

Returns whether the pointed to subtree is a right child of its parent.

isLeaf :: Zipper a -> BoolSource

Returns whether the pointed to subtree is a leaf.

zipTo :: Ord a => a -> Zipper a -> Zipper aSource

Descends (never ascends) to a subtree whose root has a given value. If no such subtree exists, points to a Nil where the value would be found, were it to exist.

insertUnbalancedAt :: AVLNode (Succ n) a -> Context n a -> AVLTree aSource

Insert an AVLNode of height (n + 1) in a Context with a hole of size n. Since this cannot be done in the usual way, rotations are used to return an AVLTree that may nothave the same height as the 'Context'\'s tree did, or have the same structure, but holds the same values, and has this enlarged AVLNode in it.

zipToSuccessor :: Zipper a -> Maybe (Zipper a)Source

Given a Zipper to a node in the tree, returns a Zipper to the successor of this node. If no such successor exists, returns Nothing.

zipToPredecessor :: Zipper a -> Maybe (Zipper a)Source

Given a Zipper to a node in the tree, returns a Zipper to the predecessor of this node. If no such predecessor exists, returns Nothing.

zipToSmallest :: Zipper a -> Zipper aSource

Given a Zipper to a node X in the tree, returns a Zipper to the smallest node in the subtree rooted at X.

zipToGreatest :: Zipper a -> Zipper aSource

Given a Zipper to a node X in the tree, returns a Zipper to the greatest node in the subtree rooted at X.

zipToFirstLeftChild :: Zipper a -> Maybe (Zipper a)Source

Given a Zipper Z, which points to a subtree S, returns a Zipper to the first ancestor of S which is a left child of its parent. If such an ancestor does not exist, returns Nothing.

zipToFirstRightChild :: Zipper a -> Maybe (Zipper a)Source

Given a Zipper Z, which points to a subtree S, returns a Zipper to the first ancestor of S which is a right child of its parent. If such an ancestor does not exist, returns Nothing.

fixContext :: forall a n. Eq a => a -> a -> Context n a -> Context n aSource

Replaces a given value by another, in the AVLTree represented by a Context.

deleteBST :: Eq a => Zipper a -> AVLTree aSource

Given a Zipper Z, deletes the value at the root of the subtree pointed to by Z. It returns a modified AVLTree with this change applied. The removal is straight-up BST removal, folowed by an AVL rebalancing.

rebalance :: forall a n. AVLNode n a -> Context (Succ n) a -> AVLTree aSource

Given an AVLNode n a, and a Context with a hole of size (n + 1), returns an AVLTree a with the AVLNode being placed in that Context. Since this cannot be done normally, it uses rotations to return an AVLTree that has the same elements as the Context and the AVLNode together, but may have a different structure than the tree the Context represented.