[Haskell-cafe] I hate Haskell's typeclasses

Ryan Ingram ryani.spam at gmail.com
Sat Apr 19 00:29:14 EDT 2008


WARNING: RANT AHEAD.  Hopefully this fires off some productive
discussion on how to fix these problems!

Don't get me wrong:  I think the idea of typeclasses is great.  Their
implementation in Haskell comes so close to being awesome and then
falls short, and that's almost worse than not being awesome in the
first place!

Some examples of things I think you should be able to do, that just Do
Not Work.  Examples like these are trivial in many other languages,
and they shouldn't be that hard here, either!

1) You can't make sensible default implementations.  For example, it'd
be nice to make all my Monads be Applicatives and Functors without
resorting to Template Haskell or infinite boilerplate.  Why can't I
just write this?

instance Monad m => Applicative m where
    pure = return
    (<*>) = ap

Sure, I get that there might be ambiguity of which instance to choose.
 But why not warn me about that ambiguity, or let me choose somehow on
a case-by-case basis when it happens?

2) You can't add sensible superclasses.  I was playing with QuickCheck
and wanted to write "equal with regards to testing".  So I wrote up a
class for it:

class TestableEq a where
    (~=) :: a -> a -> Property

instance Eq a => TestableEq a where
    -- should be a superclass of Eq instead!
    a ~= b = a == b

instance (Arbitrary a, TestableEq b) => TestableEq (a -> b) where
    f ~= g = forAll arbitrary (\a -> f a ~= g a)

But this doesn't work without overlapping & undecidable instances!

Sure, there is an alternative: I could manually declare instances of
TestableEq for EVERY SINGLE TYPE that is an instance of Eq.  I am sure
nobody here would actually suggest that I do so.

And sure, these extensions are both safe here, because the intent is
that you won't declare instances of TestableEq for things that are
already instances of Eq, and you won't do something stupid like
"instance TestableEq a => Eq a".

But why do I need to jump through these hoops for a perfectly safe &
commonly desired operation?

3) There's no reflection or ability to choose an implementation based
on other constraints.

In QuickCheck, (a -> b) is an instance of Arbitrary for appropriate a,
b.  But you can't use this instance in forAll or for testing functions
without being an instance of Show.  Now, this is probably a design
mistake, but it's the right choice with the current typeclass system
(see (2)).  But it'd be a million times better to have something like
the following:

class Arbitrary a => MkArbitrary a where
   mkArbitrary :: Gen (a, String)

case instance MkArbitrary a where
   Show a =>
       mkArbitrary = do
           x <- arbitrary
           return (x, show x)
   otherwise =>
       mkArbitrary = do
           st <- getGenState
           x <- arbitrary
           return (x, "evalGen arbitrary " ++ show st)

With this, QuickCheck could print reproducible test cases painlessly
without adding the requirement that everything is an instance of Show!

Now, you could say that mkArbitrary should be a member function of
Arbitrary, but then you clutter up your instance definitions with tons
of "mkArbitrary = defaultMkArbitrary" for types that have a Show
instance.

4) Every concrete type should be an instance of Typeable without
having to do anything, and Typeable should give you typecase &
reflection:

genericShow :: Typeable a => a -> String
genericShow x = typecase x of
    String -> x
    (Show t => t) -> show x -- any instance of Show
    _ -> "<unknown>"

  -- ryan

P.S. I'd actually love to work on any or all of these problems, but I
can't get GHC to compile!  See http://hpaste.org/5878


More information about the Haskell-Cafe mailing list