Proposal: NoImplicitPreludeImport

Dear Haskellers, I have made a wiki page describing a new proposal, NoImplicitPreludeImport, which I intend to propose for Haskell 2014: http://hackage.haskell.org/trac/haskell-prime/wiki/NoImplicitPreludeImport What do you think? Thanks to the folks on #ghc who gave some comments on an earlier draft. Thanks Ian -- Ian Lynagh, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/

On 28 May 2013, at 16:23, Ian Lynagh
Dear Haskellers,
I have made a wiki page describing a new proposal, NoImplicitPreludeImport, which I intend to propose for Haskell 2014: http://hackage.haskell.org/trac/haskell-prime/wiki/NoImplicitPreludeImport
What do you think?
I particularly like "It would also allow computer science courses to more easily use a simplified, more monomorphic Prelude replacement for teaching (or, when asking students to implement basic functions like length as exercises, no Prelude at all)." Simon T.
Thanks Ian -- Ian Lynagh, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime
Simon Thompson | Professor of Logic and Computation School of Computing | University of Kent | Canterbury, CT2 7NF, UK s.j.thompson@kent.ac.uk | M +44 7986 085754 | W www.cs.kent.ac.uk/~sjt

I'm definitely in favor of having the *option* to shut off the import of
the Prelude without entangling the notion of overriding all of the
desugarings.
I do, however, feel that removing the Prelude from base is a rather strong
step, which hasn't seen much support.
On Tue, May 28, 2013 at 11:23 AM, Ian Lynagh
Dear Haskellers,
I have made a wiki page describing a new proposal, NoImplicitPreludeImport, which I intend to propose for Haskell 2014:
http://hackage.haskell.org/trac/haskell-prime/wiki/NoImplicitPreludeImport
What do you think?
Thanks to the folks on #ghc who gave some comments on an earlier draft.
Thanks Ian -- Ian Lynagh, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

On Tue, May 28, 2013 at 11:41:44AM -0400, Edward Kmett wrote:
I'm definitely in favor of having the *option* to shut off the import of the Prelude without entangling the notion of overriding all of the desugarings.
I do, however, feel that removing the Prelude from base is a rather strong step, which hasn't seen much support.
Just to clarify: This proposal is to stop importing the module implicitly, not to actually remove the module. Thanks Ian -- Ian Lynagh, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/

Yes, but that leaves the an objection I have to this proposal requiring me
personally to write an extra 1691 import lines -- based on the contents of
my local development folder, to just get back up to par with the status quo.
As a flag I can turn on in a package to get finer grained control? I'm
totally for it!
As a source of *mandatory* boilerplate at the head of each module? It
doesn't strike me as a good trade-off.
On Tue, May 28, 2013 at 11:52 AM, Ian Lynagh
On Tue, May 28, 2013 at 11:41:44AM -0400, Edward Kmett wrote:
I'm definitely in favor of having the *option* to shut off the import of the Prelude without entangling the notion of overriding all of the desugarings.
I do, however, feel that removing the Prelude from base is a rather strong step, which hasn't seen much support.
Just to clarify: This proposal is to stop importing the module implicitly, not to actually remove the module.
Thanks Ian -- Ian Lynagh, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

On Tue, May 28, 2013 at 8:23 AM, Ian Lynagh
Dear Haskellers,
I have made a wiki page describing a new proposal, NoImplicitPreludeImport, which I intend to propose for Haskell 2014:
http://hackage.haskell.org/trac/haskell-prime/wiki/NoImplicitPreludeImport
What do you think?
-1 for me. Breaking every single Haskell module for some namespace reorganization doesn't seem worth it. I don't think alternative Prelused (one of the justifications) is a good idea to begin with, as programmers will have to first understand which particular version of e.g. map this module uses, instead of knowing it's the same one as every other module uses. Changes like this will likely cause years worth of pain e.g. see the Python 2/Python 3 failure. The likely practical result of this is that every module will now read: module M where #if MIN_VERSION_base(x,y,z) import Prelude #else import Data.Num import Control.Monad ... #endif for the next 3 years or so. -- Johan

On Tue, May 28, 2013 at 08:58:29AM -0700, Johan Tibell wrote:
The likely practical result of this is that every module will now read:
module M where
#if MIN_VERSION_base(x,y,z) import Prelude #else import Data.Num import Control.Monad ... #endif
for the next 3 years or so.
Not so. First of all, if Prelude is not removed then you can just write import Prelude But even this is not necessary during the transition period: see http://hackage.haskell.org/trac/haskell-prime/wiki/NoImplicitPreludeImport#B... for a way that backwards compatibility can be maintained, with additional imports not being needed until code migrates to the split-base packages. Thanks Ian -- Ian Lynagh, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/

On 28/05/13 17:08, Ian Lynagh wrote:
On Tue, May 28, 2013 at 08:58:29AM -0700, Johan Tibell wrote:
The likely practical result of this is that every module will now read:
module M where
#if MIN_VERSION_base(x,y,z) import Prelude #else import Data.Num import Control.Monad ... #endif
for the next 3 years or so.
Not so. First of all, if Prelude is not removed then you can just write import Prelude
But even this is not necessary during the transition period: see http://hackage.haskell.org/trac/haskell-prime/wiki/NoImplicitPreludeImport#B... for a way that backwards compatibility can be maintained, with additional imports not being needed until code migrates to the split-base packages.
Hardly anybody uses haskell98 or haskell2010, so we would still have a backwards compatibility problem. (plus I'm not keen on a magic language feature that turns on when you have a particular package enabled, even if it is only temporary). I'm firmly against this change. The Prelude is an essential baseline vocabulary that everyone can use when talking about Haskell and sharing snippets of code. Without that baseline vocabulary, *everything* has to be qualified with an import. The language report itself has a giant 'import Prelude' around it - many of the code translations used to specify the meaning of syntactic sugar use Prelude functions. Others have raised the backwards compatibility issue, and I completely agree on that front too - we're way past the point where we can break that much code to make a small improvement in language consistency. There's plenty of room for making the Prelude have a more sensible and modern coverage of library functions, I'd rather see us pursue this instead. Cheers, Simon

On Tue, Jun 04, 2013 at 01:06:25PM +0100, Simon Marlow wrote:
Hardly anybody uses haskell98 or haskell2010, so we would still have a backwards compatibility problem.
I meant 'base' to be included in 'these packages'; I've clarified the wiki page. Thanks Ian -- Ian Lynagh, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/

On Tue, May 28, 2013 at 8:23 AM, Ian Lynagh
I have made a wiki page describing a new proposal, NoImplicitPreludeImport, which I intend to propose for Haskell 2014:
http://hackage.haskell.org/trac/haskell-prime/wiki/NoImplicitPreludeImport
What do you think?
This is a truly terrible idea. It purports to be a step towards fixing the backwards compatibility problem, but of course it breaks every module ever written along the way, and it means that packages that try to be compatible across multiple versions of GHC will need mandatory CPP #ifdefs for years to come. The current model that we have, of opting out of the Prelude explicitly, provides the same capability without damning the entire Haskell world to a months-long edit-recompile cycle. Of course being able to evolve the language and its libraries is important, but experience from other languages (e.g. Python, Ruby) offer the lesson that ignoring the "if it ain't broke, don't fix it" rule is very perilous: it risks hobbling language growth and development for years. This proposal takes that rule and maximally flouts it, while offering scant payoff in return.

On Tue, May 28, 2013 at 8:23 AM, Ian Lynagh
wrote: I have made a wiki page describing a new proposal, NoImplicitPreludeImport, which I intend to propose for Haskell 2014:
Bryan O'Sullivan wrote: prime/wiki/NoImplicitPreludeImport
What do you think?
This is a truly terrible idea.
It purports to be a step towards fixing the backwards compatibility problem, but of course it breaks every module ever written along the way, and it means that packages that try to be compatible across multiple versions of GHC will need mandatory CPP #ifdefs for years to come.
I think it need not necessarily come to that. If we do this right, then adding a line extensions: ImplicitPrelude to a project's cabal file should be enough to get all existing code to compile, as a first step. The question is what comes after that? Suppose you start adapting a package to the new standard. You delete the above extensions line in the cabal file and add import Prelude to all modules that need it (most will). This should still be compatible with old compiler/language versions. Now, occasionally, you will find that what you actually need to import is in just one or two of these new modules, so you replace some import Prelude with import Data.Num -- etc and at this point the code no longer compiles with old compiler/language versions. This is bad. #ifdef is not a nice solution, but there is better one: We add a *compatibility package* (named e.g. "prelude") that contains all the new modules that are needed (in addition to already existing ones in base) to fully replace the Prelude. We also add some extra cabal magic that "knows" which version of prelude the old versions of base need to make them compatible with new packages that use the Prelude-replacement modules. The rules can be hard-coded into cabal and will be retained forever (at least for a long time). This means that all you have to do if you have an old ghc installation is to cabal install cabal cabal-install and then you can cabal install foo even if foo is already converted to the new Prelude-less style, because the new cabal will add a silent dependency of (an old) base on the prelude package. I think in order for this to actually work, the compatibility package would in turn have to depend on the installed version of base and the Prelude- replacement modules inside it would have to actually re-export everything from the (old, installed) Prelude. It probably makes sense to create several versions of the prelude package, one for every supported version of base (ideally with the same version number to avoid confusion, adding a 5th number for bug-fixes). For instance base versions that appear in past Haskell Platforms could be supported in this way. The circular dependency base-4.0.0.2 -> prelude-4.0.0.2.* -> base-4.0.0.2 -> etc must of course be handled specially by the new cabal. Or, instead of adding an implicit base-4.0.0.2 -> prelude-4.0.0.2.* dependency, cabal would -- depending on the installed version of base -- add a global constraint that adds the correct prelude package to all builds. BTW, I think this could be a general method to "backward fix" compatibility problems when re-organising core libraries. And one last caveat: Cabal itself would need to exercise some restraint w.r.t. using new language or library features, since it must be buildable on all supported language/compiler versions for this idea to work. Cheers -- Ben Franksen () ascii ribbon campaign - against html e-mail /\ www.asciiribbon.org - against proprietary attachm€nts

On 29/05/2013, at 9:02 AM, Ben Franksen wrote:
Bryan O'Sullivan wrote:
I have made a wiki page describing a new proposal, NoImplicitPreludeImport, which I intend to propose for Haskell 2014:
http://hackage.haskell.org/trac/haskell-prime/wiki/NoImplicitPreludeImport
What do you think?
This is a truly terrible idea.
It purports to be a step towards fixing the backwards compatibility problem, but of course it breaks every module ever written along the way, and it means that packages that try to be compatible across multiple versions of GHC will need mandatory CPP #ifdefs for years to come.
I think it need not necessarily come to that. If we do this right, then adding a line
extensions: ImplicitPrelude
You could handle this more generally by implementing a compiler flag that causes modules to be imported. We've already got "-package P" for exposing packages, we could add "-module M" for exposing modules. When compiling with a Haskell2014 compiler just add the "-module Prelude" flag to your Makefile/.cabal file. Ben.

I agree with Bryan. Such an invasive change should have a great payoff.
Simon Marlow (in a different discussion) proposed the following (IMO much better) idea:
If a module contains an import of the form
import Prelude.XYZ
then it also automatically uses the NoImplicitPrelude language pragma. Otherwise, the Prelude remains to be implicitly defined as before.
This simplifies using an alternative Prelude with no cost for modules that do not make use of that feature.
Manuel
Bryan O'Sullivan
On Tue, May 28, 2013 at 8:23 AM, Ian Lynagh
wrote: I have made a wiki page describing a new proposal, NoImplicitPreludeImport, which I intend to propose for Haskell 2014: http://hackage.haskell.org/trac/haskell-prime/wiki/NoImplicitPreludeImport What do you think?
This is a truly terrible idea.
It purports to be a step towards fixing the backwards compatibility problem, but of course it breaks every module ever written along the way, and it means that packages that try to be compatible across multiple versions of GHC will need mandatory CPP #ifdefs for years to come.
The current model that we have, of opting out of the Prelude explicitly, provides the same capability without damning the entire Haskell world to a months-long edit-recompile cycle.
Of course being able to evolve the language and its libraries is important, but experience from other languages (e.g. Python, Ruby) offer the lesson that ignoring the "if it ain't broke, don't fix it" rule is very perilous: it risks hobbling language growth and development for years. This proposal takes that rule and maximally flouts it, while offering scant payoff in return. _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

On Tue, Jun 04, 2013 at 01:15:58PM +1000, Manuel M T Chakravarty wrote:
If a module contains an import of the form
import Prelude.XYZ
then it also automatically uses the NoImplicitPrelude language pragma. Otherwise, the Prelude remains to be implicitly defined as before.
What about these?: import Prelude.XYZ as Foo import Foo as Prelude.XYZ Thanks Ian -- Ian Lynagh, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/

Ian Lynagh
On Tue, Jun 04, 2013 at 01:15:58PM +1000, Manuel M T Chakravarty wrote:
If a module contains an import of the form
import Prelude.XYZ
then it also automatically uses the NoImplicitPrelude language pragma. Otherwise, the Prelude remains to be implicitly defined as before.
What about these?:
import Prelude.XYZ as Foo
In that case, I think, we should also have NoImplicitPrelude, but in case of
import qualified Prelude.XYZ as Foo
they might to explicitly want to avoid clashes with the implicit Prelude. This would be an argument to not have NoImplicitPrelude in this case. On the other hand, simpler is better; so, maybe it shouldn't depend on the way a 'Prelude.XYZ' module is imported and we should use NoImplicitPrelude regardless.
import Foo as Prelude.XYZ
I would say that doesn't qualify for having NoImplicitPrelude, but I don't feel strongly about that. Summary ~~~~~~~ If and only if a module has at least one impdecl of the form 'import' ['qualified'] Prelude.XYZ ['as' modid] [impspec] then this implies {-# LANGUAGE NoImplicitPrelude #-}. That is a simple rule with no surprises. Manuel

On 05/06/13 02:53, Manuel M T Chakravarty wrote:
Ian Lynagh
: On Tue, Jun 04, 2013 at 01:15:58PM +1000, Manuel M T Chakravarty wrote:
If a module contains an import of the form
import Prelude.XYZ
then it also automatically uses the NoImplicitPrelude language pragma. Otherwise, the Prelude remains to be implicitly defined as before.
What about these?:
import Prelude.XYZ as Foo
In that case, I think, we should also have NoImplicitPrelude, but in case of
import qualified Prelude.XYZ as Foo
they might to explicitly want to avoid clashes with the implicit Prelude. This would be an argument to not have NoImplicitPrelude in this case. On the other hand, simpler is better; so, maybe it shouldn't depend on the way a 'Prelude.XYZ' module is imported and we should use NoImplicitPrelude regardless.
import Foo as Prelude.XYZ
I would say that doesn't qualify for having NoImplicitPrelude, but I don't feel strongly about that.
Summary ~~~~~~~
If and only if a module has at least one impdecl of the form
'import' ['qualified'] Prelude.XYZ ['as' modid] [impspec]
then this implies {-# LANGUAGE NoImplicitPrelude #-}.
That is a simple rule with no surprises.
Furthermore, this is a direct extension of the current behaviour. Currently: - any import declaration that imports 'Prelude' implies NoImplicitPrelude. Proposed: - any import declaration that imports 'Prelude' or a module beginning 'Prelude.' implies NoImplicitPrelude. It's a tiny generalisation, but a very useful one I think. Cheers, Simon

Hi, Ian Lynagh wrote:
I have made a wiki page describing a new proposal, NoImplicitPreludeImport, which I intend to propose for Haskell 2014: http://hackage.haskell.org/trac/haskell-prime/wiki/NoImplicitPreludeImport
I like the idea of having an ImplicitPreludeImport extensions that can be switched on and off. I'm not sure it should be switched off by default. For Haskell beginners, I think it is most convenient if they can write some interesting programs without any imports. This enables learning some Haskell without learning about modules and imports at all. So I think that beginners want an implicit import of (some) Prelude. (Maybe it would be good if tutorials or lecture notes could specify in a very easy way what Prelude to use exactly. A bit like #lang lines in Racket). Advanced Haskell programmers have long import lists and often long extension lists in their modules anyway, so the additional "import Prelude ()" or "{-# LANGUAGE NoImplicitPrelude #-}" shouldn't hurt them so much. Except that currently, "import Prelude ()" doesn't actually work in practice, because not all Prelude exports are available from other modules. I think this should be fixed independently of this proposal. Tillmann
participants (10)
-
Ben Franksen
-
Ben Lippmeier
-
Bryan O'Sullivan
-
Edward Kmett
-
Ian Lynagh
-
Johan Tibell
-
Manuel M T Chakravarty
-
Simon Marlow
-
Simon Thompson
-
Tillmann Rendel