Difference between revisions of "OOP vs type classes"

From HaskellWiki
Jump to navigation Jump to search
(added "Type classes is like interfaces" section)
(formatting and "extensions" section)
Line 118: Line 118:
 
Here is a brief listing of differences between OOP classes and Haskell type classes
 
Here is a brief listing of differences between OOP classes and Haskell type classes
   
# Type can appear at any place in function signature: be any
+
=== Type can appear at any place in function signature ===
  +
Type can appear at any place in function signature: be any
 
parameter, inside parameter, in a list (possibly empty), or in a result
 
parameter, inside parameter, in a list (possibly empty), or in a result
   
Line 150: Line 151:
   
   
# Inheritance between interfaces (in "class" declaration) means
+
=== Inheritance between interfaces ===
  +
Inheritance between interfaces (in "class" declaration) means
 
inclusion of base class dictionaries in dictionary of subclass:
 
inclusion of base class dictionaries in dictionary of subclass:
   
Line 179: Line 181:
   
   
# Inheritance between instances (in "instance" declaration) means
+
=== Inheritance between instances ===
  +
Inheritance between instances (in "instance" declaration) means
 
that operations of some class can be executed via operations of other
 
that operations of some class can be executed via operations of other
 
class, i.e. such declaration describe a way to compute dictionary of
 
class, i.e. such declaration describe a way to compute dictionary of
Line 204: Line 207:
   
   
  +
=== Downcasting is a mission impossible ===
   
# Selection between instances are done at compile-time, based only on
+
Selection between instances are done at compile-time, based only on
 
information present at this moment. So don't expect that more concrete
 
information present at this moment. So don't expect that more concrete
 
instance will be selected just because you passed this concrete
 
instance will be selected just because you passed this concrete
Line 236: Line 240:
   
   
  +
=== There is only one dictionary per function call ===
 
# For "eqList :: (Eq a) => [a] -> [a] -> Bool" types of all elements
+
For "eqList :: (Eq a) => [a] -> [a] -> Bool" types of all elements
 
in list must be the same, and types of both arguments must be the same
 
in list must be the same, and types of both arguments must be the same
 
too - there is only one dictionary and it know how to handle variables
 
too - there is only one dictionary and it know how to handle variables
 
of only one concrete type!
 
of only one concrete type!
   
# Existential variables pack dictionary together with variable (looks
+
=== Existential variables is more like OOP objects ===
  +
Existential variables pack dictionary together with variable (looks
 
very like the object concept!) so it's possible to create polymorphic
 
very like the object concept!) so it's possible to create polymorphic
 
containers (i.e. holding variables of different types). But
 
containers (i.e. holding variables of different types). But
Line 259: Line 264:
 
</haskell>
 
</haskell>
   
This code will not work - '<=' can use nor 'a' nor 'b' dictionary.
+
This code will not work - a<=b can use nor 'a' nor 'b' dictionary.
 
Even if orderings for apples and penguins are defined, we still don't have
 
Even if orderings for apples and penguins are defined, we still don't have
 
a method to compare penguin with apple!
 
a method to compare penguin with apple!
  +
  +
  +
== Type class system extensions ==
  +
  +
* Constructor classes (Haskell98)
  +
* MPTC: multi-parameter type classes (Hugs/GHC extension)
  +
* FD & AT: functional dependencies and associated types (FD is a Hugs/GHC extension, AT implemented only in GHC 6.6)
   
   

Revision as of 10:20, 16 August 2006

(this is just a sketch now. feel free to edit/comment it. i will include information you provided into the final version of this tutorial)


I'm almost not used type classes in my application programs, but when I'd gone to implement general-purpose libraries and tried to maintain as much flexibility as possible, it was natural to start build large and complex class hierarchies. I tried to use my C++ experience when doing this but I was many times bitten by the type classes restrictions. Now i think that i have better feeling and mind model for type classes and want to share it with other Haskellers, especially ones having OOP backgrounds.


Type classes is like interfaces/abstract classes, not classes itself

There is no data fields inheritance and data fields itself (so type classes more like to interfaces than to classes itself)....


For those more familiar with Java/C# rather than C++, type classes resemble interfaces more than the classes. In fact, the generics in those languages capture the notion of parametric polymorphism (but Haskell is a language that takes parametric polymorphism quite seriously, so you can expect a fair amount of type gymnastics when dealing with Haskell), so more precisely, type classes are like generic interfaces.

Why interface, and not class? Mostly because type classes do not implement the methods themselves, they just guarantee that the actual types that instantiate the type class will implement specific methods. So the types are like classes in Java/C#.

One added twist: type classes can decide to provide default implementation of some methods (using other methods). You would say, then they are sort of like abstract classes. Right. But at the same time, you cannot extend (inherit) multiple abstract classes, can you?

So a type class is sort of like a contract: "any type that instantiates this type class will have the following functions defined on them..." but with the added advantage that you have type parameters built-in, so:

eqList :: (Eq a) => [a] -> [a] -> Bool

is, in a Java-like language:

interface Eq<A> {
   boolean `==` (A that);
   boolean '/=' (A that) { return !(`==(that)) } // default, can be overriden
}

<T> boolean eqList(T this, T that) where T extends Eq<T> {
  // so that inside the method you can be sure that this.`==`(that) or this.`/=`(that) makes perfect sense
}

And the "instance TypeClass ParticularInstance where ..." definition means "ParticularInstance implements TypeClass { ... }", now, multiple parameter type classes, of course, cannot be interpreted this way.


Type classes is a sort of templates, not classes

At this moment C++/C#/Java languages has classes and templates/generics. What is a difference? With a class, type information carried with object itself while with templates it's outside of object and is part of the whole operation.

For example, if == operation is defined in a class, the actual procedure called for a==b may depend on run-time type of 'a' but if it is defined in template, actual procedure depends only on template instantiated (and determined at compile time).

Haskell's objects don't carry run-time type information. Instead, class constraint for polymorphic operation passed in form of "dictionary" implementing all operations of the class (there are also other implementation techniques, but this don't matter). For example,

eqList :: (Eq a) => [a] -> [a] -> Bool

translated into:

type EqDictionary a = (a->a->Bool, a->a->Bool)
eqList :: EqDictionary a -> [a] -> [a] -> Bool

where first parameter is "dictionary" containing implementation of "==" and "/=" operations for objects of type 'a'. If there are several class constraints, dictionary for each is passed.

If class has base class(es), the dictionary tuple also includes tuples of base classes dictionaries:

class Eq a => Cmp a where
  cmp :: a -> a -> Ordering

cmpList :: (Cmp a) => [a] -> [a] -> Ordering

turns into:

type CmpDictionary a = (eqDictionary a, a -> a -> Ordering)
cmpList :: CmpDictionary a -> [a] -> [a] -> Bool


Comparing to C++, this is like the templates, not classes! As with templates, typing information is part of operation, not object! But while C++ templates are really form of macro-processing (like Template Haskell) and at last end generates non-polymorphic code, Haskell's using of dictionaries allows run-time polymorphism (explanation of run-time polymorphism?).

Moreover, Haskell type classes supports inheritance. Run-time polymorphism together with inheritance are often seen as OOP distinctive points, so during long time i considered type classes as a form of OOP implementation. But that's wrong! Haskell type classes build on different basis, so they are like C++ templates with added inheritance and run-time polymorphism! And this means that usage of type classes is different from using classes, with its own strong and weak points.


Type classes vs classes

Here is a brief listing of differences between OOP classes and Haskell type classes

Type can appear at any place in function signature

Type can appear at any place in function signature: be any parameter, inside parameter, in a list (possibly empty), or in a result

class C a where
    f :: a -> Int
    g :: Int -> a -> Int
    h :: Int -> (Int,a) -> Int
    i :: [a] -> Int
    j :: Int -> a
    new :: a

It's even possible to define instance-specific constants (look at 'new').

If function value is instance-specific, OOP programmer will use "static" method while with type classes you need to use fake parameter:

class FixedSize a where
  sizeof :: a -> Int
instance FixedSize Int8 where
  sizeof _ = 1
instance FixedSize Int16 where
  sizeof _ = 2

main = do print (sizeof (undefined::Int8))
          print (sizeof (undefined::Int16))


Inheritance between interfaces

Inheritance between interfaces (in "class" declaration) means inclusion of base class dictionaries in dictionary of subclass:

class (Show s, Monad m s) => Stream m s where
    sClose :: s -> m ()

means

type StreamDictionary m s = (ShowDictionary s, MonadDictionary m s, s->m())

There is upcasting mechanism, it just extracts dictionary of a base class from a dictionary tuple, so you can run function that requires base class from a function that requires subclass:

f :: (Stream m s) =>  s -> m String
show ::  (Show s) =>  s -> String
f s = return (show s)

But downcasting is absolutely impossible - there is no way to get subclass dictionary from a superclass one


Inheritance between instances

Inheritance between instances (in "instance" declaration) means that operations of some class can be executed via operations of other class, i.e. such declaration describe a way to compute dictionary of inherited class via functions from dictionary of base class:

class Eq a where
  (==) :: a -> a -> Bool
class Cmp a where
  cmp :: a -> a -> Ordering
instance (Cmp a) => Eq a where
  a==b  =  cmp a b == EQ

creates the following function:

cmpDict2EqDict :: CmpDictionary a -> EqDictionary a
cmpDict2EqDict (cmp) = (\a b -> cmp a b == EQ)

This results in that any function that receives dictionary for Cmp class can call functions that require dictionary of Eq class


Downcasting is a mission impossible

Selection between instances are done at compile-time, based only on information present at this moment. So don't expect that more concrete instance will be selected just because you passed this concrete datatype to the function which accepts some general class:

class Foo a where
  foo :: a -> String

instance (Num a) => Foo a where
  foo _ = "Num"

instance Foo Int where
  foo _ = "int"

f :: (Num a) =>  a -> String
f = foo

main = do print (foo (1::Int))
          print (f (1::Int))

Here, the first call will return "int", but second - only "Num". this can be easily justified by using dictionary-based translation as described above. After you've passed data to polymorphic procedure it's type is completely lost, there is only dictionary information, so instance for Int can't be applied. The only way to construct Foo dictionary is by calculating it from Num dictionary using the first instance.


There is only one dictionary per function call

For "eqList :: (Eq a) => [a] -> [a] -> Bool" types of all elements in list must be the same, and types of both arguments must be the same too - there is only one dictionary and it know how to handle variables of only one concrete type!

Existential variables is more like OOP objects

Existential variables pack dictionary together with variable (looks very like the object concept!) so it's possible to create polymorphic containers (i.e. holding variables of different types). But downcasting is still impossible. Also, existentials still don't allow to mix variables of different types in a call to some polymorhic operation (their personal dictionaries still built for variables of one concrete type):

data HasCmp = forall a. Cmp a => HasCmp a

sorted :: [HasCmp] -> Ordering

sorted []  = True
sorted [_] = True
sorted (HasCmp a : HasCmp b : xs)  =  a<=b && sorted (b:xs)

This code will not work - a<=b can use nor 'a' nor 'b' dictionary. Even if orderings for apples and penguins are defined, we still don't have a method to compare penguin with apple!


Type class system extensions

  • Constructor classes (Haskell98)
  • MPTC: multi-parameter type classes (Hugs/GHC extension)
  • FD & AT: functional dependencies and associated types (FD is a Hugs/GHC extension, AT implemented only in GHC 6.6)


Literature

The paper that at first time introduced type classes and their implementation using dictionaries was "How to make ad-hoc polymorphism less ad-hoc" ( http://homepages.inf.ed.ac.uk/wadler/papers/class/class.ps.gz )

I thanks Ralf Lammel and Klaus Ostermann for their paper "Software Extension and Integration with Type Classes" ( http://homepages.cwi.nl/~ralf/gpce06/ ) which prompts me to start thinking about differences between OOP and type classes instead of their similarities

The Lennart Augustsson paper "Implementing Haskell overloading" shows the alternative ways to implement type classes and possible optimizations ( http://www.cs.chalmers.se/pub/cs-reports/papers/overload-fpca-93.ps.Z)