Zipper monad/TravelBTree
TravelBTree
is a library based on the Zipper monad which is used for traversing B-trees; trees where each node has an arbitrary number of branches. Read the documentation for the Zipper monad if you haven't already.
Definition
data BTree a = Leaf a | Branch [BTree a] deriving (Show, Eq)
data Cxt a = Top | Child { parent :: Cxt a, -- parent's context
lefts :: [BTree a], -- siblings to the left
rights :: [BTree a] -- siblings to the right
}
deriving (Show, Eq)
type BTreeLoc a = Loc (Cxt a) (BTree a)
type TravelBTree a = Travel (BTreeLoc a) (BTree a)
The BTree
type is fairly self-explanatory. Branch
must be given a list of its children. Cxt
is the type used for storing the context of a subtree. A BTreeLoc
represents completely a subtree, said subtrees position within the entire tree, and the entire tree itself. See Zipper for an explanation of such concepts.
Functions
Moving around
There are five main functions for stringing together TravelBTree
computations:
-- moves down to the nth child (0-indexed)
down :: Int -> TravelBTree a
left, -- moves left a sibling
right, -- moves right a sibling
up, -- moves to the node's parent
top -- moves to the top node
:: TravelTree a
All five return the subtree at the new location. Note that down
uses 0-indexed children, i.e. down 0
goes down to the first child. This is consistent with the list-access operator, (!!)
.
Mutation
You get the three functions provided by the generic Zipper monad (modifyStruct
, getStruct
and putStruct
), but there's also a load of TravelBTree
-specific mutation functions:
insertLeft, -- insert a tree to the left of the current node
insertRight, -- insert a tree to the right of the current node
insertDown -- insert a tree as the last child of the current node
:: BTree a -> TravelBTree a
insertDownAt -- insert a tree as the nth child of the current node
:: BTree a -> Int -> TravelBTree a
-- delete the current node. If we're the last node of our siblings, move left.
-- If not, move right. If we're an only child move up.
delete :: TravelBTree a
Node classification
There are four functions you can call to find out what kind of node a given location points to:
isTop, -- is the location the top node?
isChild, -- is the location the child of some other node (i.e. not the top)?
isFirst, -- is the location the first of its siblings?
isRight -- is the location the last of its siblings?
:: TreeLoc a -> Bool
Note that these functions are not monadic but instead take a TreeBLoc
. The TreeBLoc
pointing to the current node is stored as the state in a TravelBTree
computation. Thus to call these functions within a do
block, use liftM
:
do top <- liftM isTop get
when top $ down 3 >> return ()
Examples
Watch this space.
Code
The code of this file is quite length, so you can just download it. Alternatively, download the entire zipper library.