ANNOUNCE: GHC 7.0.1 Release Candidate 2

Bas van Dijk v.dijk.bas at gmail.com
Sat Oct 30 04:43:33 EDT 2010


On Sat, Oct 30, 2010 at 7:38 AM, Isaac Dupree
<ml at isaac.cedarswampstudios.org> wrote:
> On 10/29/10 20:19, Bas van Dijk wrote:
>>
>> I'm not sure this is in rc2 since I'm using the latest ghc-HEAD
>> (7.1.20101029).
>>
>> In ghc<  7 you needed to import symbols like fromInteger, (>>=) and
>> fail when you used them indirectly. For example when using integer
>> literals or do-notation.
>>
>> I noticed that in my ghc-HEAD this isn't needed anymore:
>>
>> {-# OPTIONS_GHC -Wall #-}
>> {-# LANGUAGE NoImplicitPrelude #-}
>
> Yes, in HEAD only, NoImplicitPrelude no longer implies RebindableSyntax.

Thanks, for the explanation.

> http://darcs.haskell.org/cgi-bin/darcsweb.cgi?r=ghc;a=darcs_commitdiff;h=20101022143400-1287e-746a83b4269744bb54177753c8ff67bec542b46c.gz
>
>> import Control.Monad ( return )
>> import System.IO     ( IO )
>> import Data.Int
>>
>> -- Only needed for ghc<  7.
>> -- In fact, the following gives a redundancy warning in ghc-7:
>> import Control.Monad ( (>>=), fail )
>> import Prelude       ( fromInteger )
>
> However, a redundancy warning sounds wrong (or at least confusing).  An
> "unused import" warning seems more appropriate to me, although it's a bit of
> a grey area.  If you remove LANGUAGE NoImplicitPrelude from the module, what
> warning do you get? (maybe test that in HEAD as well as 6.12 or so)

Without NoImplicitPrelude:

$ /usr/bin/ghc-6.12.3 --make GHC7.hs -fforce-recomp
[1 of 1] Compiling Main             ( GHC7.hs, GHC7.o )

GHC7.hs:9:0:
    Warning: The import of `Control.Monad' is redundant
               except perhaps to import instances from `Control.Monad'
             To import instances alone, use: import Control.Monad()

GHC7.hs:10:0:
    Warning: The import of `Prelude' is redundant
               except perhaps to import instances from `Prelude'
             To import instances alone, use: import Prelude()

Which is to be expected because the Prelude is imported implicitly.

I get the same warnings in ghc-HEAD with and without NoImplicitPrelude:

$ ~/ghc-HEAD/bin/ghc-7.1.20101029 --make GHC7.hs -Wall -fforce-recomp
[1 of 1] Compiling Main             ( GHC7.hs, GHC7.o )

GHC7.hs:9:1:
    Warning: The import of `Control.Monad' is redundant
               except perhaps to import instances from `Control.Monad'
             To import instances alone, use: import Control.Monad()

GHC7.hs:10:1:
    Warning: The import of `Prelude' is redundant
               except perhaps to import instances from `Prelude'
             To import instances alone, use: import Prelude()

Thanks,

Bas


More information about the Glasgow-haskell-users mailing list