Internal Type Error

Leon Smith lps@po.cwru.edu
Fri, 10 Nov 2000 02:06:11 -0400


This is a multi-part message in MIME format.

------=_NextPart_000_0137_01C04ABA.CBF3D120
Content-Type: text/plain;
	charset="iso-8859-1"
Content-Transfer-Encoding: 7bit

I'm using some Multi-parameter Type Classes with the November 1999 version
of Hugs98 on Windows command-line version and getting the following internal
type error:

WinHugs simply chokes and dies.

At one point, the hugs command-line version was accepting the code if I
commented out the function definitions but left the constant data
definition, but after restarting hugs, it seems to always get a internal
type-check error.
__   __ __  __  ____   ___      _________________________________________
||   || ||  || ||  || ||__      Hugs 98: Based on the Haskell 98 standard
||___|| ||__|| ||__||  __||     Copyright (c) 1994-1999
||---||         ___||           World Wide Web: http://haskell.org/hugs
||   ||                         Report bugs to: hugs-bugs@haskell.org
||   || Version: November 1999  _________________________________________

Hugs mode: Restart with command line option +98 for Haskell 98 mode

Reading file "C:\LANG\HUGS98\lib\Prelude.hs":

Hugs session for:
C:\LANG\HUGS98\lib\Prelude.hs
Type :? for help
Prelude> :l scripts/error.hs
Reading file "scripts/error.hs":
Type checking
INTERNAL ERROR: findBtyvsInt
Prelude>


best,
leon

------=_NextPart_000_0137_01C04ABA.CBF3D120
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 $ addKey t (elt,())
-}
------=_NextPart_000_0137_01C04ABA.CBF3D120--