[commit: ghc] master: Remove dead code (289be61)

Simon Peyton Jones simonpj at microsoft.com
Wed Jun 12 10:44:27 CEST 2013


Repository : http://darcs.haskell.org/ghc.git/

On branch  : master

https://github.com/ghc/ghc/commit/289be612b4e823ea705a00c45daa174549d38e4b

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

commit 289be612b4e823ea705a00c45daa174549d38e4b
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Wed Jun 12 09:43:58 2013 +0100

    Remove dead code

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

 compiler/typecheck/TcSMonad.lhs     | 12 ------------
 compiler/typecheck/TcUnify.lhs      | 21 +--------------------
 compiler/typecheck/TcUnify.lhs-boot |  5 +----
 3 files changed, 2 insertions(+), 36 deletions(-)

diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs
index dd5b561..930444a 100644
--- a/compiler/typecheck/TcSMonad.lhs
+++ b/compiler/typecheck/TcSMonad.lhs
@@ -81,8 +81,6 @@ module TcSMonad (
     newFlexiTcSTy, instFlexiTcS, instFlexiTcSHelperTcS,
     cloneMetaTyVar,
 
-    mkKindErrorCtxtTcS,
-
     Untouchables, isTouchableMetaTyVarTcS, isFilledMetaTyVar_maybe,
     zonkTyVarsAndFV,
 
@@ -110,7 +108,6 @@ import qualified TcRnMonad as TcM
 import qualified TcMType as TcM
 import qualified TcEnv as TcM 
        ( checkWellStaged, topIdLvl, tcGetDefaultTys )
-import {-# SOURCE #-} qualified TcUnify as TcM ( mkKindErrorCtxt )
 import Kind
 import TcType
 import DynFlags
@@ -147,15 +144,6 @@ import Digraph
 #endif
 \end{code}
 
-
-\begin{code}
-mkKindErrorCtxtTcS :: Type -> Kind 
-                   -> Type -> Kind 
-                   -> ErrCtxt
-mkKindErrorCtxtTcS ty1 ki1 ty2 ki2
-  = (False,TcM.mkKindErrorCtxt ty1 ty2 ki1 ki2)
-\end{code}
-
 %************************************************************************
 %*									*
 %*                            Worklists                                *
diff --git a/compiler/typecheck/TcUnify.lhs b/compiler/typecheck/TcUnify.lhs
index 4749d0c..1053340 100644
--- a/compiler/typecheck/TcUnify.lhs
+++ b/compiler/typecheck/TcUnify.lhs
@@ -31,11 +31,7 @@ module TcUnify (
   matchExpectedAppTy, 
   matchExpectedFunTys,
   matchExpectedFunKind,
-  wrapFunResCoercion,
-
-  --------------------------------
-  -- Errors
-  mkKindErrorCtxt
+  wrapFunResCoercion
 
   ) where
 
@@ -1200,19 +1196,4 @@ uUnboundKVar kv1 non_var_k2
        ; case occurCheckExpand dflags kv1 k2b of
            OC_OK k2c -> do { writeMetaTyVar kv1 k2c; return (Just EQ) }
            _         -> return Nothing }
-
-mkKindErrorCtxt :: Type -> Type -> Kind -> Kind -> TidyEnv -> TcM (TidyEnv, SDoc)
-mkKindErrorCtxt ty1 ty2 k1 k2 env0
-  = let (env1, ty1') = tidyOpenType env0 ty1
-        (env2, ty2') = tidyOpenType env1 ty2
-        (env3, k1' ) = tidyOpenKind env2 k1
-        (env4, k2' ) = tidyOpenKind env3 k2
-    in do ty1 <- zonkTcType ty1'
-          ty2 <- zonkTcType ty2'
-          k1  <- zonkTcKind k1'
-          k2  <- zonkTcKind k2'
-          return (env4, 
-                  vcat [ ptext (sLit "Kind incompatibility when matching types xx:")
-                       , nest 2 (vcat [ ppr ty1 <+> dcolon <+> ppr k1
-                                      , ppr ty2 <+> dcolon <+> ppr k2 ]) ])
 \end{code}
diff --git a/compiler/typecheck/TcUnify.lhs-boot b/compiler/typecheck/TcUnify.lhs-boot
index aa93536..35a7155 100644
--- a/compiler/typecheck/TcUnify.lhs-boot
+++ b/compiler/typecheck/TcUnify.lhs-boot
@@ -1,14 +1,11 @@
 \begin{code}
 module TcUnify where
-import TcType     ( TcTauType, Type, Kind )
-import VarEnv     ( TidyEnv )
+import TcType     ( TcTauType )
 import TcRnTypes  ( TcM )
 import TcEvidence ( TcCoercion )
-import Outputable ( SDoc )
 
 -- This boot file exists only to tie the knot between
 --              TcUnify and Inst
 
 unifyType :: TcTauType -> TcTauType -> TcM TcCoercion
-mkKindErrorCtxt :: Type -> Type -> Kind -> Kind -> TidyEnv -> TcM (TidyEnv, SDoc)
 \end{code}





More information about the ghc-commits mailing list