[commit: ghc] wip/orf-reboot: Get rid of dead code (9915fb4)

git at git.haskell.org git at git.haskell.org
Fri Mar 27 15:46:52 UTC 2015


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

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

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

commit 9915fb48a08e2ebfb4eda33f653f8241bea2d23f
Author: Adam Gundry <adam at well-typed.com>
Date:   Mon Mar 2 11:24:05 2015 +0000

    Get rid of dead code


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

9915fb48a08e2ebfb4eda33f653f8241bea2d23f
 compiler/typecheck/TcType.hs | 9 ---------
 compiler/types/Type.hs-boot  | 2 --
 2 files changed, 11 deletions(-)

diff --git a/compiler/typecheck/TcType.hs b/compiler/typecheck/TcType.hs
index 1def1fe..d6fadc7 100644
--- a/compiler/typecheck/TcType.hs
+++ b/compiler/typecheck/TcType.hs
@@ -58,7 +58,6 @@ module TcType (
   tcInstHeadTyNotSynonym, tcInstHeadTyAppAllTyVars,
   tcGetTyVar_maybe, tcGetTyVar, nextRole,
   tcSplitSigmaTy, tcDeepSplitSigmaTy_maybe,
-  tcSplitRecordsArgs,
 
   ---------------------------------
   -- Predicates.
@@ -172,7 +171,6 @@ import VarEnv
 import PrelNames
 import TysWiredIn
 import BasicTypes
-import FieldLabel
 import Util
 import Maybes
 import ListSetOps
@@ -1106,13 +1104,6 @@ tcInstHeadTyAppAllTyVars ty
     get_tv (TyVarTy tv)  = Just tv      -- through synonyms
     get_tv _             = Nothing
 
-tcSplitRecordsArgs :: [Type] -> Maybe (FieldLabelString, TyCon, [Type])
-tcSplitRecordsArgs (r:n:_)
-  | Just lbl <- isStrLitTy n
-  , Just (tc, tys) <- tcSplitTyConApp_maybe r
-  = Just (lbl, tc, tys)
-tcSplitRecordsArgs _ = Nothing
-
 tcEqKind :: TcKind -> TcKind -> Bool
 tcEqKind = tcEqType
 
diff --git a/compiler/types/Type.hs-boot b/compiler/types/Type.hs-boot
index 582b113..587454e 100644
--- a/compiler/types/Type.hs-boot
+++ b/compiler/types/Type.hs-boot
@@ -7,5 +7,3 @@ isPredTy :: Type -> Bool
 typeKind :: Type -> Kind
 substKiWith :: [KindVar] -> [Kind] -> Kind -> Kind
 eqKind :: Kind -> Kind -> Bool
-
-cmpType :: Type -> Type -> Ordering



More information about the ghc-commits mailing list