INTERNAL ERROR: findBtyvsInt strikes again!
Sigbjorn Finne
sof at galois.com
Fri Dec 19 08:03:04 EST 2003
Hi there,
thanks for a fine report. This has been fixed in the CVS sources,
but not in time for the Nov2003 release.
Notice that your code snippet depends on a feature of the
scoped type variable extension that's not supported by
Hugs (tyvars in the head of a class/instance decl being in scope);
see 7.4.10.2 of the GHC documentation:
http://haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html
--sigbjorn
----- Original Message -----
From: "Alexandru D. Salcianu" <salcianu at MIT.EDU>
To: <hugs-bugs at haskell.org>
Sent: Thursday, November 20, 2003 16:40
Subject: INTERNAL ERROR: findBtyvsInt strikes again!
>
> Hello!
>
> I'm using Hugs (the November 2002 version) and I've encountered the
> "INTERNAL ERROR: findBtyvsInt" error. I've read online that this
> error was known in the November 1999 version, but was fixed in the
> 2000 version. I'm using the 2002 version and still get it.
>
> I've encountered the error while working on a collection library (of
> course, I'm using the multi-parameter typeclass extension).
>
> $ hugs -98
> __ __ __ __ ____ ___ _________________________________________
> || || || || || || ||__ Hugs 98: Based on the Haskell 98 standard
> ||___|| ||__|| ||__|| __|| Copyright (c) 1994-2002
> ||---|| ___|| World Wide Web: http://haskell.org/hugs
> || || Report bugs to: hugs-bugs at haskell.org
> || || Version: November 2002 _________________________________________
>
> Hugs mode: Restart with command line option +98 for Haskell 98 mode
>
> Reading file "/usr/lib/hugs/lib/Prelude.hs":
>
> Hugs session for:
> /usr/lib/hugs/lib/Prelude.hs
> Type :? for help
> Prelude> :load Map.hs
> Reading file "Map.hs":
> Type checking
> INTERNAL ERROR: findBtyvsInt
> Prelude> :version
> -- Hugs Version November 2002
>
> Here is the content of Map.hs:
>
> module Map where
>
> -- objects of type ce represent sets of e's
> class (Eq e) => Set e ce | ce -> e where
> equalSet :: ce -> ce -> Bool
>
> -- objects of type map represent maps from key to value
> class (Eq key) => FiniteMap key value map | map -> key value where
> -- returns all keys from map, as a set of type keyset
> mapKeys :: (Set key keyset) => map -> keyset
>
> equalMap :: map -> map -> Bool
> {-- ERROR in this incomplete default implem. of equalMap --}
> equalMap m1 m2 =
> let
> (keys1 :: [key]) = (mapKeys m1)
> (keys2 :: [key]) = (mapKeys m2)
> in
> equalSet keys1 keys2
>
> instance (Eq a) => Set a [a] where
> equalSet = (==)
>
>
> (I've trimmed the code down to obtain a small bug report; the above
> code should be enough to trigger the error). This code compiles fine
> with the GHC 6 (with the command line "ghc -c -fglasgow-exts Map.hs").
>
> Best,
>
> Alex
More information about the Hugs-Bugs
mailing list