Difference between revisions of "OOP vs type classes"

From HaskellWiki
Jump to navigation Jump to search
 
(formatting)
Line 1: Line 1:
(this is just a paper sketch now. feel free to edit/comment it. i will include information you provided into the final version of this article)
+
(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'm almost not used type classes in my application programs, but when
i'm gone to implement general-purpose libraries and tried to maintain
+
I'd gone to implement general-purpose libraries and tried to maintain
 
as much flexibility as possible, it was natural to start build large
 
as much flexibility as possible, it was natural to start build large
and complex class hierarchies. i tried to use my C++ experience when
+
and complex class hierarchies. I tried to use my C++ experience when
doing this but i was many times bitten by the type classes
+
doing this but I was many times bitten by the type classes
restrictions. now i think that i have better feeling and mind model
+
restrictions. Now i think that i have better feeling and mind model
 
for type classes and want to share it with other Haskellers,
 
for type classes and want to share it with other Haskellers,
especially ones having OOP backgrounds
+
especially ones having OOP backgrounds.
   
   
at this moment C++/C#/Java languages has classes and
+
== Type classes is a sort of templates, not classes ==
  +
templates/generics. what is a difference? with a class, type
 
  +
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
 
information carried with object itself while with templates it's
outside of object and is part of the whole operation
+
outside of object and is part of the whole operation.
   
for example, if == operation is defined in a class, the actual
+
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
 
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
 
is defined in template, actual procedure depends only on template
instantiated (and determined at compile time)
+
instantiated (and determined at compile time).
   
Haskell's objects don't carry run-time type information. instead,
+
Haskell's objects don't carry run-time type information. Instead,
 
class constraint for polymorphic operation passed in form of
 
class constraint for polymorphic operation passed in form of
 
"dictionary" implementing all operations of the class (there are also
 
"dictionary" implementing all operations of the class (there are also
 
other implementation techniques, but this don't matter). For example,
 
other implementation techniques, but this don't matter). For example,
   
  +
<haskell>
 
eqList :: (Eq a) => [a] -> [a] -> Bool
 
eqList :: (Eq a) => [a] -> [a] -> Bool
  +
</haskell>
   
 
translated into:
 
translated into:
   
  +
<haskell>
 
type EqDictionary a = (a->a->Bool, a->a->Bool)
 
type EqDictionary a = (a->a->Bool, a->a->Bool)
 
eqList :: EqDictionary a -> [a] -> [a] -> Bool
 
eqList :: EqDictionary a -> [a] -> [a] -> Bool
  +
</haskell>
   
 
where first parameter is "dictionary" containing implementation of
 
where first parameter is "dictionary" containing implementation of
Line 41: Line 47:
 
of base classes dictionaries:
 
of base classes dictionaries:
   
  +
<haskell>
 
class Eq a => Cmp a where
 
class Eq a => Cmp a where
 
cmp :: a -> a -> Comparision
 
cmp :: a -> a -> Comparision
   
 
cmpList :: (Cmp a) => [a] -> [a] -> Comparision
 
cmpList :: (Cmp a) => [a] -> [a] -> Comparision
  +
</haskell>
   
 
turns into:
 
turns into:
   
  +
<haskell>
 
type CmpDictionary a = (eqDictionary a, a -> a -> Comparision)
 
type CmpDictionary a = (eqDictionary a, a -> a -> Comparision)
 
cmpList :: CmpDictionary a -> [a] -> [a] -> Bool
 
cmpList :: CmpDictionary a -> [a] -> [a] -> Bool
  +
</haskell>
   
   
Line 69: Line 79:
   
   
  +
== Type classes vs classes ==
   
  +
Here is a brief listing of differences between OOP classes and Haskell type classes
   
 
1. Of course, there is no data fields inheritance and data fields itself
1. type can appear at any place in function signature: be any
 
 
(so type classes more like to interfaces than to classes itself)
  +
 
2. 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
   
  +
<haskell>
 
class C a where
 
class C a where
 
f :: a -> Int
 
f :: a -> Int
Line 81: Line 97:
 
j :: Int -> a
 
j :: Int -> a
 
new :: a
 
new :: a
  +
</haskell>
   
 
it's even possible to define instance-specific constants (look at 'new').
 
it's even possible to define instance-specific constants (look at 'new').
Line 88: Line 105:
 
parameter:
 
parameter:
   
  +
<haskell>
 
class FixedSize a where
 
class FixedSize a where
 
sizeof :: a -> Int
 
sizeof :: a -> Int
Line 97: Line 115:
 
main = do print (sizeof (undefined::Int8))
 
main = do print (sizeof (undefined::Int8))
 
print (sizeof (undefined::Int16))
 
print (sizeof (undefined::Int16))
  +
</haskell>
 
  +
   
2. of course, there is no data fields inheritance and data fields itself
 
(so type classes more like to interfaces than to classes itself)
 
   
 
3. Inheritance between interfaces (in "class" declaration) means
 
3. 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:
   
  +
<haskell>
 
class (Show s, Monad m s) => Stream m s where
 
class (Show s, Monad m s) => Stream m s where
 
sClose :: s -> m ()
 
sClose :: s -> m ()
  +
</haskell>
   
 
means
 
means
   
  +
<haskell>
 
type StreamDictionary m s = (ShowDictionary s, MonadDictionary m s, s->m())
 
type StreamDictionary m s = (ShowDictionary s, MonadDictionary m s, s->m())
  +
</haskell>
   
 
There is upcasting mechanism, it just extracts dictionary of a base
 
There is upcasting mechanism, it just extracts dictionary of a base
Line 116: Line 137:
 
base class from a function that requires subclass:
 
base class from a function that requires subclass:
   
  +
<haskell>
 
f :: (Stream m s) => s -> m String
 
f :: (Stream m s) => s -> m String
 
show :: (Show s) => s -> String
 
show :: (Show s) => s -> String
 
f s = return (show s)
 
f s = return (show s)
  +
</haskell>
   
 
But downcasting is absolutely impossible - there is no way to get
 
But downcasting is absolutely impossible - there is no way to get
Line 127: Line 150:
 
4. Inheritance between instances (in "instance" declaration) means
 
4. 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
 
inherited class via functions from dictionary of base class:
 
inherited class via functions from dictionary of base class:
   
  +
<haskell>
 
class Eq a where
 
class Eq a where
 
(==) :: a -> a -> Bool
 
(==) :: a -> a -> Bool
Line 136: Line 160:
 
instance (Cmp a) => Eq a where
 
instance (Cmp a) => Eq a where
 
a==b = cmp a b == EQ
 
a==b = cmp a b == EQ
  +
</haskell>
   
 
creates the following function:
 
creates the following function:
   
  +
<haskell>
 
cmpDict2EqDict :: CmpDictionary a -> EqDictionary a
 
cmpDict2EqDict :: CmpDictionary a -> EqDictionary a
 
cmpDict2EqDict (cmp) = (\a b -> cmp a b == EQ)
 
cmpDict2EqDict (cmp) = (\a b -> cmp a b == EQ)
  +
</haskell>
   
 
This results in that any function that receives dictionary for Cmp class
 
This results in that any function that receives dictionary for Cmp class
Line 147: Line 174:
   
   
5. selection between instances are done at compile-time, based only on
+
5. Selection between instances are done at compile-time, based only on
information present at this moment. so don't wait 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
 
datatype to the function which accepts some general class:
 
datatype to the function which accepts some general class:
   
  +
<haskell>
 
class Foo a where
 
class Foo a where
 
foo :: a -> String
 
foo :: a -> String
Line 160: Line 188:
 
instance Foo Int where
 
instance Foo Int where
 
foo _ = "int"
 
foo _ = "int"
 
   
 
f :: (Num a) => a -> String
 
f :: (Num a) => a -> String
Line 167: Line 194:
 
main = do print (foo (1::Int))
 
main = do print (foo (1::Int))
 
print (f (1::Int))
 
print (f (1::Int))
  +
</haskell>
   
 
Here, the first call will return "int", but second - only "Num".
 
Here, the first call will return "int", but second - only "Num".
Line 178: Line 206:
   
   
6. for "eqList :: (Eq a) => [a] -> [a] -> Bool" types of all elements
+
6. 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!
   
7. existential variables pack dictionary together with variable (looks
+
7. 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
downcasting is still impossible. also, existentials still don't allow
+
downcasting is still impossible. Also, existentials still don't allow
 
to mix variables of different types (their personal dictionaries still
 
to mix variables of different types (their personal dictionaries still
 
built for variables of one concrete type)
 
built for variables of one concrete type)
Line 196: Line 224:
 
using dictionaries was "How to make ad-hoc polymorphism less ad-hoc"
 
using dictionaries was "How to make ad-hoc polymorphism less ad-hoc"
 
(http://homepages.inf.ed.ac.uk/wadler/papers/class/class.ps.gz)
 
(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

Revision as of 06:59, 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 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 -> Comparision

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

turns into:

type CmpDictionary a = (eqDictionary a, a -> a -> Comparision)
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

1. Of course, there is no data fields inheritance and data fields itself (so type classes more like to interfaces than to classes itself)

2. 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))


3. 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


4. 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 -> Comparision
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


5. 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.


6. 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!

7. 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 (their personal dictionaries still built for variables of one concrete type)


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