Binary search tree (Haskell)

From LiteratePrograms

Jump to: navigation, search
Other implementations: C | C++ | Haskell | Java | Scheme | Standard ML

A Binary Search Tree is a tree, where each node has two children, and the children are related in a manner which allows them to be compared. The generic example is that all items to the left of a given node are less than that node, and all items to the right are greater. How equality is treated is ambiguous, and depends on the specific application of the tree.

This file contains basic Binary Search Tree functions (including the data type definition) which operate unrelated to the actual contents of the BST.

<<BinarySearch.hs>>=
-- This file contains functions to work with Binary Search Trees unrelated to their contents.
module BinarySearch where
-- The data type definition.  A tree can consist of either a Tip or a node with a value and two tree.
data Tree a = Tip | Node a (Tree a) (Tree a) deriving (Show,Eq)
-- Returns a leaf node, makes writing leafs easier
leaf x = Node x Tip Tip
-- Some examples of structure in code
t1 = Node 10 Tip Tip
t2 = Node 17 (Node 12 (Node 5 Tip (leaf 8)) (leaf 15))
             (Node 115
                   (Node 32 (leaf 30) (Node 46 Tip (leaf 57)))
                   (leaf 163))
-- The size of the tree - the number of items in the tree
size Tip = 0
size (Node _ tl tr) = 1 + size tl + size tr
-- Converts a tree into a list.  This list, if converted back into a tree, will return the same tree
treeToList Tip = []
treeToList (Node x xl xr) = x : treeToList xl ++ treeToList xr
-- Converts a tree into a sorted list.  This list will not convert back into the same tree.
treeToListOrd Tip = []
treeToListOrd (Node x xl xr) = treeToListOrd xl ++ x : treeToListOrd xr
-- Visually outputs a tree (sideways) by indenting each next node and additional tab in, outputs the right side, then the node, then the left side
pict t = putStr (pic "" t)
         where pic ind Tip = ind ++ "."
               pic ind (Node x tl tr) = pic ('\t':ind) tr ++ "\n" ++
                                        ind ++ show x     ++ "\n" ++
                                        pic ('\t':ind) tl ++ "\n"
-- Finds farthest left item.  In a BST this is the smallest value
farLft (Node x Tip _) = x
farLft (Node x xl _) = farLft xl
-- Finds farthest right item.  In a BST this is the largest value
farRt (Node x _ Tip) = x
farRt (Node x _ xr) = farRt xr
-- Mirrors a tree, so every right and left node switch
mirror Tip = Tip
mirror (Node x xl xr) = Node x (mirror xr) (mirror xl)

This file contains functions which work with BSTs of naturally comparable items, such as numbers and strings. The comparison function is (<=)

<<BinarySearchNum.hs>>=
-- This file contains functions to work with Numeric (and string, since Haskell can use the < operator on strings) Binary Search Trees.
module BinarySearchNum where
import BinarySearch
-- Insert into a tree
-- The third parameter is a comparator function, if the contents of the tree are not numbers or strings, you can pass a different function to this third parameter to properly define how to compare, and therefore sort, the tree.
insert a Tip = leaf a
insert a (Node x xl xr) | a <= x    = Node x (insert a xl) xr
                        | otherwise = Node x xl (insert a xr)
-- Converts a list to a tree, using either comparator function f, or the natural (<=) function
listToTree = foldl (flip insert) Tip
-- Tree Sort - takes a list, and sorts it by converting to a tree and then back to a list
tsort = treeToListOrd . listToTree
-- Adds up all items in a numerical Binary Tree
sumt Tip = 0
sumt (Node x xl xr) = x + sumt xl + sumt xr
-- Finds smalles item in a tree (not necessarily ordered)
-- This function does not deal with a tree which is just a tip
mint (Node x Tip Tip) = x
mint (Node x xl Tip)  = min x (mint xl)
mint (Node x Tip xr)  = min x (mint xr)
mint (Node x xl xr)   = min x (min (mint xl) (mint xr))
-- Finds largest item in a tree (not necessarily ordered)
-- This function does not deal with a tree which is just a tip
maxt (Node x Tip Tip) = x
maxt (Node x xl Tip)  = max x (maxt xl)
maxt (Node x Tip xr)  = max x (maxt xr)
maxt (Node x xl xr)   = max x (max (maxt xl) (maxt xr))
-- Finds height of tree
height Tip = 0
height (Node _ xl xr) = 1 + max (height xl) (height xr)

This file contains functions which work with any binary search tree. The comparison function must be specified via the f parameter.

<<BinarySearchAll.hs>>=
-- This file contains functions to work with any kind of Binary Search Tree - the comparison operator is passed as needed by the f parameter
module BinarySearchAll where
import BinarySearch
-- Insert into a tree
-- The third parameter is a comparator function, if the contents of the tree are not numbers or strings, you can pass a different function to this third parameter to properly define how to compare, and therefore sort, the tree.
insert a Tip _ = leaf a
insert a (Node x xl xr) f | f a x     = Node x (insert a xl f) xr
                          | otherwise = Node x xl (insert a xr f)
-- Converts a list to a tree, using either comparator function f, or the natural (<=) function
listToTree ls f = foldl (\tre x -> insert x tre f) Tip ls
-- Tree Sort - takes a list, and sorts it by converting to a tree and then back to a list
tsort ls f = treeToListOrd (listToTree ls f)
-- Adds up all items in a numerical Binary Tree
-- h is a function which combines two items - default would be (+)
sumt Tip h = 0
sumt (Node x xl xr) h = h (h x (sumt xl h)) (sumt xr h)
-- Finds smalles item in a tree (not necessarily ordered) using comparator f
-- This function does not deal with a tree which is just a tip
mint (Node x Tip Tip) f = x
mint (Node x xl Tip) f  | f x xlSm  = x
                        | otherwise = xlSm
                        where xlSm = mint xl f
mint (Node x Tip xr) f  | f x xrSm  = x
                        | otherwise = xrSm
                        where xrSm = mint xr f
mint (Node x xl xr) f   | f x xlSm && f x xrSm = x
                        | f xlSm xrSm          = xlSm
                        | otherwise            = xrSm
                        where xlSm = mint xl f
                              xrSm = mint xr f
-- Finds largest item in a tree (not necessarily ordered) using comparator f
-- flips the parameters of f in order to find the largest using a smaller-than comparator
-- This function does not deal with a tree which is just a tip
maxt (Node x Tip Tip) f = x
maxt (Node x xl Tip) f  | (flip f) x xlSm = x
                        | otherwise       = xlSm
                        where xlSm = maxt xl f
maxt (Node x Tip xr) f  | (flip f) x xrSm = x
                        | otherwise       = xrSm
                        where xrSm = maxt xr f
maxt (Node x xl xr) f   | (flip f) x xlSm && (flip f) x xrSm = x
                        | (flip f) xlSm xrSm                 = xlSm
                        | otherwise                          = xrSm
                        where xlSm = maxt xl f
                              xrSm = maxt xr f
-- Finds height of tree
height Tip = 0
height (Node _ xl xr) = 1 + max (height xl) (height xr)
Views