Proposal: NoImplicitPreludeImport

Simon Marlow marlowsd at gmail.com
Tue Jun 4 14:06:25 CEST 2013


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




More information about the Haskell-prime mailing list