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

Reply via email to