<div dir="ltr"><div>Now if only we could somehow find a way to do the same thing for AllowAmbiguousTypes. :)<br></div><div><br></div><div>I have a 2500 line file that I'm forced to turn on AllowAmbiguousTypes in for 3 definitions, and checking that I didn't accidentally make something else ambiguous to GHC's eyes is a rather brutal affair. (I can't break up the file without inducing orphans)</div>
<div><br></div><div>This is just a passing comment, while I'm thinking about it, not a serious attempt to derail the topic!<br><div><br></div><div>-Edward</div></div></div><div class="gmail_extra"><br><br><div class="gmail_quote">
On Thu, Jul 31, 2014 at 4:13 AM, Simon Peyton Jones <span dir="ltr"><<a href="mailto:simonpj@microsoft.com" target="_blank">simonpj@microsoft.com</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">
Andreas, remember that GHC 7.8 already implements (essentially) the same algorithm.  The difference is that 7.8 offers only the brutal -XOverlappingInstances to control it.  In your example of the decision you make when writing<br>

<div class="">   instance Bla a => Bla [a]<br>
</div>vs<br>
<div class="">   instance {-# OVERLAPPABLE #-} Bla a => Bla [a]<br>
</div>you are, with GHC 7.8, making precisely the same decision when you decide whether or not to add {-# LANGUAGE OverlappingInstances #-} to that module.  Perhaps that wasn't clear in what I wrote; apologies.<br>
<br>
So your proposal seems to be this<br>
<br>
        don't remove -XOverlappingInstances, because that will prevent<br>
        programmers from "flipping on/off pragmas until their program<br>
        goes through".<br>
<br>
It's hard to argue AGAINST providing the opportunity for more careful programmers to express their intentions more precisely, which is what the OVERLAP/OVERLAPPABLE pragmas do.<br>
<br>
Concerning deprecating OverlappingInstances, my gut feel is that it is positively a good thing to guide programmers towards a more robust programming style.  But my reason for starting this thread was to see whether or not others' gut feel is similar.<br>

<br>
Simon<br>
<div class=""><br>
| -----Original Message-----<br>
| From: Libraries [mailto:<a href="mailto:libraries-bounces@haskell.org">libraries-bounces@haskell.org</a>] On Behalf Of<br>
</div><div class="">| Andreas Abel<br>
| Sent: 31 July 2014 08:59<br>
| To: Simon Peyton Jones; ghc-devs; GHC users; Haskell Libraries<br>
| (<a href="mailto:libraries@haskell.org">libraries@haskell.org</a>)<br>
</div><div class="">| Subject: Re: Overlapping and incoherent instances<br>
|<br>
</div><div><div class="h5">| On <a href="tel:31.07.2014%2009" value="+13107201409">31.07.2014 09</a>:20, Simon Peyton Jones wrote:<br>
| > Friends, in sending my message below, I should also have sent a link<br>
| > to<br>
| ><br>
| > <a href="https://ghc.haskell.org/trac/ghc/ticket/9242#comment:25" target="_blank">https://ghc.haskell.org/trac/ghc/ticket/9242#comment:25</a><br>
|<br>
| Indeed.<br>
|<br>
| Quoting from the spec:<br>
|<br>
|   * Eliminate any candidate IX for which both of the following hold:<br>
|     * There is another candidate IY that is strictly more specific;<br>
|       that is, IY is a substitution instance of IX but not vice versa.<br>
|<br>
|     * Either IX is overlappable or IY is overlapping.<br>
|<br>
| Mathematically, this makes a lot of sense.  But put on the hat of<br>
| library writers, and users, and users that don't rtfm.  Looking out<br>
| from under this hat, the one may always wonder whether one should make<br>
| one's generic instances OVERLAPPABLE or not.<br>
|<br>
| If I create a library with type class Bla and<br>
|<br>
|    instance Bla a => Bla [a]<br>
|<br>
| I could be a nice library writer and spare my users from declaring<br>
| their Bla String instances as OVERLAPPING, so I'd write<br>
|<br>
|    instance {-# OVERLAPPABLE #-} Bla a => Bla [a]<br>
|<br>
| Or maybe that would be malicious?<br>
|<br>
| I think the current proposal is too sophisticated.  There are no<br>
| convincing examples given in the discussion so far that demonstrate<br>
| where this sophistication pays off in practice.<br>
|<br>
| Keep in mind that 99% of the Haskell users will never study the<br>
| instance resolution algorithm or its specification, but just flip<br>
| on/off pragmas until their code goes through.  [At least that was my<br>
| approach: whenever GHC asks for one more LANGUAGE pragma, just throw it<br>
| in.]<br>
|<br>
| Cheers,<br>
| Andreas<br>
|<br>
|<br>
| > Comment 25 describes the semantics of OVERLAPPING/OVERLAPPABLE etc,<br>
| > which I signally failed to do in my message below, leading to<br>
| > confusion in the follow up messages.  My apologies for that.<br>
| ><br>
| > Some key points:<br>
| ><br>
| > *There is a useful distinction between /overlapping/ and<br>
| > /overlappable/, but if you don't want to be bothered with it you can<br>
| > just say OVERLAPS (which means both).<br>
| ><br>
| > *Overlap between two candidate instances is allowed if /either/ has<br>
| > the relevant property.  This is a bit sloppy, but reduces the<br>
| > annotation burden.  Actually, with this per-instance stuff I think<br>
| > it'd be perfectly defensible to require both to be annotated, but<br>
| > that's a different discussion.<br>
| ><br>
| > I hope that helps clarify.<br>
| ><br>
| > I'm really pretty certain that the basic proposal here is good: it<br>
| > implements the current semantics in a more fine-grained manner.  My<br>
| > main motivation was to signal the proposed deprecation of the global<br>
| > per-module flag -XoverlappingInstances.  Happily people generally<br>
| seem<br>
| > fine with this.   It is, after all, precisely what deprecations are<br>
| for<br>
| > ("the old thing still works for now, but it won't do so for ever, and<br>
| > you should change as soon as is convenient").<br>
| ><br>
| > Thanks<br>
| ><br>
| > Simon<br>
| ><br>
| > *From:*Libraries [mailto:<a href="mailto:libraries-bounces@haskell.org">libraries-bounces@haskell.org</a>] *On Behalf Of<br>
| > *Simon Peyton Jones<br>
| > *Sent:* 29 July 2014 10:11<br>
| > *To:* ghc-devs; GHC users; Haskell Libraries (<a href="mailto:libraries@haskell.org">libraries@haskell.org</a>)<br>
| > *Subject:* Overlapping and incoherent instances<br>
| ><br>
| > Friends<br>
| ><br>
| > One of GHC's more widely-used features is overlapping (and sometimes<br>
| > incoherent) instances.  The user-manual documentation is here<br>
| > <<a href="http://www.haskell.org/ghc/docs/latest/html/users_guide/type-class-" target="_blank">http://www.haskell.org/ghc/docs/latest/html/users_guide/type-class-</a><br>
| extensions.html#instance-overlap>.<br>
| ><br>
| > The use of overlapping/incoherent instances is controlled by LANGUAGE<br>
| > pragmas: OverlappingInstances and IncoherentInstances respectively.<br>
| ><br>
| > However the overlap/incoherent-ness is a property of the **instance<br>
| > declaration** itself, and has been for a long time.  Using LANGUAGE<br>
| > OverlappingInstances simply sets the "I am an overlapping instance"<br>
| > flag for every instance declaration in that module.<br>
| ><br>
| > This is a Big Hammer.  It give no clue about **which** particular<br>
| > instances the programmer is expecting to be overlapped, nor which are<br>
| > doing the overlapping.    It brutally applies to every instance in<br>
| the<br>
| > module.  Moreover, when looking at an instance declaration, there is<br>
| > no nearby clue that it might be overlapped.  The clue might be in the<br>
| > command line that compiles that module!<br>
| ><br>
| > Iavor has recently implemented per-instance-declaration pragmas, so<br>
| > you can say<br>
| ><br>
</div></div>| > instance {-# OVERLAPPABLE #-} Show a => Show [a] where ...<br>
| ><br>
| > instance {-# OVERLAPPING #-} Show [Char] where ...<br>
<div class="">| ><br>
| > This is much more precise (it affects only those specific instances)<br>
| > and it is much clearer (you see it when you see the instance<br>
| declaration).<br>
| ><br>
| > This new feature will be in GHC 7.10 and I'm sure you will be happy<br>
| > about that. *But I propose also to deprecate the LANGUAGE pragmas<br>
| > OverlappingInstances and IncoherentInstances*, as way to encourage<br>
| > everyone to use the new feature instead of the old big hammer.  The<br>
| > old LANGUAGE pragmas will continue to work, of course, for at least<br>
| > another complete release cycle.  We could make that two cycles if it<br>
| was helpful.<br>
| ><br>
| > However, if you want deprecation-free libraries, it will entail a<br>
| wave<br>
| > of library updates.<br>
| ><br>
| > This email is just to warn you, and to let you yell if you think this<br>
| is<br>
| > a bad idea.   It would actually not be difficult to retain the old<br>
| > LANGUAGE pragmas indefinitely - it just seems wrong not to actively<br>
| > push authors in the right direction.<br>
| ><br>
| > These deprecations of course popped up in the test suite, so I've<br>
| been<br>
| > replacing them with per-instance pragmas there too.  Interestingly in<br>
| > some cases, when looking for which instances needed the pragmas, I<br>
</div>| > found...none. So OverlappingInstances was entirely unnecessary.  Maybe<br>
<div class="im HOEnZb">| > library authors will find that too!<br>
| ><br>
| > Simon<br>
| ><br>
| ><br>
| ><br>
| > _______________________________________________<br>
| > Libraries mailing list<br>
| > <a href="mailto:Libraries@haskell.org">Libraries@haskell.org</a><br>
| > <a href="http://www.haskell.org/mailman/listinfo/libraries" target="_blank">http://www.haskell.org/mailman/listinfo/libraries</a><br>
| ><br>
|<br>
|<br>
| --<br>
| Andreas Abel  <><      Du bist der geliebte Mensch.<br>
|<br>
| Department of Computer Science and Engineering Chalmers and Gothenburg<br>
| University, Sweden<br>
|<br>
| <a href="mailto:andreas.abel@gu.se">andreas.abel@gu.se</a><br>
| <a href="http://www2.tcs.ifi.lmu.de/~abel/" target="_blank">http://www2.tcs.ifi.lmu.de/~abel/</a><br>
| _______________________________________________<br>
| Libraries mailing list<br>
| <a href="mailto:Libraries@haskell.org">Libraries@haskell.org</a><br>
| <a href="http://www.haskell.org/mailman/listinfo/libraries" target="_blank">http://www.haskell.org/mailman/listinfo/libraries</a><br>
</div><div class="HOEnZb"><div class="h5">_______________________________________________<br>
Glasgow-haskell-users mailing list<br>
<a href="mailto:Glasgow-haskell-users@haskell.org">Glasgow-haskell-users@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/glasgow-haskell-users" target="_blank">http://www.haskell.org/mailman/listinfo/glasgow-haskell-users</a><br>
</div></div></blockquote></div><br></div>