[commit: ghc] wip/hasfield: Remove redundant imports (3aaae48)

git at git.haskell.org git at git.haskell.org
Sun Oct 9 13:32:33 UTC 2016


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

On branch  : wip/hasfield
Link       : http://ghc.haskell.org/trac/ghc/changeset/3aaae48d195e56ce0b7fbaf8660947fffd9de612/ghc

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

commit 3aaae48d195e56ce0b7fbaf8660947fffd9de612
Author: Adam Gundry <adam at well-typed.com>
Date:   Sun Oct 9 13:04:08 2016 +0100

    Remove redundant imports


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

3aaae48d195e56ce0b7fbaf8660947fffd9de612
 compiler/typecheck/TcExpr.hs     | 2 --
 compiler/typecheck/TcInteract.hs | 9 ++-------
 libraries/base/GHC/Records.hs    | 2 --
 3 files changed, 2 insertions(+), 11 deletions(-)

diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs
index 4cbe50e..2411182 100644
--- a/compiler/typecheck/TcExpr.hs
+++ b/compiler/typecheck/TcExpr.hs
@@ -33,7 +33,6 @@ import TcSimplify       ( simplifyInfer, InferMode(..) )
 import FamInst          ( tcGetFamInstEnvs, tcLookupDataFamInst )
 import FamInstEnv       ( FamInstEnvs )
 import RnEnv            ( addUsedGRE, addNameClashErrRn
-                        , lookupOccRn
                         , unknownSubordinateErr )
 import TcEnv
 import TcArrows
@@ -62,7 +61,6 @@ import TysWiredIn
 import TysPrim( intPrimTy )
 import PrimOp( tagToEnumKey )
 import PrelNames
-import MkId ( proxyHashId )
 import DynFlags
 import SrcLoc
 import Util
diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs
index a2222ee..aac0089 100644
--- a/compiler/typecheck/TcInteract.hs
+++ b/compiler/typecheck/TcInteract.hs
@@ -9,7 +9,7 @@ module TcInteract (
 
 #include "HsVersions.h"
 
-import BasicTypes ( infinity, IntWithInf, intGtLimit, Origin(Generated) )
+import BasicTypes ( infinity, IntWithInf, intGtLimit )
 import HsTypes ( HsIPName(..) )
 import TcCanonical
 import TcFlatten
@@ -29,7 +29,7 @@ import PrelNames ( knownNatClassName, knownSymbolClassName,
                    heqTyConKey, ipClassKey )
 import TysWiredIn ( typeNatKind, typeSymbolKind, heqDataCon,
                     coercibleDataCon )
-import TysPrim    ( eqPrimTyCon, eqReprPrimTyCon, mkProxyPrimTy )
+import TysPrim    ( eqPrimTyCon, eqReprPrimTyCon )
 import Id( idType, isNaughtyRecordSelector )
 import CoAxiom ( Eqn, CoAxiom(..), CoAxBranch(..), fromBranches )
 import Class
@@ -41,11 +41,6 @@ import FamInst
 import FamInstEnv
 import Unify ( tcUnifyTyWithTFs )
 
-import HsBinds ( emptyLocalBinds )
-import HsExpr
-import HsPat ( Pat(WildPat) )
-import HsUtils ( mkHsWrap )
-
 import TcEvidence
 import Outputable
 
diff --git a/libraries/base/GHC/Records.hs b/libraries/base/GHC/Records.hs
index 9a3e654..dc1cfc4 100644
--- a/libraries/base/GHC/Records.hs
+++ b/libraries/base/GHC/Records.hs
@@ -27,7 +27,5 @@ module GHC.Records
        ( HasField(..)
        ) where
 
-import GHC.Base ( Symbol )
-
 class HasField (x :: k) r a | x r -> a where
   fromLabel :: r -> a



More information about the ghc-commits mailing list