gphilip.newsgroups: > 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?
There's a highly efficient example here, not exactly a beginner's example, but perhaps useful: http://shootout.alioth.debian.org/gp4/benchmark.php?test=binarytrees&lang=ghc&id=2 > > ------------------------------------------------------------------------------ > 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) Too many parens, perhaps? Those (Tree a)'s look unnecessary. > ------------------------------------------------------------------------------ > 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) Logic looks too convoluted. Perhaps use guards and pattern matching: insert Empty x = Tree x Empty Empty insert (Tree root Empty r) x = Tree root (Tree x Empty Empty) r insert (Tree root l Empty) x = Tree root l (Tree x Empty Empty) insert (Tree root l r) x | countNodes l <= countNodes r = Tree root (insert l x) r | otherwise = Tree root l (insert r x) Seems inefficent to recalculate countNodes each time though. > ------------------------------------------------------------------------------ > 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 Pretty good. Cheers, Don _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe