[Haskell-cafe] programming style...and type classes...

Olaf Klinke olf at aatal-apotheke.de
Thu Nov 3 20:08:45 UTC 2016


Mark,

Haskell typeclasses are a wonderful thing to have. I dare say that typeclasses are what makes haskell code modular and re-usable, because you can develop an algorithm "aginst the class interface" and users only need to supply a class instance for their own data type in order to use your algorithm. What the wiki warns about is misuse or over-use of typeclasses. Typeclasses express properties that different types have in common, and in that respect they are somewhat similar to OO-classes. However, there is no hierarchy of inheritance. 
It is true that typeclasses, particularly the more advanced ones with e.g. multiple parameters or functional dependencies, sometimes get into your way. One example is ambiguity arising from multi-parameter type classes: Suppose you have a two-parameter class

{-# LANGUAGE MultiParamTypeClasses,FunctionalDependencies #-}
class Foo a b where
  foo :: a -> b
  bar :: b -> (a,[Int])

Now you write a function using only bar: 

f :: (Foo a b) => b -> Int
f = length.snd.bar

The compiler will complain that it does not know which Foo instance to use, because while bar itself mentions both class parameters a and b, snd.bar has type b -> [Int] and hence lost the information about the first class parameter. Adding a functional dependency b -> a helps in this case. But the promise that for every b there is only one a such that Foo a b holds may not be what you want. So what went wrong? Observe that

bar :: b -> (a,[Int])

is equivalent to two functions

bar1 :: b -> a
bar2 :: b -> [Int]

and bar2 probably did not belong into the class Foo. We've been cramming to much into one typeclass and should therefore split Foo into two classes. 

Olaf


More information about the Haskell-Cafe mailing list