Re: Proposal: NoImplicitPreludeImport

2013-06-04 Thread Simon Marlow

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#Backwardscompatibility
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


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Proposal: NoImplicitPreludeImport

2013-06-04 Thread Ian Lynagh
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/

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Proposal: NoImplicitPreludeImport

2013-06-04 Thread 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

import Foo as Prelude.XYZ


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


Re: Proposal: NoImplicitPreludeImport

2013-06-04 Thread Manuel M T Chakravarty
Ian Lynagh i...@well-typed.com:
 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




___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime