
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