[Haskell-cafe] OOP vs type classes Re: type gurus, can you please help?

Bulat Ziganshin bulat.ziganshin at gmail.com
Wed Aug 16 02:55:42 EDT 2006


Hello Bulat,

Monday, August 14, 2006, 10:37:37 AM, you wrote:

> i'm started to write article about type classes. can you, type gurus,
> please check this initial text for correctness in explaining
> differences between classes and type classes?

i continue to develop this text. below is list of differences i
recalled, or may be a list of TC features. please critique it, add new
list entries (it's especially important), add/correct examples and
explanations. it's just a sketch now. i also put it to the
http://haskell.org/haskellwiki/Haskell_inside/OOP_vs_type_classes
after all critique will be accepted, i will try to turn this into
one more mini-tutorial



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)


-- 
Best regards,
 Bulat                            mailto:Bulat.Ziganshin at gmail.com



More information about the Haskell-Cafe mailing list