
19 Dec
2006
19 Dec
'06
1:43 a.m.
The code below does not compile unless the "bar" function is annotated with a suitable constraint on the class of the formal parameter.
module Main where
class (C a) data (C foo) => XY foo = X foo | Y foo
bar :: a -> XY a bar aFoo = X aFoo
main = return ()
I get:
$ ghc Test.hs
Test.hs:8:8: No instance for (C a) arising from use of `X' at Test.hs:8:8-10 Possible fix: add (C a) to the type signature(s) for `foo' In the expression: X a In the definition of `foo': foo a = X a
As suggested, this works:
bar :: (C a) => a -> XY a
Can someone explain to me why the compiler can not infer that "a" (in bar) must be (C a) from the bar result type "XY a" (by way of the "C class" provided for the datatype)? Thanks, - Reto