Re: [Haskell-cafe] Newbie request

2006-06-09 Thread Bertram Felgenhauer
Geevarghese Philip wrote:
> 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?

I'll try.
> 
> Thanks,
> Philip

> >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)
[...]

you can use pattern matching to your advantage, to avoid if-s and
comparisons (you can get rid of the Eq requirement that way)

insert (Empty x)   = Tree x Empty Empty
insert (Tree root Empty rtree) = Tree root (Tree x Empty Empty) rtree
...
insert ... | countNodes x <= countNodes y = ...
   | otherwise= ...

> --
> 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

createTree xs = foldl insert Empty xs

works just as well.

Here are two algorithmic ideas:

1. It's possible to avoid the counting if you create a function that
  inserts multiple values at once, walking the nodes from left to right.
  
  -- walk tree from left to right and insert nodes at the next
  -- level as long as there are elements in the list left;
  -- keep the rest of the tree unmodified.
  insertLevel :: Tree a => [a] -> Tree a -> ([a], Tree a)
  insertLevel [] t = t
  insertLevel (x:xs) Empty = (Tree x Empty Empty, xs)
  insertLevel xs (Tree node ltree rtree) = ...
  
  Then use this function iteratively starting with an empty tree,
  until the whole list is consumed.

2. It's possible to build the tree from bottom up. This works,
  as follows:
  1. split the given list into levels (that is, lists of length 2^n
 starting with n=0. The last, lowest level may be incomplete.)
  2. convert the lowest level into singleton trees.
 Call the result the processed list, and mark the lowest level
 as processed.
  3. For each unprocessed level, starting with the lowest, do:
 Walk through this level and the processed list simultaneously,
 combining one element from the level and two elements from
 the processed list and combining them into a tree Node.
 When the level is exhausted, we take empty trees to fill it
 up.  The result is the new processed list.
  4. Now the processed list is either empty - in which case we
 return an empty tree, or a list that contains a single tree,
 in which case we return that.
  
  Example: (I write E for Empty)
 input = [1,2,3,4,5,6,7,8,9,10]
  1. levels= [[1],[2,3],[4,5,6,7],[8,9,10]]
  2. processed = [Tree 8 E E, Tree 9 E E, Tree 10 E E]
  3. after first iteration:
   processed = [Tree 4 (Tree 8 E E) (Tree 9 E E),
 Tree 5 (Tree 10 E E) E, Tree 6 E E, Tree 7 E E]
 after second iteration:
   processed = [Tree 2 (Tree 4 (Tree 8 E E) (Tree 9 E E))
 (Tree 5 (Tree 10 E E) E), Tree 3 (Tree 6 E E) (Tree 7 E E)]
 after third iteration:
   processed = [Tree 1 ... (the final tree)]
  4. return (Tree 1 ...)
  
  The algorithm simplifies a bit if we follow the convention that the
  processed list always ends in an infinite list of empty trees, can
  you see why?

regards,

Bertram
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie request

2006-06-09 Thread Donald Bruce Stewart
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


[Haskell-cafe] Newbie request

2006-06-09 Thread Geevarghese Philip
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




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe