
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.

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.

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@haskell.org [mailto:glasgow-haskell-users- | bounces@haskell.org] On Behalf Of Geoffrey Alan Washburn | Sent: 04 June 2006 18:53 | To: glasgow-haskell-users@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@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Simon Peyton-Jones wrote:
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.
I must admit I can't understand where the ambiguity actually is. bar has been defined as a -> Int, so surely anything on the rhs of an equation for an instance of the bar method in Foo is therefore an Int also, so having to explicitly write 1::Int seems superfluous. bar([x]) = 1 -- why is ::Int needed when we know that bar:: a->Int ??? Also, the error message suggests that the ambiguity is caused by Foo t and Num t, but what's the problem - surely this just means t belongs to both Foo and Num? Thanks, Brian.
So it seems that this is all fine.
Simon
-----Original Message----- From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell-users- bounces@haskell.org] On Behalf Of Geoffrey Alan Washburn Sent: 04 June 2006 18:53 To: glasgow-haskell-users@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)
-- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

Brian Hulley wrote:
I must admit I can't understand where the ambiguity actually is. bar has been defined as a -> Int, so surely anything on the rhs of an equation for an instance of the bar method in Foo is therefore an Int also, so having to explicitly write 1::Int seems superfluous.
bar([x]) = 1 -- why is ::Int needed when we know that bar:: a->Int ???
I haven't tested the combination where I omit the annotation on "bar([x]) = 1", but I believe that the annotation is only actualyl necessary for the "bar [] = bar [1]" case where ghc cannot determine the type at which it needs to be calling bar recursively.

Geoffrey Alan Washburn wrote:
Brian Hulley wrote:
I must admit I can't understand where the ambiguity actually is. bar has been defined as a -> Int, so surely anything on the rhs of an equation for an instance of the bar method in Foo is therefore an Int also, so having to explicitly write 1::Int seems superfluous.
bar([x]) = 1 -- why is ::Int needed when we know that bar:: a->Int ???
I haven't tested the combination where I omit the annotation on "bar([x]) = 1", but I believe that the annotation is only actualyl necessary for the "bar [] = bar [1]" case where ghc cannot determine the type at which it needs to be calling bar recursively.
Oh I see now - I was looking at the wrong "1" ! :-) Thanks, Brian.
participants (3)
-
Brian Hulley
-
Geoffrey Alan Washburn
-
Simon Peyton-Jones