show tree

James Grist meemoe_uk@yahoo.com
Wed, 30 Apr 2003 19:54:45 +0100 (BST)


ok, 
I've got a prob with this 'ere piece of code
there is no Show instance for Tree, so I anticipated
the result of typing...

Nil

at the hugs console, which was...

ERROR - Cannot find "show" function for:
*** Expression : Nil
*** Of type    : Tree a   

OK so far, next I tried to write a show instance for
Tree ( near bottom, commented out here ), and I was
suprised to get this error at the hugs console when I
tried to compile it.....

ERROR C:\My Documents\com2020\Heap.hs:16 - Overlapping
instances for class "Show"
*** This instance   : Show (Tree a)
*** Overlaps with   : Show (Tree a)
*** Common instance : Show (Tree a)    

I'm guessing that the compiler has decided that I've
tried to declare a show instance for Tree twice.
But if this is the case, why does typing "Nil" cause
the error it does? 

Someone please explain. Thanks

***

module Heap where

class Heap h where
  empty     :: Ord a => h a
  isEmpty   :: Ord a => h a -> Bool
  insert    :: Ord a => a -> h a -> h a
  merge     :: Ord a => h a -> h a -> h a
  findMin   :: Ord a => h a -> Maybe a
  deleteMin :: Ord a => h a -> h a

toHeap :: (Ord a, Heap h) => [a] -> h a
toHeap xs = foldr insert empty xs

data Way = L | R deriving (Eq, Show)

data Tree a = Nil | Node Way a (Tree a) (Tree a)
	      deriving Show

isNil :: Tree a -> Bool
isNil Nil = True
isNil _   = False

isNode :: Tree a -> Bool
isNode = not . isNil

leftSub :: Tree a -> Tree a
leftSub Nil             = error "leftSub"
leftSub (Node _ _ lt _) = lt

rightSub :: Tree a -> Tree a
rightSub Nil             = error "rightSub"
rightSub (Node _ _ _ rt) = rt

root :: Tree a -> a
root Nil            = error "root"
root (Node _ v _ _) = v

insTree :: Ord a => a -> Tree a -> Tree a
insTree val Nil = Node L val Nil Nil -- L is an
arbitrary choice
insTree val (Node way v lt rt)
    | v==val    = Node way v lt rt   -- no change,
value in tree
    | val < v   = if (way==L) then
		  Node R val (insTree v lt) rt else
		  Node L val lt (insTree v rt)
    | v < val   = if (way==L) then
		  Node R v (insTree val lt) rt else
		  Node L v lt (insTree val rt)

minTree :: Ord a => Tree a -> Maybe a
minTree t
    | isNil t   = Nothing
    | otherwise = Just(root t)

deleteM :: Ord a => Tree a -> Tree a
deleteM Nil              = error "deleteM"
deleteM (Node _ _ lt rt) = join lt rt

join :: Ord a => Tree a -> Tree a -> Tree a
join t Nil = t
join Nil t = t
join lt@(Node way1 v1 lt1 rt1) rt@(Node way2 v2 lt2
rt2)
    | v1 <= v2 = Node L v1 lt1 (join rt1 rt)
    | v2 <  v1 = Node R v2 (join lt lt2) rt2

--instance (Show a) => Show (Tree a) where
--	show a = "as"

instance Heap Tree where

  empty = Nil

  isEmpty = isNil
  
  insert = insTree

  merge = join

  findMin = minTree

  deleteMin = deleteM

***

__________________________________________________
Yahoo! Plus
For a better Internet experience
http://www.yahoo.co.uk/btoffer