RE: Overlapping and incoherent instances

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

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