[Haskell-beginners] instances of different kinds

Greg greglists at me.com
Sat Aug 28 06:44:38 EDT 2010


On Aug 27, 2010, at 8:15 PM, Brandon S Allbery KF8NH wrote:

> You were told about this already:  

No doubt I'm being quite dense here.  I think your re-explanation may have clicked though: 

> because "b" is only mentioned in the
> result of div2pi, it must be able to return *any* "b" that has a Floating
> instance.
> 
> But then you say
>> instance (Floating a) => TwoPi (Foo a)  where
>>  div2pi (Foo x) = x / (2*pi)
> 
> An instance applies to a *specific* type; thus, this instance declaration
> forces a *specific* type on the result of div2pi, when the class declaration
> says it must be able to return *any* type.
> 
> Expanding the types, the class declaration says
> 
>> div2pi :: forall b. (Floating a, Floating b) => a -> b
> 
> but the instance declares
> 
>> div2pi :: (Floating a) => a -> a
> 
> The instance doesn't conform to the class definition; it includes a
> constraint that the class does not, as the class insists that the type of
> the result must be independent of the type of the argument, while the
> instance insists that they must be identical.

I've been working on the assumption, perhaps despite attempts to teach me otherwise, that the class is essentially the interface to the rest of the world.  That is, the class is the guarantee.  The instance, then, can do no less than the class interface has guaranteed.  In this case, for example, I've been assuming that the type variable 'b' in my class definition meant "div2pi will result in a value of a type which is an instance of the Floating class".  Then, since my instance method resulted in a Float, which is an instance of the Floating class, everything should be happy.  If my instance method resulted in a Double, it would be equally happy.

I think what you're saying is that not only can an instance do no less than the class has guaranteed, it can do no *more*-- meaning the instance can't further restrict the return type even if that return type still conforms to the class definition.  In this case returning a Float breaks the class contract because I've gone and said what type of Floating type will be returned.  

The class definition doesn't mean "div2pi can return any type of Floating value", it means "div2pi *will* return any type of floating value".

I have a harder time working out why returning a "(Floating a) => a" is seen as different.  If I understand what Jürgen was saying, it's because the "a" in this case is specifically the "a" in "Foo a", which nails it down again.  If this is right, then my class definition:

> class TwoPi a where
>  div2pi :: (Floating b) => a -> b

is essentially impossible to conform to because b is completely untethered to anything else in the code and not all "(Floating b)"'s are created equal.  I think the intent of the functional dependency in the suggestion you provided in your second email is essentially to tether b to something.  Unfortunately if chokes in the second, non-Foo, instance.


Am I getting this right?  Rereading Jürgen's response, this seems to fit with his explanation as well-- I just didn't grasp it.

I think I've mistakenly been thinking of instances as more like subclasses, but that's apparently not quite right (thus the "instance" keyword, I suppose).

> 
> Perhaps the correct question is "what exactly are you trying to do?"
> 

I'm literally just trying to understand the type system and its syntax.  It's the part of Haskell that feels most foreign, and I'm trying to work through the implications.

Typeclasses provide a mechanism to abstract operations over multiple types, as you mentioned in the thread for my last question.  What I'm trying to figure out now is what kinds of types they can be abstracted over.  I'm looking to get the result:  "((5.6,Foo 9.8),(0.8912676813146139,1.5597184423005745))"

From code that looks kind of like this :

data Foo a = Foo a deriving (Show)

x :: Float
x= 5.6

y :: Foo Double
y= Foo 9.8

class {-something-} TwoPi {-something-} where
  div2pi :: {-something-}

instance {-something-} TwoPi Foo where
  div2pi (Foo b) = b / (2*pi)

instance TwoPi Float where
  div2pi a = a / (2*pi)

main = do
  print ((x,y),(div2pi x, div2pi y))

Thanks--
 Greg



-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/beginners/attachments/20100828/7d6f1199/attachment.html


More information about the Beginners mailing list