[commit: ghc] master: Kill Type.isKindTy in favour of Kind.isKind (same code) (3462534)

git at git.haskell.org git at git.haskell.org
Fri Sep 20 15:52:16 CEST 2013


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/3462534cdd4f84b7aa7fde536741eaa573f4d874/ghc

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

commit 3462534cdd4f84b7aa7fde536741eaa573f4d874
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Fri Sep 20 14:49:36 2013 +0100

    Kill Type.isKindTy in favour of Kind.isKind (same code)


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

3462534cdd4f84b7aa7fde536741eaa573f4d874
 compiler/typecheck/TcGenGenerics.lhs |    3 ++-
 compiler/types/Type.lhs              |    5 +----
 2 files changed, 3 insertions(+), 5 deletions(-)

diff --git a/compiler/typecheck/TcGenGenerics.lhs b/compiler/typecheck/TcGenGenerics.lhs
index 7e2b014..de66588 100644
--- a/compiler/typecheck/TcGenGenerics.lhs
+++ b/compiler/typecheck/TcGenGenerics.lhs
@@ -23,6 +23,7 @@ module TcGenGenerics (canDoGenerics, canDoGenerics1,
 import DynFlags
 import HsSyn
 import Type
+import Kind             ( isKind )
 import TcType
 import TcGenDeriv
 import DataCon
@@ -204,7 +205,7 @@ canDoGenerics tc tc_args
           -- The type arguments should not be instantiated (see #5939)
           -- Data family indices can be instantiated; the `tc_args` here are the
           -- representation tycon args
-              (if (all isTyVarTy (filterOut isKindTy tc_args))
+              (if (all isTyVarTy (filterOut isKind tc_args))
                 then Nothing
                 else Just (tc_name <+> text "must not be instantiated;" <+>
                            text "try deriving `" <> tc_name <+> tc_tys <>
diff --git a/compiler/types/Type.lhs b/compiler/types/Type.lhs
index b2dfe97..7581c19 100644
--- a/compiler/types/Type.lhs
+++ b/compiler/types/Type.lhs
@@ -63,7 +63,7 @@ module Type (
 
         -- ** Predicates on types
         isTypeVar, isKindVar,
-        isTyVarTy, isFunTy, isDictTy, isPredTy, isKindTy,
+        isTyVarTy, isFunTy, isDictTy, isPredTy, 
 
         -- (Lifting and boxity)
         isUnLiftedType, isUnboxedTupleType, isAlgType, isClosedAlgType,
@@ -852,9 +852,6 @@ isPredTy ty = go ty []
     go_k (ForAllTy kv k1) (k2:args) = go_k (substKiWith [kv] [k2] k1) args
     go_k _ _ = False                  -- Typeable * Int :: Constraint
 
-isKindTy :: Type -> Bool
-isKindTy = isSuperKind . typeKind
-
 isClassPred, isEqPred, isIPPred :: PredType -> Bool
 isClassPred ty = case tyConAppTyCon_maybe ty of
     Just tyCon | isClassTyCon tyCon -> True




More information about the ghc-commits mailing list