
Dear maintainers of bytestring cabal vector time dph As discussed in Trac #6032 I am deprecating Rank2Types PolymorphicComponents in favour of the single flag RankNTypes Could you update your packages to match? Until then we'll need to accept the deprecation warnings that GHC will produce when building them. The change is backward compatible; older GHCs understand RankNTypes. In addition to changing any LANGAUGE pragmas, there may be some changes to Cabal's flaggery. Thanks Simon ./Cabal/Cabal/Distribution/PackageDescription/Check.hs:1114: , RankNTypes, PolymorphicComponents, ExistentialQuantification ./Cabal/Cabal/Distribution/Simple/GHC.hs:459: ,(PolymorphicComponents , fglasgowExts) ./Cabal/Cabal/Distribution/Simple/Hugs.hs:194: ,(PolymorphicComponents , ext98) ./Cabal/Cabal/Distribution/Simple/UHC.hs:103: (PolymorphicComponents, alwaysOn), ./Cabal/Cabal/Language/Haskell/Extension.hs:186: | PolymorphicComponents ./bytestring/Data/ByteString/Builder/Internal.hs:1:{-# LANGUAGE ScopedTypeVariables, CPP, BangPatterns, Rank2Types #-} ./Cabal/Cabal/Distribution/PackageDescription/Check.hs:1113: , FunctionalDependencies, Rank2Types ./Cabal/Cabal/Distribution/Simple/GHC.hs:457: ,(Rank2Types , fglasgowExts) ./Cabal/Cabal/Distribution/Simple/Hugs.hs:193: ,(Rank2Types , ext98) ./Cabal/Cabal/Distribution/Simple/UHC.hs:108: (Rank2Types, alwaysOn), ./Cabal/Cabal/Language/Haskell/Extension.hs:177: | Rank2Types ./containers/Data/Graph.hs:3:{-# LANGUAGE Rank2Types #-} ./dph/dph-lifted-copy/Data/Array/Parallel/Lifted/TH/Repr.hs:1:{-# LANGUAGE TemplateHaskell, Rank2Types #-} ./time/Data/Time/Calendar/Days.hs:13:#if LANGUAGE_Rank2Types ./time/Data/Time/Calendar/Days.hs:20:#if LANGUAGE_Rank2Types ./time/Data/Time/Clock/Scale.hs:19:#if LANGUAGE_Rank2Types ./time/Data/Time/Clock/Scale.hs:27:#if LANGUAGE_Rank2Types ./time/Data/Time/Clock/Scale.hs:45:#if LANGUAGE_Rank2Types ./time/Data/Time/Clock/TAI.hs:24:#if LANGUAGE_Rank2Types ./time/Data/Time/Clock/TAI.hs:31:#if LANGUAGE_Rank2Types ./time/Data/Time/Clock/UTC.hs:23:#if LANGUAGE_Rank2Types ./time/Data/Time/Clock/UTC.hs:37:#if LANGUAGE_Rank2Types ./time/Data/Time/Clock/UTC.hs:66:#if LANGUAGE_Rank2Types ./time/Data/Time/Format/Parse.hs:8:#if LANGUAGE_Rank2Types ./time/Data/Time/Format/Parse.hs:21:#if LANGUAGE_Rank2Types ./time/Data/Time/Format/Parse.hs:30:#if LANGUAGE_Rank2Types ./time/Data/Time/Format/Parse.hs:34:#if LANGUAGE_Rank2Types ./time/Data/Time/Format/Parse.hs:64:#if LANGUAGE_Rank2Types ./time/Data/Time/Format/Parse.hs:344:#if LANGUAGE_Rank2Types ./time/Data/Time/LocalTime/LocalTime.hs:22:#if LANGUAGE_Rank2Types ./time/Data/Time/LocalTime/LocalTime.hs:35:#if LANGUAGE_Rank2Types ./time/Data/Time/LocalTime/LocalTime.hs:79:#if LANGUAGE_Rank2Types ./time/Data/Time/LocalTime/TimeOfDay.hs:19:#if LANGUAGE_Rank2Types ./time/Data/Time/LocalTime/TimeOfDay.hs:34:#if LANGUAGE_Rank2Types ./time/Data/Time/LocalTime/TimeZone.hs:24:#if LANGUAGE_Rank2Types ./time/Data/Time/LocalTime/TimeZone.hs:38:#if LANGUAGE_Rank2Types ./vector/Data/Vector/Fusion/Stream/Monadic.hs:1:{-# LANGUAGE ExistentialQuantification, Rank2Types, BangPatterns #-} ./vector/Data/Vector/Fusion/Stream.hs:1:{-# LANGUAGE FlexibleInstances, Rank2Types #-} ./vector/Data/Vector/Generic/Base.hs:1:{-# LANGUAGE Rank2Types, MultiParamTypeClasses, FlexibleContexts, ./vector/Data/Vector/Generic/New.hs:1:{-# LANGUAGE Rank2Types, FlexibleContexts #-} ./vector/Data/Vector/Generic.hs:1:{-# LANGUAGE Rank2Types, MultiParamTypeClasses, FlexibleContexts, ./vector/Data/Vector/Primitive.hs:1:{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, TypeFamilies, ScopedTypeVariables, Rank2Types #-} ./vector/Data/Vector/Storable.hs:1:{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, TypeFamilies, Rank2Types, ScopedTypeVariables #-} ./vector/Data/Vector/Unboxed.hs:1:{-# LANGUAGE Rank2Types #-} ./vector/Data/Vector.hs:1:{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, TypeFamilies, Rank2Types #-}

Hi Simon,
On Fri, Oct 19, 2012 at 4:49 AM, Simon Peyton-Jones
As discussed in Trac #6032 I am deprecating
Rank2Types
PolymorphicComponents
in favour of the single flag
RankNTypes
I'm fine with making the changes to cabal, but before I do, I want to make sure that we really want to do this. I did a quick investigation of how many modules need to be updated on Hackage. It's about 775. That will require quite a lot of work by quite a lot of people. Could we instead have Rank2Types be an alias for RankNTypes? Cheers, Johan

See my response on http://hackage.haskell.org/trac/ghc/ticket/6032#comment:6
Not sure what the best path is here
S
| -----Original Message-----
| From: Johan Tibell [mailto:johan.tibell@gmail.com]
| Sent: 19 October 2012 17:39
| To: Simon Peyton-Jones
| Cc: Don Stewart; Duncan Coutts; Roman Leshchinskiy;
| ashley@semantic.org; cabal-devel@haskell.org; Ben Lippmeier; Manuel M T
| Chakravarty; cvs-ghc@haskell.org
| Subject: Re: deprecating
|
| Hi Simon,
|
| On Fri, Oct 19, 2012 at 4:49 AM, Simon Peyton-Jones
|

On Fri, Oct 19, 2012 at 04:53:32PM +0000, Simon Peyton-Jones wrote:
See my response on http://hackage.haskell.org/trac/ghc/ticket/6032#comment:6 Not sure what the best path is here
FWIW, I agree with Simon. And even if Rank2Types /is/ left as a permanent alias, I don't see a reason not to make the change in Cabal. Also, if you do want to take figures into account when considering this sort of change, then I think a better figure than "number of modules" would be "number of packages which compile with GHC 7.4/7.6" (or perhaps "number of packages uploaded within the last year" would be easier to measure and good enough).
| > As discussed in Trac #6032 I am deprecating | > | > Rank2Types | > | > PolymorphicComponents | > | > in favour of the single flag | > | > RankNTypes | | I'm fine with making the changes to cabal, but before I do, I want to | make sure that we really want to do this. I did a quick investigation | of how many modules need to be updated on Hackage. It's about 775. | That will require quite a lot of work by quite a lot of people. Could | we instead have Rank2Types be an alias for RankNTypes?
Thanks Ian

On Fri, Oct 19, 2012 at 09:38:44AM -0700, Johan Tibell wrote:
Hi Simon,
On Fri, Oct 19, 2012 at 4:49 AM, Simon Peyton-Jones
wrote: As discussed in Trac #6032 I am deprecating
Rank2Types
PolymorphicComponents
in favour of the single flag
RankNTypes
I'm fine with making the changes to cabal, but before I do, I want to make sure that we really want to do this. I did a quick investigation of how many modules need to be updated on Hackage. It's about 775. That will require quite a lot of work by quite a lot of people. Could we instead have Rank2Types be an alias for RankNTypes?
"What will be the least work?" seems a relatively poor basis for making decisions. And it really isn't "quite a lot of work". Changing "Rank2Types" to "RankNTypes" is hardly any work at all. -Brent

On Fri, Oct 19, 2012 at 11:49 AM, Simon Peyton-Jones
Dear maintainers of****
bytestring****
cabal****
vector****
time****
dph
Hi, Simon - How did you come up with this list? It is missing the vast majority of users of Rank2Types. Most people embed language pragmas directly into the source files that use them, so grepping .cabal files is going to massively undercount users of any given feature. Based on repeated recent experience, I expect getting rid of Rank2Types to be another substantial source of make-work for library authors. The GHC upgrade path has been very bumpy indeed recently, and this seems assured to continue that unhappy trend. I respectfully request that you silently retain Rank2Types as a synonym for RankNTypes. Thanks, Bryan.

Based on repeated recent experience, I expect getting rid of Rank2Types to be another substantial source of make-work for library authors. The GHC upgrade path has been very bumpy indeed recently, and this seems assured to continue that unhappy trend. I respectfully request that you silently retain Rank2Types as a synonym for RankNTypes.
Do you mean “silently and forever”? Deprecation simply means that everything continues to work, but you get a little nudge to change. Isn’t that what it’s for? If you treat deprecation as equivalent to error, then there isn’t much point in having it.
It’s possible that making Rank2Types = RankNTypes silently and forever is the right answer. It just doesn’t feel right to me. But I’m not a library author and I don’t feel terribly strongly.
Simon
From: Bryan O'Sullivan [mailto:bos@serpentine.com]
Sent: 22 October 2012 17:06
To: Simon Peyton-Jones
Cc: johan.tibell@gmail.com; Don Stewart; Duncan Coutts; Roman Leshchinskiy; ashley@semantic.org; cabal-devel@haskell.org; Ben Lippmeier; Manuel M T Chakravarty; cvs-ghc@haskell.org
Subject: Re: deprecating
On Fri, Oct 19, 2012 at 11:49 AM, Simon Peyton-Jones

On Mon, Oct 22, 2012 at 9:14 AM, Simon Peyton-Jones
Do you mean “silently and forever”? Deprecation simply means that everything continues to work, but you get a little nudge to change. Isn’t that what it’s for? If you treat deprecation as equivalent to error, then there isn’t much point in having it.
Most people do treat deprecations as errors; having your compilation output warning clean makes you less likely to miss those warnings that are really important. If you look at some widely used languages, like Java, you see that they only deprecate things that are really error prone but avoid deprecations altogether otherwise. When they do deprecate something, they typically don't remove the deprecated entity, ever.
It’s possible that making Rank2Types = RankNTypes silently and forever is the right answer. It just doesn’t feel right to me. But I’m not a library author and I don’t feel terribly strongly.
I think so. -- Johan

On Mon, Oct 22, 2012 at 4:14 PM, Simon Peyton-Jones
Do you mean “silently and forever”?
I think that's what I mean, yes. As Johan notes, many of us run our continuous builds of our packages with -Wall -Werror in order to keep them as clean as possible. Introducing a deprecation thus forces me into some kind of response as my builds all suddenly fail: I can either turn off -Werror for a package, or edit the affected source files. I'm not arguing that the compiler shouldn't be improved, but seemingly trivial changes like the above deprecation can and do now come with surprisingly expensive consequences for users of the compiler. I noted that when catch got dropped from Prelude during the 7.6 cycle, it took me almost two weeks of spare time to fix up all of the build errors in packages I wrote, and somewhat longer to sort out build problems in packages maintained by other people. Some breaking changes are clearly worthwhile; others are clearly not; and there are plenty more on the continuum between the two. This particular one seems closer to the "clearly not worth it" end of the spectrum: not trivially obviously a bad idea, but in my opinion definitely not worth the disruption it threatens.
participants (5)
-
Brent Yorgey
-
Bryan O'Sullivan
-
Ian Lynagh
-
Johan Tibell
-
Simon Peyton-Jones