Internal Type Error

Leon Smith lps@po.cwru.edu
Fri, 10 Nov 2000 03:41:15 -0400


This is a multi-part message in MIME format.

------=_NextPart_000_0148_01C04AC8.141355E0
Content-Type: text/plain;
	charset="iso-8859-1"
Content-Transfer-Encoding: 7bit

I found a minor mistake in the example code, but the same problem remains.

The "real" code is a 2-3-4 Tree which I'd like to use to implement a couple
different things, such as Finite Maps and Sets.  It works fine without type
classes.

best,
leon

------=_NextPart_000_0148_01C04AC8.141355E0
Content-Type: application/octet-stream;
	name="error.hs"
Content-Transfer-Encoding: 7bit
Content-Disposition: attachment;
	filename="error.hs"

class Set set a where
	empty   :: set a
	hasElem :: set a -> a -> set a
	addElem :: set a -> a -> set a
	
data Ord a => Tree a b =
	    Leaf a b
	|   Branch (Tree a b) a (Tree a b)

lookupKey :: Ord a => Tree a b -> a -> (a,b)
lookupKey (Leaf a b) key = (a,b)
lookupKey (Branch l a r) key 
		| key < a   = lookupKey l key
		| otherwise = lookupKey r key

addKey :: Ord a => Tree a b -> (a,b) -> Tree a b
addKey n@(Leaf a' _) (a,b)
	| a <  a'   = (Branch (Leaf a b) a' n)
	| a == a'   = Leaf a b
	| otherwise = (Branch n a (Leaf a b))
addKey (Branch l a' r) e@(a,b)
	| a <  a'   = Branch (addKey l e) a' r
	| otherwise = Branch l a' (addKey r e)

newtype Ord a => TreeSet a = MkTreeSet (Maybe (Tree a ()))

instance (Ord a) => Set TreeSet a where
	empty = MkTreeSet Nothing
	hasElem (MkTreeSet Nothing)  elt = False
	hasElem (MkTreeSet (Just t)) elt = elt == a
		where (a,_) = lookupKey t elt
	addElem (MkTreeSet Nothing)  elt = MkTreeSet $ Just (Leaf elt ())
	addElem (MkTreeSet (Just t)) elt = MkTreeSet $ Just (addKey t (elt,()))
------=_NextPart_000_0148_01C04AC8.141355E0--