On 18 Apr 2008, at 9:29 PM, Ryan Ingram wrote:
WARNING: RANT AHEAD.

WARNING: RESPONSE IN THE SPIRIT OF THE ORIGINAL AHEAD.

  Hopefully this fires off some productive
discussion on how to fix these problems!

{-# GHC_OPTIONS -foverlapping-instances -fundecidable-instances #-} :)

What you want to work is precisely what this allows.

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!

We've noticed. The literature on extending Haskell type classes is, um, enormous.


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,

I call.  Name a language that is

a) Completely statically typed (no type errors at runtime),
b) Has an ad-hoc overloading mechanism powerful enough to encode Num and Monad, and
c) Is substantially better than Haskell + extensions for your examples.

The examples aren't all that long; comparison code snippets shouldn't be all that long either.

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?

You can already choose on a case-by-case basis. In this specific case, you can only think of one super-instance, but I can think of another:

instance Arrow a => Applicative (a alpha) where
  pure = arr . const
  a <*> b = (a &&& b) >>> arr ($)

I think Conal Elliot's recent work of FRP can be extended to show that Fudgets-style stream processors can be made instances of Applicative by both these methods, with different instances. So as soon as both are present, you have to choose the instance you want every time. Having something like this spring up and bite you because of a change in some library you pulled off of Haddock does not make for maintainable code.

More generally, specifying what you want is really not hard. Do you really have gazillions of monads in your code you have to repeat this implementation for?

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

Again, this is one (*) line per type.  How many types do you declare?

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.

Bzzzt.  Wrong.  Thanks for playing!

And sure, these extensions are both safe here, because the intent

What?  By that reasoning, perl is `safe'.  Haskell is not perl.

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?

It's called a proof obligation. Haskell is not here to stop you from jumping through hoops. In fact, it is here precisely to force you to jump through hoops. That's why it's called a bondage and discipline language.

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)

So we compile in a table of every instance and every datatype, add a Typeable constraint to forAll (since parametricity just got shot to heck), and scan through that table on every test. Millions of times better. And slower. And more likely to develop odd changes and hard- to-debug errors.

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

QuickCheck makes testing so easy, I think the Arbitrary (a -> b) instance is almost unnecessary; (btw., functions /are/ instances of Show). You can easily write a showable ADT encoding the functions you want to test.

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.

Thousands and thousands of pounds! You have too many types. Look for ways to re-factor, and move your duplication into functors.

4) Every concrete type should be an instance of Typeable without
having to do anything,

Sure. And seq should go back to being a class method. (See earlier about parametricity being shot to heck). I have an excellent design which will preserve the language's semantics (which are fine the way they are, thank you), while being convenient for programmers, which this margin is too small to contain.[1]

and Typeable should give you typecase &

Type case is easy:

  genericShow :: Typeable a => a -> String
  genericShow x = fromJust $ do
                                s <- cast x :: Maybe String
                                return s
                     `mplus` do
                                n <- cast x :: Maybe Int
                                return (show n)
                     `mplus` do
                                return "<unknown>"

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

Reflection is harder, because of the need for the lookup table with every instance of every class I mentioned earlier. (And you get to figure out how to encode polymorphic instances, too! Good luck[2]).

jcc

[1, 2] These are the non-sarcastic bits.
_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to