[commit: ghc] master: Remove typeKind from Type.hs-boot (aeb4bd9)
git at git.haskell.org
git at git.haskell.org
Thu Aug 24 13:40:05 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/aeb4bd958439515e02e6f8f9bb22cf84f7cd7d75/ghc
>---------------------------------------------------------------
commit aeb4bd958439515e02e6f8f9bb22cf84f7cd7d75
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Wed Aug 23 13:58:51 2017 +0100
Remove typeKind from Type.hs-boot
Simple refactoring, reducing unncessary module loops
>---------------------------------------------------------------
aeb4bd958439515e02e6f8f9bb22cf84f7cd7d75
compiler/types/Kind.hs | 4 ++--
compiler/types/TyCoRep.hs | 16 +---------------
compiler/types/Type.hs | 13 +++++++++++++
compiler/types/Type.hs-boot | 3 +--
4 files changed, 17 insertions(+), 19 deletions(-)
diff --git a/compiler/types/Kind.hs b/compiler/types/Kind.hs
index ae11c8a..0d619fc 100644
--- a/compiler/types/Kind.hs
+++ b/compiler/types/Kind.hs
@@ -3,7 +3,7 @@
{-# LANGUAGE CPP #-}
module Kind (
-- * Main data type
- Kind, typeKind,
+ Kind,
-- ** Predicates on Kinds
isLiftedTypeKind, isUnliftedTypeKind,
@@ -20,7 +20,7 @@ module Kind (
#include "HsVersions.h"
-import {-# SOURCE #-} Type ( typeKind, coreView, tcView
+import {-# SOURCE #-} Type ( coreView, tcView
, splitTyConApp_maybe )
import {-# SOURCE #-} DataCon ( DataCon )
diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs
index 8b8a960..0fbcc2c 100644
--- a/compiler/types/TyCoRep.hs
+++ b/compiler/types/TyCoRep.hs
@@ -40,7 +40,6 @@ module TyCoRep (
mkPiTy, mkPiTys,
isLiftedTypeKind, isUnliftedTypeKind,
isCoercionType, isRuntimeRepTy, isRuntimeRepVar,
- isRuntimeRepKindedTy, dropRuntimeRepArgs,
sameVis,
-- * Functions over binders
@@ -141,7 +140,7 @@ import {-# SOURCE #-} Type( isPredTy, isCoercionTy, mkAppTy, mkCastTy
, tyCoVarsOfTypeWellScoped
, tyCoVarsOfTypesWellScoped
, toposortTyVars
- , coreView, typeKind )
+ , coreView )
-- Transitively pulls in a LOT of stuff, better to break the loop
import {-# SOURCE #-} Coercion
@@ -736,23 +735,10 @@ isRuntimeRepTy ty | Just ty' <- coreView ty = isRuntimeRepTy ty'
isRuntimeRepTy (TyConApp tc []) = tc `hasKey` runtimeRepTyConKey
isRuntimeRepTy _ = False
--- | Is this a type of kind RuntimeRep? (e.g. LiftedRep)
-isRuntimeRepKindedTy :: Type -> Bool
-isRuntimeRepKindedTy = isRuntimeRepTy . typeKind
-
-- | Is a tyvar of type 'RuntimeRep'?
isRuntimeRepVar :: TyVar -> Bool
isRuntimeRepVar = isRuntimeRepTy . tyVarKind
--- | Drops prefix of RuntimeRep constructors in 'TyConApp's. Useful for e.g.
--- dropping 'LiftedRep arguments of unboxed tuple TyCon applications:
---
--- dropRuntimeRepArgs [ 'LiftedRep, 'IntRep
--- , String, Int# ] == [String, Int#]
---
-dropRuntimeRepArgs :: [Type] -> [Type]
-dropRuntimeRepArgs = dropWhile isRuntimeRepKindedTy
-
{-
%************************************************************************
%* *
diff --git a/compiler/types/Type.hs b/compiler/types/Type.hs
index f43e0e0..df7333b 100644
--- a/compiler/types/Type.hs
+++ b/compiler/types/Type.hs
@@ -1956,6 +1956,19 @@ isUnliftedType ty
= not (isLiftedType_maybe ty `orElse`
pprPanic "isUnliftedType" (ppr ty <+> dcolon <+> ppr (typeKind ty)))
+-- | Is this a type of kind RuntimeRep? (e.g. LiftedRep)
+isRuntimeRepKindedTy :: Type -> Bool
+isRuntimeRepKindedTy = isRuntimeRepTy . typeKind
+
+-- | Drops prefix of RuntimeRep constructors in 'TyConApp's. Useful for e.g.
+-- dropping 'LiftedRep arguments of unboxed tuple TyCon applications:
+--
+-- dropRuntimeRepArgs [ 'LiftedRep, 'IntRep
+-- , String, Int# ] == [String, Int#]
+--
+dropRuntimeRepArgs :: [Type] -> [Type]
+dropRuntimeRepArgs = dropWhile isRuntimeRepKindedTy
+
-- | Extract the RuntimeRep classifier of a type. For instance,
-- @getRuntimeRep_maybe Int = LiftedRep at . Returns 'Nothing' if this is not
-- possible.
diff --git a/compiler/types/Type.hs-boot b/compiler/types/Type.hs-boot
index 002db72..375c31f 100644
--- a/compiler/types/Type.hs-boot
+++ b/compiler/types/Type.hs-boot
@@ -3,7 +3,7 @@
module Type where
import TyCon
import Var ( TyCoVar )
-import {-# SOURCE #-} TyCoRep( Type, Coercion, Kind )
+import {-# SOURCE #-} TyCoRep( Type, Coercion )
import Util
isPredTy :: Type -> Bool
@@ -13,7 +13,6 @@ mkAppTy :: Type -> Type -> Type
mkCastTy :: Type -> Coercion -> Type
piResultTy :: HasDebugCallStack => Type -> Type -> Type
-typeKind :: Type -> Kind
eqType :: Type -> Type -> Bool
partitionInvisibles :: TyCon -> (a -> Type) -> [a] -> ([a], [a])
More information about the ghc-commits
mailing list