[Haskell-cafe] Type question in instance of a class

Claude Heiland-Allen claudiusmaximus at goto10.org
Sun Nov 16 17:01:20 EST 2008


Maurí­cio wrote:
> Hi,
> 
> Why is this wrong?
> 
> ----
> class MyClass r where function :: r -> s
> 
> data MyData u = MyData u
> 
> instance MyClass (MyData v) where function (MyData a) = a
> ----
> 
> GHC says that the type of the result of 'function' is both determined by
> the "rigid type" from MyClass and  the "rigid type" from MyData. But why
> can't both be the same?

particular instances can't add extra restrictions (eg: "both types are 
the same") to the interface declared by the class (eg: "both types are 
arbitrary").


Compare this version:

----8<----
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}
module Test where
class MyClass r s where function :: r -> s
data MyData u = MyData u
instance MyClass (MyData v) v where function (MyData a) = a
----8<----

And ghci session:

----8<----
*Test> function (MyData "hello")

<interactive>:1:0:
     No instance for (MyClass (MyData [Char]) s)
       arising from a use of `function' at <interactive>:1:0-24
     Possible fix:
       add an instance declaration for (MyClass (MyData [Char]) s)
     In the expression: function (MyData "hello")
     In the definition of `it': it = function (MyData "hello")
*Test> :t function (MyData "hello")
function (MyData "hello") :: (MyClass (MyData [Char]) s) => s
*Test> function (MyData "hello") :: String
"hello"
----8<----

I don't know how evil those language extensions are, though - I just 
fiddled until it worked...

> What am I doing wrong?


Claude
-- 
http://claudiusmaximus.goto10.org/



More information about the Haskell-Cafe mailing list