Derivable type classes bug?

2004-11-22 Thread Koen Claessen
Hi,

Take a look at the following program, making use of
derivable type classes.


module Bug where

import Data.Generics

class Foo a where
  foo :: a - Int
  foo{| Unit |}_ = 1
  foo{| a :*: b |} _ = 2
  foo{| a :+: b |} _ = 3

instance Foo [a]


GHC 6.2.2 produces the following error message:


Bug.hs:12:
Could not deduce (Foo a) from the context (Foo [a])
  arising from use of `foo' at Bug.hs:12


Why is the context needed? 'foo' is not a recursive
function?

I guess it is because the default declaration is split up
into several instances:


instance Foo Unit where
  foo _ = 1

instance (Foo a, Foo b) = Foo (a :*: b) where
  foo _ = 2

instance (Foo a, Foo b) = Foo (a :+: b) where
  foo _ = 3


Why not generating:


instance Foo Unit where
  foo _ = 1

instance Foo (a :*: b) where
  foo _ = 2

instance Foo (a :+: b) where
  foo _ = 3


when the context is not needed?

(My motivation is: I have a class like this:

  class Arbitrary a = Shrink a where
shrinkSub :: a - [a]
shrinkSub{| ... |} = ... shrink ...

The definition of shrinkSub is not recursive, it calls a
function 'shrink' from the Arbitrary class instead.)

Regards,
/Koen

PS. Has the implementation of Generics changed from some
earlier compiler version (GHC 5.xx)? I have code lying
around that I am almost certain of used to compile with an
earlier version of GHC (that I do not have access to
anymore).


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


RE: Derivable type classes bug?

2004-11-22 Thread Simon Peyton-Jones
Yes, you guessed right.  Your generic class declaration gives rise to
instance declarations like

| instance (Foo a, Foo b) = Foo (a :*: b) where
|   foo _ = 2

You suggest that it could be cleverer about guessing the context for the
instance decl, and that would make sense.  But this'd then be the *only*
time that the context of an instance decl was inferred, rather than
provided.  So (a) that's unusual (needs explanation etc), and (b) it'd
require some jiggling in the compiler, which is currently set up for
checking instance decls only.

An alternative, I guess, would be to ask the programmer to supply the
context for the instance decls.  But it's hard to see good syntax.  Were
would the context go in the class decl?

Another alternative could be for the programmer to give the
separated-out instance declarations himself, rather than having them
grouped in the class decl.  But we'd still need some way to signal that
the method should be generated generically. Something like

class Foo a where
  foo :: a - Int 
  generic foo   -- New keyword

instance Foo Unit where ...
instance Foo (a :+: b) where ...
etc

Signalling generic-ness like this could even allow generic-ness on a
method-by-method basis.  Kind of like specifying the default method.  I
don't want to eat another keyword, though.  And somehow it'd be better
if the same signal happened for the current case.  But
class Foo a where
  foo :: a - Int
  generic foo
  foo {| Unit |} = ...
seems rather heavy.   

So the possibilities are:

(A).  Infer the instance context.
(B).  Somehow specify the instance contexts in the class decl
(C).  Optionally, give separate instances for Unit, :+: etc, plus a
signal
in the class decl the default method is generic.  Syntax?

I think my preferences would go (C), (A), (B); if we could agree a
syntax for (C).  

Does anyone else have a (somewhat informed) opinion?

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:glasgow-haskell-bugs-
| [EMAIL PROTECTED] On Behalf Of Koen Claessen
| Sent: 16 November 2004 17:17
| To: [EMAIL PROTECTED]
| Subject: Derivable type classes bug?
| 
| Hi,
| 
| Take a look at the following program, making use of
| derivable type classes.
| 
| 
| module Bug where
| 
| import Data.Generics
| 
| class Foo a where
|   foo :: a - Int
|   foo{| Unit |}_ = 1
|   foo{| a :*: b |} _ = 2
|   foo{| a :+: b |} _ = 3
| 
| instance Foo [a]
| 
| 
| GHC 6.2.2 produces the following error message:
| 
| 
| Bug.hs:12:
| Could not deduce (Foo a) from the context (Foo [a])
|   arising from use of `foo' at Bug.hs:12
| 
| 
| Why is the context needed? 'foo' is not a recursive
| function?
| 
| I guess it is because the default declaration is split up
| into several instances:
| 
| 
| instance Foo Unit where
|   foo _ = 1
| 
| instance (Foo a, Foo b) = Foo (a :*: b) where
|   foo _ = 2
| 
| instance (Foo a, Foo b) = Foo (a :+: b) where
|   foo _ = 3
| 
| 
| Why not generating:
| 
| 
| instance Foo Unit where
|   foo _ = 1
| 
| instance Foo (a :*: b) where
|   foo _ = 2
| 
| instance Foo (a :+: b) where
|   foo _ = 3
| 
| 
| when the context is not needed?
| 
| (My motivation is: I have a class like this:
| 
|   class Arbitrary a = Shrink a where
| shrinkSub :: a - [a]
| shrinkSub{| ... |} = ... shrink ...
| 
| The definition of shrinkSub is not recursive, it calls a
| function 'shrink' from the Arbitrary class instead.)
| 
| Regards,
| /Koen
| 
| PS. Has the implementation of Generics changed from some
| earlier compiler version (GHC 5.xx)? I have code lying
| around that I am almost certain of used to compile with an
| earlier version of GHC (that I do not have access to
| anymore).
| 
| 
| ___
| Glasgow-haskell-bugs mailing list
| [EMAIL PROTECTED]
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs