[commit: ghc] wip/orf-reboot: Fix redundant import warnings, involving gratuitous CPP thanks to FTP (389793e)

git at git.haskell.org git at git.haskell.org
Fri Mar 27 15:47:14 UTC 2015


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/orf-reboot
Link       : http://ghc.haskell.org/trac/ghc/changeset/389793e6f1745e1fe6afb82aa598b5bdc2c737e4/ghc

>---------------------------------------------------------------

commit 389793e6f1745e1fe6afb82aa598b5bdc2c737e4
Author: Adam Gundry <adam at well-typed.com>
Date:   Fri Mar 20 15:28:09 2015 +0000

    Fix redundant import warnings, involving gratuitous CPP thanks to FTP


>---------------------------------------------------------------

389793e6f1745e1fe6afb82aa598b5bdc2c737e4
 compiler/basicTypes/FieldLabel.hs | 9 +++++----
 compiler/hsSyn/HsPat.hs           | 1 -
 compiler/hsSyn/HsUtils.hs         | 5 ++++-
 compiler/main/InteractiveEval.hs  | 1 -
 compiler/rename/RnEnv.hs          | 3 ---
 compiler/rename/RnNames.hs        | 6 ++++--
 compiler/typecheck/TcExpr.hs      | 2 --
 compiler/typecheck/TcRnTypes.hs   | 1 -
 compiler/types/TyCon.hs           | 1 -
 9 files changed, 13 insertions(+), 16 deletions(-)

diff --git a/compiler/basicTypes/FieldLabel.hs b/compiler/basicTypes/FieldLabel.hs
index d273028..9af7f88 100644
--- a/compiler/basicTypes/FieldLabel.hs
+++ b/compiler/basicTypes/FieldLabel.hs
@@ -39,7 +39,7 @@ dfuns/axioms differ.  Each FieldLabel value is unique to its type
 constructor.
 -}
 
-{-# LANGUAGE DeriveFunctor, DeriveFoldable, DeriveTraversable #-}
+{-# LANGUAGE CPP, DeriveFunctor, DeriveFoldable, DeriveTraversable #-}
 
 module FieldLabel ( FieldLabelString
                   , FieldLabelEnv
@@ -53,11 +53,12 @@ import Name
 
 import Binary
 import FastString
-import FastStringEnv
 import Outputable
 
-import Data.Foldable
-import Data.Traversable
+#if __GLASGOW_HASKELL__ < 709
+import Data.Foldable ( Foldable )
+import Data.Traversable ( Traversable )
+#endif
 
 -- | Field labels are just represented as strings;
 -- they are not necessarily unique (even within a module)
diff --git a/compiler/hsSyn/HsPat.hs b/compiler/hsSyn/HsPat.hs
index 2c72855..54fb472 100644
--- a/compiler/hsSyn/HsPat.hs
+++ b/compiler/hsSyn/HsPat.hs
@@ -48,7 +48,6 @@ import Var
 import ConLike
 import DataCon
 import TyCon
-import FieldLabel
 import Outputable
 import Type
 import RdrName
diff --git a/compiler/hsSyn/HsUtils.hs b/compiler/hsSyn/HsUtils.hs
index 2580844..6206a78 100644
--- a/compiler/hsSyn/HsUtils.hs
+++ b/compiler/hsSyn/HsUtils.hs
@@ -101,10 +101,13 @@ import Bag
 import Outputable
 
 import Data.Either
-import Data.Foldable ( foldMap )
 import Data.Function
 import Data.List
+
+#if __GLASGOW_HASKELL__ < 709
+import Data.Foldable ( foldMap )
 import Data.Monoid ( mempty, mappend )
+#endif
 
 {-
 ************************************************************************
diff --git a/compiler/main/InteractiveEval.hs b/compiler/main/InteractiveEval.hs
index ba1f2f7..ff588e1 100644
--- a/compiler/main/InteractiveEval.hs
+++ b/compiler/main/InteractiveEval.hs
@@ -58,7 +58,6 @@ import Name             hiding ( varName )
 import NameSet
 import Avail
 import RdrName
-import TcRnMonad
 import VarSet
 import VarEnv
 import ByteCodeInstr
diff --git a/compiler/rename/RnEnv.hs b/compiler/rename/RnEnv.hs
index 236b753..756b961 100644
--- a/compiler/rename/RnEnv.hs
+++ b/compiler/rename/RnEnv.hs
@@ -53,8 +53,6 @@ import RdrName
 import HscTypes
 import TcEnv
 import TcRnMonad
-import Id
-import Var
 import Name
 import NameSet
 import NameEnv
@@ -63,7 +61,6 @@ import Module
 import ConLike
 import DataCon
 import TyCon
-import CoAxiom
 import PrelNames        ( mkUnboundName, isUnboundName, rOOT_MAIN, forall_tv_RDR )
 import ErrUtils         ( MsgDoc )
 import BasicTypes       ( Fixity(..), FixityDirection(..), minPrecedence, defaultFixity )
diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs
index b42d4bd..b03d4cd 100644
--- a/compiler/rename/RnNames.hs
+++ b/compiler/rename/RnNames.hs
@@ -23,7 +23,6 @@ import TcEnv
 import RnEnv
 import RnHsDoc          ( rnHsDoc )
 import LoadIface        ( loadSrcInterface )
-import IfaceEnv
 import TcRnMonad
 import PrelNames
 import Module
@@ -47,13 +46,16 @@ import ListSetOps
 import Control.Monad
 import Data.Map         ( Map )
 import qualified Data.Map as Map
-import Data.Monoid      ( mconcat )
 import Data.Ord         ( comparing )
 import Data.List        ( partition, (\\), find, sortBy )
 import qualified Data.Set as Set
 import System.FilePath  ((</>))
 import System.IO
 
+#if __GLASGOW_HASKELL__ < 709
+import Data.Monoid      ( mconcat )
+#endif
+
 {-
 ************************************************************************
 *                                                                      *
diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs
index dde5467..9d6980a 100644
--- a/compiler/typecheck/TcExpr.hs
+++ b/compiler/typecheck/TcExpr.hs
@@ -50,8 +50,6 @@ import Var
 import VarSet
 import VarEnv
 import TysWiredIn
-import TysPrim
-import MkId
 import TysPrim( intPrimTy, addrPrimTy )
 import PrimOp( tagToEnumKey )
 import PrelNames
diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs
index 44578c9..ccdfe0c 100644
--- a/compiler/typecheck/TcRnTypes.hs
+++ b/compiler/typecheck/TcRnTypes.hs
@@ -106,7 +106,6 @@ import Type
 import CoAxiom  ( Role )
 import Class    ( Class )
 import TyCon    ( TyCon )
-import CoAxiom
 import ConLike  ( ConLike(..) )
 import DataCon  ( DataCon, FieldLabel, dataConUserType, dataConOrigArgTys )
 import PatSyn   ( PatSyn, patSynType )
diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs
index 8a38e05..8caef1e 100644
--- a/compiler/types/TyCon.hs
+++ b/compiler/types/TyCon.hs
@@ -112,7 +112,6 @@ import CoAxiom
 import PrelNames
 import Maybes
 import Outputable
-import FastString
 import FastStringEnv
 import FieldLabel
 import Constants



More information about the ghc-commits mailing list