Bug? Or at least a better error message?
Simon Peyton-Jones
simonpj at microsoft.com
Mon Jun 5 08:54:14 EDT 2006
Right. The crash was definitely a bug, but it seems to have been fixed.
The error message about ambiguity is just what you'd expect.
So it seems that this is all fine.
Simon
| -----Original Message-----
| From: glasgow-haskell-users-bounces at haskell.org
[mailto:glasgow-haskell-users-
| bounces at haskell.org] On Behalf Of Geoffrey Alan Washburn
| Sent: 04 June 2006 18:53
| To: glasgow-haskell-users at haskell.org
| Cc: Stephanie C Weirich
| Subject: Re: Bug? Or at least a better error message?
|
|
| I just upgraded to ghc 6.5.20060603 and now I get the following
error
|
| Prelude> :load strange.hs
| [1 of 1] Compiling Testing ( strange.hs, interpreted )
|
| strange.hs:9:13:
| Ambiguous type variable `t' in the constraints:
| `Foo t' arising from use of `bar' at strange.hs:9:13-19
| `Num t' arising from the literal `1' at strange.hs:9:18
| Probable fix: add a type signature that fixes these type
| variable(s)
| Failed, modules loaded: none.
|
| If I wrap "1" with ( :: Int) it seems to be accepted.
|
|
| Geoffrey Alan Washburn wrote:
| > While trying out the following example, in an attempt to learn
something
| > about the fiddly case where a type class instance tries to use an
| > instance that is more specific than itself
| >
| > module Testing where
| >
| > class Foo a where { bar :: a -> Int }
| >
| > instance Foo Int where
| > bar i = i
| >
| > instance Foo a => Foo [a] where
| > bar [] = bar [1]
| > bar ([x]) = 1
| > bar (x:xs) = (bar x) + (bar xs)
| >
| > It is kind of like polymorphic recursion, I suppose. I get the
| > following exception
| >
| > [1 of 1] Compiling Testing ( strange.hs, interpreted )
| > *** Exception: typecheck/TcEnv.lhs:(365,0)-(392,32):
Non-exhaustive
| > patterns in function find_thing
| >
| > Is the example supposed to work? I'm trying to determine the source
| > of a problem with type classes and GADTs and I figured this example
| > using "normal" data types would be a good place to start in
| > understanding what was going wrong.
| >
| > I was using ghci version 6.5.20060503.
|
| _______________________________________________
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users at haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
More information about the Glasgow-haskell-users
mailing list