ANNOUNCE: GHC 7.0.1 Release Candidate 2

Isaac Dupree ml at isaac.cedarswampstudios.org
Sat Oct 30 01:38:16 EDT 2010


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.

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)

-Isaac


More information about the Glasgow-haskell-users mailing list