[Haskell-cafe] Newbie request

Geevarghese Philip gphilip.newsgroups at gmail.com
Thu Jun 8 17:27:01 EDT 2006


I am trying to learn Haskell. As an exercise, I wrote a
function to create a binary tree in level-order. I am attaching
the code. I am sure there are a number of places where
the code could be improved. Could you please point these out?

Thanks,
Philip

------------------------------------------------------------------------------
BinTree.lhs : Implementation of a binary tree. createTree 
accepts a sequence and builds a binary tree in level-order.
------------------------------------------------------------------------------

>module BinTree where

------------------------------------------------------------------------------
A binary tree either 
1. is empty, or
2. consists of three distinct binary trees : a root node, a left 
subtree, and a right subtree.
------------------------------------------------------------------------------

>data Tree a = Empty | Tree {rootNode::a, left::(Tree a), 
				right::(Tree a)} deriving (Eq, Show)

------------------------------------------------------------------------------
Count the number of nodes in a binary tree, using the simple 
recursive definition of the count.
------------------------------------------------------------------------------

>countNodes :: Tree a -> Integer
>countNodes Empty = 0
>countNodes (Tree rootNode left right) = 1 + countNodes left 
						+ countNodes right

------------------------------------------------------------------------------
Insert a single element into the proper place in the tree, as 
per level-order.
------------------------------------------------------------------------------

>insert :: Eq a => Tree a -> a -> Tree a
>insert tree x = if tree == Empty
>                       then Tree x Empty Empty
>                       else if (left tree) == Empty
>                               then Tree (rootNode tree) (Tree x Empty Empty) (right tree)
>                               else if (right tree) == Empty 
>                                       then Tree (rootNode tree) (left tree) (Tree x Empty Empty) 
>                                       else if countNodes (left tree) <= countNodes (right tree)
>                                               then Tree (rootNode tree) (insert (left tree) x) (right tree)
>                                               else Tree (rootNode tree) (left tree) (insert (right tree) x)

------------------------------------------------------------------------------
Use insert to create a tree from a sequence.
------------------------------------------------------------------------------

>createTree :: Eq a => [a] -> Tree a
>createTree [] = Empty
>createTree (x:xs) = foldl insert (insert Empty x) xs






More information about the Haskell-Cafe mailing list