ANNOUNCE: GHC 7.0.1 Release Candidate 2
Bas van Dijk
v.dijk.bas at gmail.com
Fri Oct 29 20:19:48 EDT 2010
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 #-}
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 )
main :: IO ()
main = do _ <- return (1 :: Int)
return ()
Is this intentional?
Regards,
Bas
More information about the Glasgow-haskell-users
mailing list