
Hello haskell, 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? 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. -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin

Hello Gabriel, Tuesday, August 15, 2006, 10:36:28 PM, you wrote:
| 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.
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.
i can't agree. the differences between TC inheritance/polymorphism and C++ classes are substantial. i listed them in next part of tutorial which you should see alongside this message. you can also see paper at http://homepages.cwi.nl/~ralf/gpce06/ which is all about consequences of differences between classes and type classes for software development -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin

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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- John Meacham - ⑆repetae.net⑆john⑈

On 8/18/06, John Meacham
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.
C++ programmers deal with this using a number of techniques, mostly involving templates. Actually, there is one technique using C++ templates that I really want to see going mainstream in the Haskell implementations. Existential types are already there, now I want to see associated types (trait types in C++). Maybe I've been doing too much C++ programming in the last few years, but a lot of the times when I end up using multiparameter type classes, what I really want is an associated type. For example class Monad s => Store s where type Key insert :: Binary -> s Key retrStore :: Key -> s Binary ... so that part of the instance is a choice of the key type. For those who are interested, I'm sure the relevant papers are readily available on citeseer/Google. :-) Tom

Hello Thomas, Friday, August 18, 2006, 7:57:13 AM, you wrote:
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.
C++ programmers deal with this using a number of techniques, mostly involving templates.
Haskell type classes are closer to templates/generics than to classes itself
Actually, there is one technique using C++ templates that I really want to see going mainstream in the Haskell implementations. Existential types are already there, now I want to see associated types (trait types in C++). Maybe I've been doing too much C++ programming in the last few years, but a lot of the times when I end up using multiparameter type classes, what I really want is an associated type.
i also wrote a lot of such code for Streams library and can say that MPTC+FD are close enough to emulate AT, although need slightly more verbose definitions. moreover, AT are already implemented in GHC 6.5, afai seen in ghc-cvs reports
For those who are interested, I'm sure the relevant papers are readily available on citeseer/Google. :-)
http://haskell.org/haskellwiki/Research_papers/Type_systems#Associated_types -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin

Hello John, Friday, August 18, 2006, 5:16:45 AM, you wrote:
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.
your letter is damn close to that i wrote in http://haskell.org/haskellwiki/OOP_vs_type_classes although i mentioned not only pluses but also drawbacks of type classes: lack of record extension mechanisms (such at that implemented in O'Haskell) and therefore inability to reuse operation implementation in an derived data type, lack of downcasting mechanism (which bites me all the way), requirement to rebuild dictionaries in polymorphic operations what is slow enough i will put your letter there and later use it to build up the final description, ok? -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
http://haskell.org/haskellwiki/OOP_vs_type_classes although i mentioned not only pluses but also drawbacks of type classes: lack of record extension mechanisms (such at that implemented in O'Haskell) and therefore inability to reuse operation implementation in an derived data type...
Hi Bulat - You can reuse ops in a derived data type but it involves a tremendous amount of boilerplate. Essentially, you just use the type classes to simulate extendable records by having a method in each class that accesses the fixed-length record corresponding to that particular C++ class. Here is an example (apologies for the length!) which shows a super class function being overridden in a derived class and a derived class method (B::Extra) making use of something implemented in the super class: module Main where {- Haskell translation of the following C++ class A { public: String s; Int i; A(String s, Int i) s(s), i(i){} virtual void Display(){ printf("A %s %d\n", s.c_str(), i); } virtual Int Reuse(){ return i * 100; } }; class B: public A{ public: Char c; B(String s, Int i, Char c) : A(s, i), c(c){} virtual void Display(){ printf("B %s %d %c", s.c_str(), i, c); } virtual void Extra(){ printf("B Extra %d\n", Reuse()); } }; -} data A = A { _A_s :: String , _A_i :: Int } -- This could do arg checking etc constructA :: String -> Int -> A constructA = A class ClassA a where getA :: a -> A display :: a -> IO () display a = do let A{_A_s = s, _A_i = i} = getA a putStrLn $ "A " ++ s ++ show i reuse :: a -> Int reuse a = _A_i (getA a) * 100 data WrapA = forall a. ClassA a => WrapA a instance ClassA WrapA where getA (WrapA a) = getA a display (WrapA a) = display a reuse (WrapA a) = reuse a instance ClassA A where getA = id data B = B { _B_A :: A, _B_c :: Char } constructB :: String -> Int -> Char -> B constructB s i c = B {_B_A = constructA s i, _B_c = c} class ClassA b => ClassB b where getB :: b -> B extra :: b -> IO () extra b = do putStrLn $ "B Extra " ++ show (reuse b) data WrapB = forall b. ClassB b => WrapB b instance ClassB WrapB where getB (WrapB b) = getB b extra (WrapB b) = extra b instance ClassA WrapB where getA (WrapB b) = getA b display (WrapB b) = display b reuse (WrapB b) = reuse b instance ClassB B where getB = id instance ClassA B where getA = _B_A -- override the base class version display b = putStrLn $ "B " ++ _A_s (getA b) ++ show (_A_i (getA b)) ++ [_B_c (getB b)] main :: IO () main = do let a = constructA "a" 0 b = constructB "b" 1 '*' col = [WrapA a, WrapA b] mapM_ display col putStrLn "" mapM_ (putStrLn . show . reuse) col putStrLn "" extra b {- Output:
ghc -fglasgow-exts --make Main main A a0 B b1*
0 100 B Extra 100
-} (If the "caseless underscore" Haskell' ticket is accepted the leading underscores would have to be replaced by something like "_f" ie _A_s ---> _fA_s etc) Regards, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com

Hello Brian, Friday, August 18, 2006, 8:54:08 PM, you wrote:
http://haskell.org/haskellwiki/OOP_vs_type_classes although i mentioned not only pluses but also drawbacks of type classes: lack of record extension mechanisms (such at that implemented in O'Haskell) and therefore inability to reuse operation implementation in an derived data type...
You can reuse ops in a derived data type but it involves a tremendous amount of boilerplate.
of course, but it's just OOP emulation. one can do the same in C, for example. i've added your letter to the page. but anyway, one of key OOP ideas was extensible records, it was idea what distinguished OOP from abstract data types approach -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hello Brian, Friday, August 18, 2006, 8:54:08 PM, you wrote:
classes: lack of record extension mechanisms (such at that implemented in O'Haskell) and therefore inability to reuse operation implementation in an derived data type...
You can reuse ops in a derived data type but it involves a tremendous amount of boilerplate. Essentially, you just use the type classes to simulate extendable records by having a method in each class that accesses the fixed-length record corresponding to that particular C++ class.
btw, i just found the following in HWN: * HList updates . Oleg Kiselyov [17]announced that HList, the library for strongly typed heterogeneous lists, records, type-indexed products (TIP) and co-products is now accessible via darcs, [18]here. Additionally, Oleg pointed to some new features for HList, including a new representation for open records. Finally, he [19]published a note on how HList supports, natively, polymorphic variants: extensible recursive open sum datatypes, quite similar to Polymorphic variants of OCaml. HList thus solves the `expression problem' -- the ability to add new variants to a datatype without changing the existing code. 17. http://article.gmane.org/gmane.comp.lang.haskell.general/13905 18. http://darcs.haskell.org/HList/ 19. http://article.gmane.org/gmane.comp.lang.haskell.general/13906 -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin

John Meacham

Hello Gabriel, Sunday, August 20, 2006, 8:26:30 AM, you wrote:
| 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.
The dictionary can be attached to the operations (not just to the values) by using objects local to functions (which sort of matierialize the dictionary).
This means that type classes can be _emulated_ in C++. but the bare semantics is just as we said - in Haskell dictionaries are passed around the functions (unless existential used) and in C++ they are attached to objects i agree that emulation you provided is closer to type classes at least in that it implements _dynamic_ dispatching vs compile-time dispatching of templates. but typical C++ programming involves using classes and templates, not the unusual technique you have introduced. please note that one can also use some other technique (say, function pointers or switch statements) to emulate type classes behavior and this don't means that switch statements in C is a kind of type classes :) my comparison was targeted to teaching Haskell newbies (especially former OOP programmers) how to use type classes, give them a _intuition_ of this language feature and directions about its usage. C++ templates with their type inference and dispatch based on the type of entire operation is a best approximation in OOP world i know but (of course) i will add your letter as one more description of that type classes are, at this time - in terms of emulation them in C++ (in addition to emulation them in Haskell, written by Wadler and Blott) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin

I was mainly specifically comparing haskell to standard OOP classes, Most OOP languages certainly have some set of other features in addition, such as forms of ad hoc polymorphism or the template meta-language of C++, or the code reuse primitives in sather, however I was mainly interested in exploring base OOP and its relation to haskell typeclasses. As it seems to come up a lot. C++ templates are a whole nother ball of wax. John -- John Meacham - ⑆repetae.net⑆john⑈

John Meacham

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@gmail.com
participants (5)
-
Brian Hulley
-
Bulat Ziganshin
-
Gabriel Dos Reis
-
John Meacham
-
Thomas Conway