Re: MRP, 3-year-support-window, and the non-requirement of CPP

On 2015-10-06 at 10:10:01 +0200, Johan Tibell wrote: [...]
You say that you stick to the 3-major-ghc-release support-window convention for your libraries. This is good, because then you don't need any CPP at all! Here's why:
[...]
So what do I have to write today to have my Monad instances be:
* Warning free - Warnings are useful. Turning them off or having spurious warnings both contribute to bugs.
Depends on the warnings. Some warnings are more of an advisory kind (hlint-ish). I wouldn't consider redundant imports a source of bugs. Leaving off a top-level signature shouldn't be a source of correctness bugs either. Also, warnings about upcoming changes (i.e. deprecation warnings) also are not necessarily a bug, but rather a way to raise awareness of API changes. At the other end of the spectrum are more serious warnings I'd almost consider errors, such as failing to define a non-defaulting method or violating a MINIMAL pragma specification, as that can lead to bottoms either in the form of runtime errors or even worse, hanging computations (in case of cyclic definitions). IMO, GHC should classify its warnings into severities/categories or introduce some compromise between -Wall and not-Wall.
* Use imports that either are qualified or have explicit import lists - Unqualified imports makes code more likely to break when dependencies add exports. * Don't use CPP.
That being said, as how to write your Monad instances today with GHC 7.10 w/o CPP, while supporting at least GHC 7.4/7.6/7.8/7.10: This *does* work (admittedly for an easy example, but this can be generalised): --8<---------------cut here---------------start------------->8--- module MyMaybe where import Control.Applicative (Applicative(..)) import Prelude (Functor(..), Monad(..), (.)) -- or alternatively: `import qualified Prelude as P` data Maybe' a = Nothing' | Just' a instance Functor Maybe' where fmap f (Just' v) = Just' (f v) fmap _ Nothing' = Nothing' instance Applicative Maybe' where pure = Just' f1 <*> f2 = f1 >>= \v1 -> f2 >>= (pure . v1) instance Monad Maybe' where Nothing' >>= _ = Nothing' Just' x >>= f = f x return = pure -- "deprecated" since GHC 7.10 --8<---------------cut here---------------end--------------->8--- This example above compiles -Wall-clean and satisfies all your 3 stated requirements afaics. I do admit this probably not what you had in mind. But to be consistent, if you want to avoid unqualified imports at all costs in order to have full control of what gets imported into your namespace, you shouldn't tolerate an implicit unqualified wildcard `Prelude` import either. As `Prelude` can, even if seldom, gain new exports as well (or even loose them -- `interact` *could* be a candidate for removal at some point).
Neither AMP or MRP includes a recipe for this in their proposal.
That's because -Wall-hygiene (w/o opting out of harmless) warnings across multiple GHC versions is not considered a show-stopper. In the specific case of MRP, I can offer you a Wall-perfect transition scheme by either using `ghc-options: -fno-mrp-warnings` in your cabal-file, or if that doesn't satisfy you, we can delay phase1 (i.e. redundant return-def warnings) to GHC 8.2: Now you can continue to write `return = pure` w/o GHC warning bothering you until GHC 8.2, at which point the 3-year-window will reach to GHC 7.10. Then starting with GHC 8.2 you can drop the `return` definition, and keep your More generally though, we need more language-features and/or modifications to the way GHC triggers warnings to make such refactorings/changes to the libraries -Wall-perfect as well. Beyond what Ben already suggested in another post, there was also the more general suggestion to implicitly suppress warnings when you explicitly name an import. E.g. import Control.Applicative (Applicative(..)) would suppress the redundant-import warning for Applicative via Prelude, because we specifically requested Applicative, so we don't mind that Prelude re-exports the same symbol.
AMP got one post-facto on the Wiki. It turns out that the workaround there didn't work (we tried it in Cabal and it conflicted with one of the above requirements.)
Yes, that unqualified `import Prelude`-last trick mentioned on the Wiki breaks down for more complex imports with (redundant) explicit import lists. However, the Maybe-example above works at the cost of a wordy Prelude-import, but it's more robust, as you pin down exactly which symbol you expect to get from each module.
The problem by discussions is that they are done between two groups with quite a difference in experience. On one hand you have people like Bryan, who have considerable contributions to the Haskell ecosystem and much experience in large scale software development (e.g. from Facebook). On the other hand you have people who don't. That's okay. We've all been at the latter group at some point of our career. [...]
At the risk of stating the obvious: I don't think it matters from which group a given argument comes from as its validity doesn't depend on the messenger. Neither does it matter whether an argument is repeated several times or stated only once. Also, every argument deserves to be considered regardless of its origin or frequency. -- hvr

I hit "send" too early, so here's the incomplete section completed: On 2015-10-06 at 18:47:08 +0200, Herbert Valerio Riedel wrote: [...]
In the specific case of MRP, I can offer you a Wall-perfect transition scheme by either using `ghc-options: -fno-mrp-warnings` in your cabal-file, or if that doesn't satisfy you, we can delay phase1 (i.e. redundant return-def warnings) to GHC 8.2:
Now you can continue to write `return = pure` w/o GHC warning bothering you until GHC 8.2, at which point the 3-year-window will reach to GHC 7.10.
Then starting with GHC 8.2 you can drop the `return` definition, and
...keep supporting a 3-year-window back till GHC 7.10 (which incorporates AMP and doesn't need `return` explicitly defined anymore) without CPP. And since you don't define `return` anymore, you don't get hit by the MRP warning either, which would start with GHC 8.2. GHC can keep providing as long as we want it to, and consider `return` being an extra method of `Monad` simply a GHC-ism. Future Haskell books and learning materials will hopefully be based on the next Haskell Report incorporating the AMP and stop referring to the historical `return` accident (which I consider badly named anyway from a pedagogically perspective). Code written unaware of `return` being a method of Monad will work anyway just fine. Do you see any problems with this scheme?

I hit "send" too early, so here's the incomplete section completed: On 2015-10-06 at 18:47:08 +0200, Herbert Valerio Riedel wrote: [...]
In the specific case of MRP, I can offer you a Wall-perfect transition scheme by either using `ghc-options: -fno-mrp-warnings` in your cabal-file, or if that doesn't satisfy you, we can delay phase1 (i.e. redundant return-def warnings) to GHC 8.2:
Now you can continue to write `return = pure` w/o GHC warning bothering you until GHC 8.2, at which point the 3-year-window will reach to GHC 7.10.
Then starting with GHC 8.2 you can drop the `return` definition, and
...keep supporting a 3-year-window back till GHC 7.10 (which incorporates AMP and doesn't need `return` explicitly defined anymore) without CPP. And since you don't define `return` anymore, you don't get hit by the MRP warning either, which would start with GHC 8.2. GHC can keep providing as long as we want it to, and consider `return` being an extra method of `Monad` simply a GHC-ism. Future Haskell books and learning materials will hopefully be based on the next Haskell Report incorporating the AMP and stop referring to the historical `return` accident (which I consider badly named anyway from a pedagogically perspective). Code written unaware of `return` being a method of Monad will work anyway just fine. Do you see any problems with this scheme?

2015-10-06 18:47 GMT+02:00 Herbert Valerio Riedel
[...] That being said, as how to write your Monad instances today with GHC 7.10 w/o CPP, while supporting at least GHC 7.4/7.6/7.8/7.10: This *does* work (admittedly for an easy example, but this can be generalised):
--8<---------------cut here---------------start------------->8--- module MyMaybe where
import Control.Applicative (Applicative(..)) import Prelude (Functor(..), Monad(..), (.)) -- or alternatively: `import qualified Prelude as P` [...] --8<---------------cut here---------------end--------------->8---
This example above compiles -Wall-clean and satisfies all your 3 stated requirements afaics. I do admit this probably not what you had in mind.
OK, so the trick is that you're effectively hiding Applicative from the Prelude (which might be a no-op). This "works" somehow, but is not satisfactory IMHO for several reasons: * If you explicitly import all entities from Prelude, your import list will typically get *very* long and unreadable. Furthermore, if that's the suggested technique, what's the point of having a Prelude at all? * Some people see qualified imports as the holy grail, but having to prefix tons of things with "P." is IMHO very ugly. Things are even worse for operators: The whole notion of operators in itself is totally useless and superfluous *except* for a single reason: Readability. And exactly that gets destroyed when you have to qualify them, so I would (sadly) prefer some #ifdef hell, if that gives me readable code elsewhere. * With the current trend of moving things to the Prelude, I can envision a not-so-distant future where the whole Control.Applicative module will be deprecated. As it is now, it's mostly superfluous and/or contains only stuff which might better live somewhere else.
[...] That's because -Wall-hygiene (w/o opting out of harmless) warnings across multiple GHC versions is not considered a show-stopper.
That's your personal POV, I'm more leaning towards "-Wall -Werror". I've seen too many projects where neglecting warning over an extended period of time made fixing them basically impossible at the end. Anyway, I think that a sane ecosystem should allow *both* POVs, the sloppy one and the strict one.
[...] Beyond what Ben already suggested in another post, there was also the more general suggestion to implicitly suppress warnings when you explicitly name an import. E.g.
import Control.Applicative (Applicative(..))
would suppress the redundant-import warning for Applicative via Prelude, because we specifically requested Applicative, so we don't mind that Prelude re-exports the same symbol. [...]
Uh, oh... That would be bad, because one normally wants to see redundant imports. Without the compiler telling me, how should I find out which are redundant? Manually trying to remove them step by step? :-/ Cheers, S.

On 2015-10-06 at 19:41:51 +0200, Sven Panne wrote:
2015-10-06 18:47 GMT+02:00 Herbert Valerio Riedel
: [...] That being said, as how to write your Monad instances today with GHC 7.10 w/o CPP, while supporting at least GHC 7.4/7.6/7.8/7.10: This *does* work (admittedly for an easy example, but this can be generalised):
--8<---------------cut here---------------start------------->8--- module MyMaybe where
import Control.Applicative (Applicative(..)) import Prelude (Functor(..), Monad(..), (.)) -- or alternatively: `import qualified Prelude as P` [...] --8<---------------cut here---------------end--------------->8---
This example above compiles -Wall-clean and satisfies all your 3 stated requirements afaics. I do admit this probably not what you had in mind.
OK, so the trick is that you're effectively hiding Applicative from the Prelude (which might be a no-op). This "works" somehow, but is not satisfactory IMHO for several reasons:
[...] Btw, I've also seen the trick below, in which you use the aliased `A.` prefix just once so GHC considers the import non-redundant, and don't have to suffer from prefixed operators in the style of `A.<*>`. Is this any better? --8<---------------cut here---------------start------------->8--- import Control.Applicative as A (Applicative(..)) data Maybe' a = Nothing' | Just' a instance Functor Maybe' where fmap f (Just' v) = Just' (f v) fmap _ Nothing' = Nothing' instance A.Applicative Maybe' where pure = Just' f1 <*> f2 = f1 >>= \v1 -> f2 >>= (pure . v1) instance Monad Maybe' where Nothing' >>= _ = Nothing' Just' x >>= f = f x return = pure -- "deprecated" since GHC 7.10 --8<---------------cut here---------------end--------------->8--- -- hvr

2015-10-07 9:35 GMT+02:00 Herbert Valerio Riedel
Btw, I've also seen the trick below, in which you use the aliased `A.` prefix just once so GHC considers the import non-redundant, and don't have to suffer from prefixed operators in the style of `A.<*>`.
Is this any better? [...]
While not perfect, it's much better than having to fiddle around with Prelude imports. Although there's the slight danger that somebody else (or the author 1 year later) looks at the code and has a WTF-moment... ;-) To be honest, while it's somehow obvious how it works when you read it, I've never seen that trick. Perhaps stuff like this belongs into some general "Porting Guide", along with its alternatives. It's general enough that it should not be buried in some AMP/FTP/return/... transitioning guide. Cheers, S.

On Wed, Oct 7, 2015 at 3:35 AM, Herbert Valerio Riedel
--8<---------------cut here---------------start------------->8--- import Control.Applicative as A (Applicative(..))
data Maybe' a = Nothing' | Just' a
instance Functor Maybe' where fmap f (Just' v) = Just' (f v) fmap _ Nothing' = Nothing'
instance A.Applicative Maybe' where pure = Just' f1 <*> f2 = f1 >>= \v1 -> f2 >>= (pure . v1)
instance Monad Maybe' where Nothing' >>= _ = Nothing' Just' x >>= f = f x
return = pure -- "deprecated" since GHC 7.10 --8<---------------cut here---------------end--------------->8---
Alternately, import Control.Applicative import Prelude data Maybe' a = Nothing' | Just' a instance Functor Maybe' where fmap f (Just' v) = Just' (f v) fmap _ Nothing' = Nothing' instance Applicative Maybe' where
-- hvr _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime

On Tue, Oct 6, 2015 at 1:41 PM, Sven Panne
2015-10-06 18:47 GMT+02:00 Herbert Valerio Riedel
: [...] That's because -Wall-hygiene (w/o opting out of harmless) warnings
across multiple GHC versions is not considered a show-stopper.
That's your personal POV, I'm more leaning towards "-Wall -Werror". I've seen too many projects where neglecting warning over an extended period of time made fixing them basically impossible at the end. Anyway, I think that a sane ecosystem should allow *both* POVs, the sloppy one and the strict one.
Note: You haven't been able to upload a package that has -Werror turned on in the cabal file for a couple of years now -- even if it is only turned on on the test suite, so any -Werror discipline you choose to enforce is purely local. -Edward

On 6 Oct 2015, at 17:47, Herbert Valerio Riedel wrote:
The problem by discussions is that they are done between two groups with quite a difference in experience. On one hand you have people like Bryan, who have considerable contributions to the Haskell ecosystem and much experience in large scale software development (e.g. from Facebook). On the other hand you have people who don't. That's okay. We've all been at the latter group at some point of our career. [...]
At the risk of stating the obvious: I don't think it matters from which group a given argument comes from as its validity doesn't depend on the messenger.
In that case, I think you are misunderstanding the relevance of Johan's argument here. Let me try to phrase it differently. Some people who can reasonably claim to have experience with million-line plus codebases are warning that this change is too disruptive, and makes maintenance harder than it ought to be. On the other hand, of the people who say the change is not really disruptive, none of them have (yet?) made claims to have experience of the maintenance of extremely large-scale codebases. The authority of the speaker does matter in technical arguments of this nature: people without the relevant experience are simply unqualified to make guesses about the impact. Regards, Malcolm

On Tue, Oct 6, 2015 at 3:02 PM, Malcolm Wallace
On 6 Oct 2015, at 17:47, Herbert Valerio Riedel wrote:
At the risk of stating the obvious: I don't think it matters from which group a given argument comes from as its validity doesn't depend on the messenger.
In that case, I think you are misunderstanding the relevance of Johan's argument here. Let me try to phrase it differently. Some people who can reasonably claim to have experience with million-line plus codebases are warning that this change is too disruptive, and makes maintenance harder than it ought to be. On the other hand, of the people who say the change is not really disruptive, none of them have (yet?) made claims to have experience of the maintenance of extremely large-scale codebases.
Very well. Let me offer a view from the "other side of the fence." I personally maintain about 1.3 million lines of Haskell, and over 120 packages on hackage. It took me less than a half a day to get everything running with 7.10, and about two days to build -Wall clean. In that first day I actually had to spend vastly more time fixing things related to changes in Typeable, template-haskell and a tweaked corner case in the typechecker than anything AMP/FTP related. In the end I had to add two type signatures. Most of the patches to go -Wall clean looked like +#if __GLASGOW_HASKELL__ < 710 import Control.Applicative import Data.Monoid +#endif Maybe 10% were more complicated. -Edward

Dear all, I think this discussion has gotten quite heated for reasons not related to the concrete MRP proposal, which, to be honest, I considered quite modest in terms of both scope and impact. Instead, I think it is a proxy for lots of remaining frustration and anxiety over the poor handling over the Foldable Traversable Proposal. I would like to remind everyone that due to the broad discussions and concerns over the proposal, a very rare, careful poll of Haskell users was taken, announced broadly in many channels. [1] The poll, overwhelmingly, revealed a mandate for the FTP. The breakdown of that mandate was 87% in favor among hobbyists and 79% in favor among non-hobbyists (who constituted a majority of those polled). I. Generalities That said, even the _best_ poll was not a substitute for a better earlier discussion. The handling of the AMP and FTP, which I think was heroic in terms of minimizing breakage while accomplishing long-desired change also still could have been better. As a whole, the work accomplished the mandate of allowing code to be written backwards-compatible without requiring CPP. However, it did not also seek to prevent warnings. This in itself was an enormous step forward from changes in the past which have _not_ even managed to prevent the need for CPP. At the time, I think it was not recognized how much desire there would be for things that were _both_ CPP free and _also_ warning-free for 3 releases. I think one of the great elements of progress in the current discussion is that there is now a proposal on the table which recognizes this, and seeks to accomplish this change in accordance with this desire. It is not the world’s most important change, but the recognition that change should seek to be both CPP _and_ warning free is a good recognition, and I’m sure it will be taken into account in future proposals as well. I don’t think it is useful to continue to have abstract discussions on the conflict between desire for incremental improvement versus the need to minimize pain on maintainers. We might as well continue to argue about the need for purely functional programming versus the need to print “hello world” to the console. Rather, we should put our collective minds together as collaborators and colleagues to accomplish _both_, and to come up with solutions that should work for everyone. To the extent this discussion has been about that, I think it has been useful and positive. However, to the extent this discussion insists, on either side, on the shallow idea that we must treat “improvement” versus “stability” as irreconcilable factions in necessary conflict, then I fear it will be a missed opportunity. II. Particulars With that in mind, I think the _concrete_ voices of concern have been the most useful. Gregory Collins’ list of issues requiring CPP should be very sobering. Of note, I think they point to areas where the core libraries committee has not paid _enough_ attention (or perhaps has not been sufficiently empowered: recall that not all core libraries fall under its maintenance [2]). Things like the newtype FFI issue, the changes to prim functions, the splitup of old-time and the changes to exception code were _not_ vetted as closely as the AMP and FTP were, or as the MRP is currently being. I don’t know all the reasons for this, but I suspect they just somewhat slipped under the radar. In any case, if all those changes were as carefully engineered as the MRP proposal has been, then imho things would have been much smoother. So, while this discussion may be frustrating, it nonetheless in some ways provides a model of how people have sought to do better and be more proactive with careful discussion of changes. This is much appreciated. Personally, since the big switch to extensible exceptions back prior in 6.10, and since the split-base nonsense prior to that, very few changes to the core libraries have really caused too much disruption in my code. Since then, the old-time cleanup was the worst, and the big sin there was that time-locale-compat was only written some time after the fact by a helpful third-party contributor and not engineered from the start. (I will note that the time library is one of the core libraries that is _not_ maintained by the core libraries committee). Outside of that, the most disruptive changes to my code that I can recall have been from changes to the aeson library over the years — particularly but not only regarding its handling of doubles. I don’t begrudge these changes — they iteratively arrived at a _much_ better library than had they not been made. [3] After than, I made a few changes regarding Happstack and Snap API changes if I recall. Additionally, the addition of “die” to System.Exit caused a few name clashes. My point is simply that there are many packages outside of base that also move, and “real” users with “real” code will these days often have quite a chain of dependencies, and will encounter movement and change from across many of them. So if we say “base never changes” that does not mean “packages will never break” — it just means that base will not have the same opportunity to improve that other packages do, which will eventually lead to frustration, just as it did in the past and in the leadup to the BBP. III. Discussions Further, since there has been much discussion of a window of opportunity, I would like to offer a counterpoint to the (sound) advice that we take into consideration voices with long experience in Haskell. The window of opportunity is, by definition, regarding takeup of Haskell by new users. And so if newer users favor certain changes, then it is good evidence that those changes will help with uptake among other new users. So, if they are good changes on their own, then the fact that they are appealing to newer users should be seen as a point in their favor, rather than a reason to dismiss those opinions. But if we are in a situation where we see generations of adopters pitted against one another, then we already have deeper problems that need to be sorted out. Regarding where and how to have these discussions — the decision was made some time ago (I believe at the start of the initial Haskell Prime process if not sooner, so circa 2009?) that the prime committee would focus on language extensions and not library changes, and that those changes would be delegated to the libraries@ list. The lack of structure to the libraries@ list is what prompted the creation of the libraries committee, whose ultimately responsibility it is to decide on and shepherd through these changes, in consultation with others and ideally driven by broad consensus. Prior to this structure, things broke even more, imho, and simultaneously the things that were widely desired were still not implemented. So I thank the libraries committee for their good work so far. So, it may be that the process of community discussion on core libraries changes is not best suited for the libraries@ list. But if not there, Where? I worry that the proliferation of lists will not improve things here. Those involved with Haskell have multiplied (this is good). The voices to take into account have multiplied (this is good). Necessarily, this means that there will just be _more_ stuff, and making sure that everyone can filter to just that part they want to is difficult. Here, perhaps, occasional libraries-related summary addenda to the ghc newsletter could be appropriate? Or is there another venue we should look towards? “Chair’s reports” to the Haskell Weekly News maybe? IV. Summing up We should bear in mind after all that this is just about cleaning up a redundant typeclass method (albeit one in a very prominent place) and hardly the hill anyone would want to die on [4]. Nonetheless, I think it would be a good sign of progress and collaboration if we can find a way to implement a modest change like this in a way that everyone finds acceptable vis a vis a sufficiently slow pace, the lack of a need for CPP and the lack of any induced warnings. On the other hand, other opportunities will doubtless present themselves in the future. Best, Gershom [1] https://mail.haskell.org/pipermail/libraries/2015-February/025009.html [2] https://wiki.haskell.org/Library_submissions#The_Core_Libraries [3] and in any case I am sure Bryan would be the last to want us to treat him as some sort of “guru” on these matters. [4] for those in search of better hills to die on, this is a list of some good ones: http://www.theawl.com/2015/07/hills-to-die-on-ranked P.S. In case there is any question, this email, as all emails I write that do not state otherwise, is not being written in any particular capacity regarding the various infra-related hats I wear, but is just an expression of my own personal views.
participants (5)
-
Edward Kmett
-
Gershom B
-
Herbert Valerio Riedel
-
Malcolm Wallace
-
Sven Panne