[Haskell-cafe] C++ class = neutered (haskell class + haskell existential)

John Meacham john at repetae.net
Thu Aug 17 21:16:45 EDT 2006


On Tue, Aug 15, 2006 at 08:36:28PM +0200, Gabriel Dos Reis wrote:
> Roughly Haskell type classes correspond to parameterized abstract
> classes in C++ (i.e. class templates with virtual functions 
> representing the operations).  Instance declarations correspond to
> derivation and implementations of those parameterized classes.

There is a major difference though, in C++ (or java, or sather, or c#,
etc..) the dictionary is always attached to the value, the actual class
data type you pass around. in haskell, the dictionary is passed
separately and the appropriae one is infered by the type system. C++
doesn't infer, it just assumes everything will be carying around its
dictionary with it.

this makes haskell classes signifigantly more powerful in many ways.

class Num a where
   (+) :: a -> a -> a

is imposible to express in OO classes, since both arguments to +
necessarily carry their dictionaries with them, there is no way to
statically guarentee they have the same one. Haskell will pass a single
dictionary that is shared by both types so it can handle this just fine.

in haskell you can do

class Monoid a where
        mempty :: a

in OOP, this cannot be done because where does the dicionary come from?
since dictionaries are always attached to a concrete class, every method
must take at least one argument of the class type (in fact, exactly one,
as I'll show below). In haskell again, this is not a problem since the
dictionary is passed in by the consumer of 'mempty', mempty need not
conjure one out of thin air.


In fact, OO classes can only express single parameter type classes where
the type argument appears exactly once in strictly covariant position.
in particular, it is pretty much always the first argument and often
(but not always) named 'self' or 'this'.


class HasSize a where
        getSize :: a -> Int

can be expressed in OO, 'a' appears only once, as its first argument.


Now, another thing OO classes can do is they give you the ability to
create existential collections (?) of objects. as in, you can have a
list of things that have a size. In haskell, the ability to do this is
independent of the class (which is why haskell classes can be more
powerful) and is appropriately named existential types.

data Sized = exists a . HasSize a => Sized a 

what does this give you? you can now create a list of things that have a
size  [Sized] yay!

and you can declare an instance for sized, so you can use all your
methods on it.

instance HasSize Sized where
        getSize (Sized a) = a


an exisential, like Sized, is a value that is passed around with its
dictionary in tow, as in, it is an OO class! I think this is where
people get confused when comparing OO classes to haskell classes. _there
is no way to do so without bringing existentials into play_. OO classes
are inherently existential in nature.

so, an OO abstract class declaration declares the equivalent of 3 things
in haskell: a class to establish the mehods, an existential type to
carry the values about, and an instance of the class for the exisential
type.

an OO concrete class declares all of the above plus a data declaration
for some concrete representation.


OO classes can be perfectly (even down to the runtime representation!)
emulated in Haskell, but not vice versa. since OO languages tie class
declarations to existentials, they are limited to only the intersection
of their capabilities, because haskell has separate concepts for them,
each is independently much much more powerful.

data CanApply = exists a b . CanApply (a -> b) a (b -> a)

is an example of something that cannot be expressed in OO, existentials
are limited to having exactly a single value since they are tied to a
single dictionary


class Num a where
   (+) :: a -> a -> a
   zero :: a
   negate :: a -> a

cannot be expressed in OO, because there is no way to pass in the same
dicionary for two elements, or for a returning value to conjure up a
dictionary out of thin air. (if you are not convinced, try writing a
'Number' existential and making it an instance of Num and it will be
clear why it is not possible)

negate is an interesting one, there is no technical reason it cannot be
implemented in OO languages, but none seem to actually support it.


so, when comparing, remember an OO class always cooresponds to a haskell
class + a related haskell existential.


incidentally, an extension I am working on is to allow

data Sized = exists a . HasSize a => Sized a 
        deriving(HasSize)

which would have the obvious interpretation, obviously it would only work
under the same limitations as OO classes have, but it would be a simple
way for haskell programs to declare OO style classes if they so choose.

(actually, it is still signifigantly more powerful than OO classes since
you can derive many instances, and even declare your own for classes
that don't meet the OO consraints, also, your single class argument need
not appear as the first one. it can appear in any strictly covarient
position, and it can occur as often as you want in contravariant ones!)


        John





[1] exists is called forall in ghc





> -- 
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 

-- 
John Meacham - ⑆repetae.net⑆john⑈


More information about the Haskell-Cafe mailing list