I hate Haskell's typeclasses

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

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.

Independently of the rant...
On Sat, Apr 19, 2008 at 6:01 AM, Jonathan Cast
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.
Surely it's there to lovingly assist you through the hoops? You can't just force people not to do the wrong thing and expect to get a good statically typed language out of it - you have to make it easier for them to do the right thing.

David MacIver wrote:
Independently of the rant...
On Sat, Apr 19, 2008 at 6:01 AM, Jonathan Cast
wrote: 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.
Surely it's there to lovingly assist you through the hoops?
From what I've read, B&D relationships can be quite loving, despite appearances. And Haskell has safewords you can use if the pain gets too intense, like unsafePerformIO. Just be sure to get the capitalization right, or Mistress Haskell will punish you again with a "not in scope" message. At which point it's customary to fix the error, and reinvoke the compiler while saying "Thank you ma'am, may I have another?"

On 19 Apr 2008, at 5:02 AM, David MacIver wrote:
Independently of the rant...
On Sat, Apr 19, 2008 at 6:01 AM, Jonathan Cast
wrote: 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.
Surely it's there to lovingly assist you through the hoops? You can't just force people not to do the wrong thing and expect to get a good statically typed language out of it - you have to make it easier for them to do the right thing.
I think going through the hoop is paramount in Haskell. That's why Haskell is pure, for example, even though it (still) requires awkward code on occasion. Haskell is certainly designed to make getting through the hoops as easy as possible, but never by providing a general way around them. (unsafePerformIO notwithstanding). jcc

On Sun, Apr 20, 2008 at 4:46 AM, Jonathan Cast
On 19 Apr 2008, at 5:02 AM, David MacIver wrote:
Independently of the rant...
On Sat, Apr 19, 2008 at 6:01 AM, Jonathan Cast
wrote: 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.
Surely it's there to lovingly assist you through the hoops? You can't just force people not to do the wrong thing and expect to get a good statically typed language out of it - you have to make it easier for them to do the right thing.
I think going through the hoop is paramount in Haskell. That's why Haskell is pure, for example, even though it (still) requires awkward code on occasion. Haskell is certainly designed to make getting through the hoops as easy as possible, but never by providing a general way around them. (unsafePerformIO notwithstanding).
Sure. I'm just saying, it's more of a "Jump through this hoop and you shall have moist, delicious cake. And by the way, here's a leg up" set up. There are rewards for the hoop jumping, and assistance on the way there (which is more than can be said for a lot of languages which make you jump through hoops) :-) I think I might be stretching the analogy slightly.

On 20 Apr 2008, at 3:05 AM, David MacIver wrote:
On Sun, Apr 20, 2008 at 4:46 AM, Jonathan Cast
wrote: On 19 Apr 2008, at 5:02 AM, David MacIver wrote:
Independently of the rant...
On Sat, Apr 19, 2008 at 6:01 AM, Jonathan Cast
wrote: 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.
Surely it's there to lovingly assist you through the hoops? You can't just force people not to do the wrong thing and expect to get a good statically typed language out of it - you have to make it easier for them to do the right thing.
I think going through the hoop is paramount in Haskell. That's why Haskell is pure, for example, even though it (still) requires awkward code on occasion. Haskell is certainly designed to make getting through the hoops as easy as possible, but never by providing a general way around them. (unsafePerformIO notwithstanding).
Sure. I'm just saying, it's more of a "Jump through this hoop and you shall have moist, delicious cake. And by the way, here's a leg up" set up. There are rewards for the hoop jumping, and assistance on the way there (which is more than can be said for a lot of languages which make you jump through hoops) :-)
Absolutely. But I think the original rant strayed into the realm of wanting the cake and the leg up /without/ the hoop.
I think I might be stretching the analogy slightly.
There is nothing the least bit wrong with that. jcc

David MacIver wrote:
Sure. I'm just saying, it's more of a "Jump through this hoop and you shall have moist, delicious cake. And by the way, here's a leg up" set up. There are rewards for the hoop jumping, and assistance on the way there (which is more than can be said for a lot of languages which make you jump through hoops) :-)
I think I might be stretching the analogy slightly.
THE CAKE IS A LIE!! (Sorry, couldn't resist... I'll try not to do that again.)

On Fri, Apr 18, 2008 at 10:01 PM, Jonathan Cast
{-# GHC_OPTIONS -foverlapping-instances -fundecidable-instances #-} :) What you want to work is precisely what this allows.
Of course, I bring that point up. And overlapping instances has the problem that it doesn't really do what you want; you always eventually end up with this problem: oops :: Eq a => a -> a -> Property oops x y = x ~= y Overlapping instances for EqTestable a arising from a use of `~=' Matching instances: instance [overlap ok] (Eq a) => EqTestable a instance [overlap ok] (Show a, Arbitrary a, EqTestable b) => EqTestable (a -> b) (The choice depends on the instantiation of `a' To pick the first instance above, use -fallow-incoherent-instances when compiling the other instance declarations) In the expression: x ~= y In the definition of `oops': oops x y = x ~= y
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.
No fair! I'm on haskell-cafe for a reason: every language sucks, Haskell just sucks less :) But I can give a couple of thoughts that almost meet your criteria: 1) Ruby. Totally misses (a) but absolutely nails (b) and (c). 2) C++: Fine on (a) as long as you don't write stupid stuff. Template meta-programming involves pattern-matching on types and I believe is strong enough for (b). But it's really verbose; from an elegance point of view it probably misses (c). 3) Scala? I don't know enough about it to say for sure but what I have seen looks promising.
On 18 Apr 2008, at 9:29 PM, Ryan Ingram wrote:
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.
That's true, but if the authors of Applicative could, I am sure they would have chosen to make it (and Functor) a superclass of Monad with the proper default implementation; after all (1) Applicative is damn useful, and (2) it's the common case.
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?
Yes, actually. First, I like writing monads. See http://hackage.haskell.org/cgi-bin/hackage-scripts/package/MonadPrompt-1.0.0... And second, just today I had to write instance Applicative STM where pure = return (<*>) = ap It felt like it was driving home the point.
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?
I don't declare too many myself, except on days when I'm trying to embed system F in Haskell via GADTs, but I use a lot of them; and many of them the authors have conveniently already made instances of useful typeclasses. Then I try to add some new functionality and run into a lot of friction because now every library I use needs an implementation which matches. Have you ever tried to write a monad transformer that is compatible with the MTL? O(n^2) instances is not a fun place to be, especially when most of the definitions are just variations on "lift". Disclaimer: this is actually a hard problem; I don't expect the compiler to be able to solve it, but it's frustrating nonetheless. The things I bring up here are easy in comparison.
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!
Ha ha, you got me there :)
But why do I need to jump through these hoops for a perfectly safe & commonly desired operation?
It's called a proof obligation.
My argument is that there shouldn't even be a proof obligation here; the language is just not expressive enough to allow me to write the code that I want; something that is actually completely decidable & non-overlapping.
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.
It's had a lot of research; I want the best of all worlds. For a start: http://www.google.com/search?q=optimizing+dynamic+dispatch You could get close without going to full dynamic dispatch, though; consider the following "core": -- This part is all in haskell now data ShowDict a = ShowDict { show :: a -> String } show_String :: ShowDict String show_Int :: ShowDict Int show_List :: ShowDict a -> ShowDict [a] -- foo :: Show a => [a] -> String -- foo x = show x ++ "!" foo :: ShowDict a -> [a] -> String foo sd x = show (show_List sd) x ++ "!" -- This part isn't in haskell, and the syntax sucks, but the idea is there. type MaybeShow a = Maybe (ShowDict a) -- bar :: MaybeInstance Show a => [a] -> String -- bar xs -- | Show a = foo xs -- | otherwise = show (length xs) bar :: MaybeShow a -> [a] -> String bar (Just sd) xs = foo sd xs bar Nothing xs = show (show_Int) (length xs) With this I could write instance (MaybeInstance Show a, Arbitrary a) => MkArbitrary a where mkArbitrary xs | Show a = do x <- arbitrary return (x, show x) | otherwise = do st <- getGenState x <- arbitrary return (x, "evalGen arbitrary " ++ show st) Now, every concrete type would be an instance of MaybeInstance <classname>, and "dynamic" dispatch and (I think) closed typeclasses would be a free benefit.
And more likely to develop odd changes and hard-to-debug errors.
Or so you claim :)
QuickCheck makes testing so easy, I think the Arbitrary (a -> b) instance is almost unnecessary; (btw., functions /are/ instances of Show).
Now it's my turn to call: Prelude Test.QuickCheck> show ((\x -> x) :: Int -> Int) <interactive>:1:0: No instance for (Show (Int -> Int)) Although, I do see a useless instance in the standard prelude at http://www.haskell.org/haskell-report/standard-prelude.html I actually would love to have (unsafeShow :: a -> String) which made a "best effort" attempt (subject to the compiler's debugging level) to evaluate an object and tell you what it contains, including source code for functions if possible.
You can easily write a showable ADT encoding the functions you want to test.
That's fair (and actually pretty interesting). But definitely less elegant than -- assuming Arbitrary (Behavior Int) prop_fmap_at :: (Int -> Int) -> Property prop_fmap_at f = fmap f . at ~= at . fmap f (see Conal's recent FRP paper for the formulation of this property)
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]
At least we agree on something. But please don't keep your design to yourself, share!
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]).
See dynamic dispatch, above. Although polymorphic instances do seem tricky. But you could probably get away with treating each typeclass as a member of the "typerep" object for each type with some amount of lookup; doesn't one of the existing compilers implement typeclasses in this way already? -- ryan

On Apr 21, 2008, at 3:50 , Ryan Ingram wrote:
is almost unnecessary; (btw., functions /are/ instances of Show).
Now it's my turn to call:
Prelude Test.QuickCheck> show ((\x -> x) :: Int -> Int) <interactive>:1:0: No instance for (Show (Int -> Int))
import Data.Function. (but it is indeed a useless instance) A slightly less useless instance (more or less the one lambdabot uses) is at http://www.cmu.edu.edu/~allbery/FuncShow.hs; note that it only works for monomorphic functions (more specifically, for functions whose parameters are Typeable). -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Apr 21, 2008, at 14:21 , Brandon S. Allbery KF8NH wrote:
http://www.cmu.edu.edu/~allbery/FuncShow.hs; note that it only works for monomorphic functions (more
Note to self: be more careful when you just woke up. http:// www.ece.cmu.edu/~allbery/FuncShow.hs -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On 21 Apr 2008, at 12:50 AM, Ryan Ingram wrote:
On Fri, Apr 18, 2008 at 10:01 PM, Jonathan Cast
wrote: {-# GHC_OPTIONS -foverlapping-instances -fundecidable-instances #-} :) What you want to work is precisely what this allows.
Of course, I bring that point up. And overlapping instances has the problem that it doesn't really do what you want; you always eventually end up with this problem:
oops :: Eq a => a -> a -> Property oops x y = x ~= y
Overlapping instances for EqTestable a arising from a use of `~=' Matching instances: instance [overlap ok] (Eq a) => EqTestable a instance [overlap ok] (Show a, Arbitrary a, EqTestable b) => EqTestable (a -> b) (The choice depends on the instantiation of `a' To pick the first instance above, use -fallow-incoherent- instances when compiling the other instance declarations) In the expression: x ~= y In the definition of `oops': oops x y = x ~= y
OK, right. But I think what this shows is that sometimes you need to name and manipulate instances (instances are designed to be anonymous and transparent, which made sense when the alternative was thought to be the anonymous and transparent overloading of traditional languages, but has started to slip as time goes on). I think the traditional solution here is newtype; I think that using type signatures to try to choose an instance, in cases like this, is an abuse of the original insight behind type classes.
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.
No fair! I'm on haskell-cafe for a reason: every language sucks, Haskell just sucks less :)
Amen to that.
But I can give a couple of thoughts that almost meet your criteria: 1) Ruby. Totally misses (a) but absolutely nails (b) and (c).
I must have failed to communicate well. To me, the point of giving a class a name is that then you can write a program that is parametric over the elements of that class. Knowing that I can implement monads in Ruby doesn't impress me nearly as much as knowing that I can implement mapM does. Haskell has me addicted to code reuse (mapM) the way the rest of the programming world is addicted to design patterns (monads). What I mean by `encoding Num and Monad' is that you can do something like this: sum = foldr (+) 0 sequence = foldr (liftM2 (:)) (return []) I don't know of any language that is dynamically typed and also can encode `return' or `0' in a way that lets those examples work. Statically typed languages where it works are rare, even. Haskell gives up a fair amount of control by making these things implicit, which is what I think you're running up against --- but I think it gets something useful and non-trivial to acheive in return.
2) C++: Fine on (a) as long as you don't write stupid stuff.
C++ would be a decent successor to C if it had HM typing and GC and
dropped the whole silly OO business. Sum in C++ (I forget how to do
higher-order templates):
template
Template meta-programming involves pattern-matching on types and I believe is strong enough for (b). But it's really verbose; from an elegance point of view it probably misses (c).
3) Scala? I don't know enough about it to say for sure but what I have seen looks promising.
Scala indeed looks promising. I was secretly hoping you'd know something I didn't. But I'm still not sure it knows how to encode mapM.
On 18 Apr 2008, at 9:29 PM, Ryan Ingram wrote:
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.
That's true, but if the authors of Applicative could, I am sure they would have chosen to make it (and Functor) a superclass of Monad with the proper default implementation; after all (1) Applicative is damn useful, and (2) it's the common case.
Sure. And sometimes they'd get complaints (or engender flamewars) when the default instance wasn't what someone wanted.
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?
Yes, actually. First, I like writing monads. See http://hackage.haskell.org/cgi-bin/hackage-scripts/package/ MonadPrompt-1.0.0.1
And second, just today I had to write instance Applicative STM where pure = return (<*>) = ap
It felt like it was driving home the point.
I'll agree with this point. I've complained, concretely, about the lack of instances for (some) standard types before. (STM is actually a rather bad offender here; it's lacking MonadPlus, as well, despite the specific observation in the paper that it has the right signature for that class.)
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?
I don't declare too many myself, except on days when I'm trying to embed system F in Haskell via GADTs, but I use a lot of them; and many of them the authors have conveniently already made instances of useful typeclasses. Then I try to add some new functionality and run into a lot of friction because now every library I use needs an implementation which matches.
Have you ever tried to write a monad transformer that is compatible with the MTL? O(n^2) instances is not a fun place to be, especially when most of the definitions are just variations on "lift".
Not yet. For which I am grateful. But I think this is more a problem with monad transformers than with type classes; monad transformers just do not seem to have solid mathematical underpinnings.
Disclaimer: this is actually a hard problem; I don't expect the compiler to be able to solve it, but it's frustrating nonetheless. The things I bring up here are easy in comparison.
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!
Ha ha, you got me there :)
But why do I need to jump through these hoops for a perfectly safe & commonly desired operation?
It's called a proof obligation.
My argument is that there shouldn't even be a proof obligation here; the language is just not expressive enough to allow me to write the code that I want; something that is actually completely decidable & non-overlapping.
Just remember that `choose this instance if there's no other instance available' means `no other instance on the planet' everywhere but Main.
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.
It's had a lot of research; I want the best of all worlds. For a start: http://www.google.com/search?q=optimizing+dynamic+dispatch
I'll read through the results. My complaint about parametricity stands, I think.
You could get close without going to full dynamic dispatch, though; consider the following "core":
-- This part is all in haskell now data ShowDict a = ShowDict { show :: a -> String }
show_String :: ShowDict String show_Int :: ShowDict Int show_List :: ShowDict a -> ShowDict [a]
-- foo :: Show a => [a] -> String -- foo x = show x ++ "!" foo :: ShowDict a -> [a] -> String foo sd x = show (show_List sd) x ++ "!"
-- This part isn't in haskell, and the syntax sucks, but the idea is there. type MaybeShow a = Maybe (ShowDict a)
-- bar :: MaybeInstance Show a => [a] -> String -- bar xs -- | Show a = foo xs -- | otherwise = show (length xs) bar :: MaybeShow a -> [a] -> String bar (Just sd) xs = foo sd xs bar Nothing xs = show (show_Int) (length xs)
With this I could write
instance (MaybeInstance Show a, Arbitrary a) => MkArbitrary a where mkArbitrary xs | Show a = do x <- arbitrary return (x, show x) | otherwise = do st <- getGenState x <- arbitrary return (x, "evalGen arbitrary " ++ show st)
Now, every concrete type would be an instance of MaybeInstance <classname>, and "dynamic" dispatch and (I think) closed typeclasses would be a free benefit.
When can we discharge a MaybeInstance context?
And more likely to develop odd changes and hard-to-debug errors.
Or so you claim :)
Having the | Show a test suddenly trip from False to True because some other module imported Text.Show.Functions sounds like an odd change to me. At any rate, it scares me enough to make me oppose the idea.
QuickCheck makes testing so easy, I think the Arbitrary (a -> b) instance is almost unnecessary; (btw., functions /are/ instances of Show).
Now it's my turn to call:
Prelude Test.QuickCheck> show ((\x -> x) :: Int -> Int) <interactive>:1:0: No instance for (Show (Int -> Int))
Prelude Text.Show.Functions> show ((\x -> x) :: Int -> Int) "<function>"
Although, I do see a useless instance in the standard prelude at http://www.haskell.org/haskell-report/standard-prelude.html
I actually would love to have (unsafeShow :: a -> String) which made a "best effort" attempt (subject to the compiler's debugging level) to evaluate an object and tell you what it contains, including source code for functions if possible.
I wonder how useful this would be in practice.
You can easily write a showable ADT encoding the functions you want to test.
That's fair (and actually pretty interesting). But definitely less elegant than
-- assuming Arbitrary (Behavior Int) prop_fmap_at :: (Int -> Int) -> Property prop_fmap_at f = fmap f . at ~= at . fmap f
(see Conal's recent FRP paper for the formulation of this property)
Point.
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]
At least we agree on something. But please don't keep your design to yourself, share!
class Forceable alpha where seq :: alpha -> beta -> beta Instances derived automatically by the compiler, when possible, for every type (like Typeable should be). We can omit functions if desired (I don't remember why I thought this was a good idea). When you say f :: alpha -> beta or f :: C alpha => alpha -> beta The compiler adds implicit Forceable constraints on alpha and beta. But, if you say f :: !Forceable alpha => alpha -> beta The compiler leaves the Forceable alpha constraint off. Then you can say build :: (forall c. !Forceable c => (a -> c -> c) -> c -> c) -> [a] And the foldr/build law is still sound.
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]).
See dynamic dispatch, above. Although polymorphic instances do seem tricky. But you could probably get away with treating each typeclass as a member of the "typerep" object for each type with some amount of lookup; doesn't one of the existing compilers implement typeclasses in this way already?
I can't speak to the specific issue of dynamic dispatch. Most of the links I've looked at thus far seem to be about deciding when you actually /don't/ need dynamic dispatch. Haskell has that down pat, now; I haven't seen anything about making the actual function call go faster yet. Neither have I seen anything suggesting that the behavior of a function in one module cannot change because I added a multi-method in another module. That's what I'm most worried about; it sounds too much like perl's spooky action at a distance 10x over. jcc

On Mon, Apr 21, 2008 at 10:58 PM, Jonathan Cast
I must have failed to communicate well. To me, the point of giving a class a name is that then you can write a program that is parametric over the elements of that class. Knowing that I can implement monads in Ruby doesn't impress me nearly as much as knowing that I can implement mapM does. Haskell has me addicted to code reuse (mapM) the way the rest of the programming world is addicted to design patterns (monads). What I mean by `encoding Num and Monad' is that you can do something like this:
sum = foldr (+) 0 sequence = foldr (liftM2 (:)) (return [])
I don't know of any language that is dynamically typed and also can encode `return' or `0' in a way that lets those examples work. Statically typed languages where it works are rare, even. Haskell gives up a fair amount of control by making these things implicit, which is what I think you're running up against --- but I think it gets something useful and non-trivial to acheive in return.
I think ruby generally solves this problem via duck-typing; instead of
the cast happening in the (implicit) fromInteger call in sum above,
instead the cast happens in the function with more information via a
call to otherclass#to_whatever_i_am. You can do something like this:
class Frob
attr_reader :val
def initialize(i)
@val = i
end
def to_frob
self
end
def +(rhs)
rhsF = rhs.to_frob
Frob.new(rhsF.val + @val)
end
end
class Integer
def to_frob
Frob.new(self)
end
end
class Array
def sum
foldl(0) {|acc,x| acc + x}
end
def foldl(z)
each {|x| z = yield(z,x)}
z
end
end
irb(main):055:0> [1,2,3].sum
=> 6
irb(main):057:0> [1,2,3].map {|x| Frob.new(x)}.sum
=> #
I'll agree with this point. I've complained, concretely, about the lack of instances for (some) standard types before. (STM is actually a rather bad offender here; it's lacking MonadPlus, as well, despite the specific observation in the paper that it has the right signature for that class.)
Actually: GHCi, version 6.8.2: http://www.haskell.org/ghc/ :? for help Loading package base ... linking ... done. Prelude> :m Control.Monad Control.Monad.STM Prelude Control.Monad.STM Control.Monad> :i STM ... instance MonadPlus STM -- Defined in Control.Monad.STM
When can we discharge a MaybeInstance context?
On any concrete type. Like Typeable should be :) The compiler then determines whether that type is an instance of the class and provides the appropriate dictionary if applicable.
Having the | Show a test suddenly trip from False to True because some other module imported Text.Show.Functions sounds like an odd change to me. At any rate, it scares me enough to make me oppose the idea.
I see the worry now. I think this is more of a problem with orphan instances; are orphan instances considered to be a valuable enough feature to avoid potentially more powerful constructs? Maybe there is a better solution to the "I have class C from library X and type T from library Y and I want to make them play nice together" problem than orphan instances.
class Forceable alpha where seq :: alpha -> beta -> beta
Instances derived automatically by the compiler, when possible, for every type (like Typeable should be). We can omit functions if desired (I don't remember why I thought this was a good idea). When you say
f :: alpha -> beta
or
f :: C alpha => alpha -> beta
The compiler adds implicit Forceable constraints on alpha and beta. But, if you say
f :: !Forceable alpha => alpha -> beta
The compiler leaves the Forceable alpha constraint off. Then you can say
build :: (forall c. !Forceable c => (a -> c -> c) -> c -> c) -> [a]
And the foldr/build law is still sound.
This seems like a really interesting idea. -- ryan

On 22 Apr 2008, at 9:53 AM, Ryan Ingram wrote:
On Mon, Apr 21, 2008 at 10:58 PM, Jonathan Cast
wrote: I must have failed to communicate well. To me, the point of giving a class a name is that then you can write a program that is parametric over the elements of that class. Knowing that I can implement monads in Ruby doesn't impress me nearly as much as knowing that I can implement mapM does. Haskell has me addicted to code reuse (mapM) the way the rest of the programming world is addicted to design patterns (monads). What I mean by `encoding Num and Monad' is that you can do something like this:
sum = foldr (+) 0 sequence = foldr (liftM2 (:)) (return [])
I don't know of any language that is dynamically typed and also can encode `return' or `0' in a way that lets those examples work. Statically typed languages where it works are rare, even. Haskell gives up a fair amount of control by making these things implicit, which is what I think you're running up against --- but I think it gets something useful and non-trivial to acheive in return.
I think ruby generally solves this problem via duck-typing; instead of the cast happening in the (implicit) fromInteger call in sum above, instead the cast happens in the function with more information via a call to otherclass#to_whatever_i_am. You can do something like this:
class Frob attr_reader :val def initialize(i) @val = i end def to_frob self end def +(rhs) rhsF = rhs.to_frob Frob.new(rhsF.val + @val) end end
class Integer def to_frob Frob.new(self) end end
class Array def sum foldl(0) {|acc,x| acc + x} end def foldl(z) each {|x| z = yield(z,x)} z end end
irb(main):055:0> [1,2,3].sum => 6 irb(main):057:0> [1,2,3].map {|x| Frob.new(x)}.sum => #
How do I extend Num, in this case? Assign into the Integer namespace (maybe the wrong terminology, I don't know Ruby and don't want to)? I've considered designs like this, but they feel like a hack compared to type classes.
I'll agree with this point. I've complained, concretely, about the lack of instances for (some) standard types before. (STM is actually a rather bad offender here; it's lacking MonadPlus, as well, despite the specific observation in the paper that it has the right signature for that class.)
Actually:
GHCi, version 6.8.2: http://www.haskell.org/ghc/ :? for help Loading package base ... linking ... done. Prelude> :m Control.Monad Control.Monad.STM Prelude Control.Monad.STM Control.Monad> :i STM ... instance MonadPlus STM -- Defined in Control.Monad.STM
OK. I was going off the documentation (which is spotty for STM anyway).
When can we discharge a MaybeInstance context?
On any concrete type. Like Typeable should be :) The compiler then determines whether that type is an instance of the class and provides the appropriate dictionary if applicable.
This works if orphan instances are outlawed. That invalidates Haskell 98 programs, of course, including ones both of us have written. Forbidding those would be an interesting language design choice, of course, and would make most of what you've asked for sensible. Hmm.
Having the | Show a test suddenly trip from False to True because some other module imported Text.Show.Functions sounds like an odd change to me. At any rate, it scares me enough to make me oppose the idea.
I see the worry now. I think this is more of a problem with orphan instances; are orphan instances considered to be a valuable enough feature to avoid potentially more powerful constructs?
Maybe there is a better solution to the "I have class C from library X and type T from library Y and I want to make them play nice together" problem than orphan instances.
I can't think of one, for the general case, but I guarantee I'll be worrying about both questions until I think I know the answer... <snip> jcc

On Mon, 2008-04-21 at 22:58 -0700, Jonathan Cast wrote:
class Forceable alpha where seq :: alpha -> beta -> beta
Instances derived automatically by the compiler, when possible, for every type (like Typeable should be). We can omit functions if desired (I don't remember why I thought this was a good idea). When you say
f :: alpha -> beta
or
f :: C alpha => alpha -> beta
The compiler adds implicit Forceable constraints on alpha and beta. But, if you say
f :: !Forceable alpha => alpha -> beta
The compiler leaves the Forceable alpha constraint off. Then you can say
build :: (forall c. !Forceable c => (a -> c -> c) -> c -> c) -> [a]
And the foldr/build law is still sound.
Why do you want types that lie, plus some crazy ad-hoc special case? Why not just let f :: a -> b mean what you write as f :: !Forceable a => a -> b exactly as it would if seq were moved (back) into a class? Then the free theorems would hold for the types as stated.

On 22 Apr 2008, at 8:03 PM, Derek Elkins wrote:
On Mon, 2008-04-21 at 22:58 -0700, Jonathan Cast wrote:
class Forceable alpha where seq :: alpha -> beta -> beta
Instances derived automatically by the compiler, when possible, for every type (like Typeable should be). We can omit functions if desired (I don't remember why I thought this was a good idea). When you say
f :: alpha -> beta
or
f :: C alpha => alpha -> beta
The compiler adds implicit Forceable constraints on alpha and beta. But, if you say
f :: !Forceable alpha => alpha -> beta
The compiler leaves the Forceable alpha constraint off. Then you can say
build :: (forall c. !Forceable c => (a -> c -> c) -> c -> c) -> [a]
And the foldr/build law is still sound.
Why do you want types that lie, plus some crazy ad-hoc special case? Why not just let f :: a -> b mean what you write as f :: !Forceable a => a -> b exactly as it would if seq were moved (back) into a class? Then the free theorems would hold for the types as stated.
See /Being Lazy with Class/, on why seq was made polymorphic in the first place. I don't /want/ this design, but the most common case is that you don't care, for a type variable alpha, whether seq can be used on alpha or not. When you do care, the most common case is that you want seq, and adding seq where it wasn't previously legal requires a chain of modifications reminiscent of const poisoning. I'm willing to consider seq :: a -> b -> b a practical necessity, and compromise with it, as long as I can still declare properly parametric types on command. jcc PS ‘Lie’ is a bit strong. A lie is a statement crafted to have a meaning not in the belief set of the speaker. The meaning of a Haskell type judgement is given by the language. So square :: Num alpha => alpha -> alpha square x = x ** 2 contains a lie. But I don't think seq :: alpha -> beta -> beta does.

Jonathan Cast wrote:
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>"
This is a nice idiom I didn't know before. Definitely worth page on the wiki or two. Cheers Ben
participants (8)
-
Andrew Coppin
-
Anton van Straaten
-
Ben Franksen
-
Brandon S. Allbery KF8NH
-
David MacIver
-
Derek Elkins
-
Jonathan Cast
-
Ryan Ingram