[commit: ghc] master: Use kind 'Symbol' consistently, rather than kind 'String' (829be06)
Simon Peyton Jones
simonpj at microsoft.com
Fri Jan 25 13:50:31 CET 2013
Repository : ssh://darcs.haskell.org//srv/darcs/ghc
On branch : master
http://hackage.haskell.org/trac/ghc/changeset/829be0669c43ecf57c3a5b8b91e194c8f81bb490
>---------------------------------------------------------------
commit 829be0669c43ecf57c3a5b8b91e194c8f81bb490
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Fri Jan 25 12:49:19 2013 +0000
Use kind 'Symbol' consistently, rather than kind 'String'
>---------------------------------------------------------------
compiler/prelude/PrelNames.lhs | 4 ++--
compiler/prelude/TysWiredIn.lhs | 18 +++++++++---------
compiler/prelude/TysWiredIn.lhs-boot | 2 +-
compiler/typecheck/TcHsType.lhs | 4 ++--
compiler/types/Type.lhs | 4 ++--
5 files changed, 16 insertions(+), 16 deletions(-)
diff --git a/compiler/prelude/PrelNames.lhs b/compiler/prelude/PrelNames.lhs
index 1d3a7f9..261d102 100644
--- a/compiler/prelude/PrelNames.lhs
+++ b/compiler/prelude/PrelNames.lhs
@@ -1411,11 +1411,11 @@ repTyConKey = mkPreludeTyConUnique 155
rep1TyConKey = mkPreludeTyConUnique 156
-- Type-level naturals
-typeNatKindConNameKey, typeStringKindConNameKey,
+typeNatKindConNameKey, typeSymbolKindConNameKey,
typeNatAddTyFamNameKey, typeNatMulTyFamNameKey, typeNatExpTyFamNameKey
:: Unique
typeNatKindConNameKey = mkPreludeTyConUnique 160
-typeStringKindConNameKey = mkPreludeTyConUnique 161
+typeSymbolKindConNameKey = mkPreludeTyConUnique 161
typeNatAddTyFamNameKey = mkPreludeTyConUnique 162
typeNatMulTyFamNameKey = mkPreludeTyConUnique 163
typeNatExpTyFamNameKey = mkPreludeTyConUnique 164
diff --git a/compiler/prelude/TysWiredIn.lhs b/compiler/prelude/TysWiredIn.lhs
index c06ac23..e83fcb5 100644
--- a/compiler/prelude/TysWiredIn.lhs
+++ b/compiler/prelude/TysWiredIn.lhs
@@ -65,7 +65,7 @@ module TysWiredIn (
unitTy,
-- * Kinds
- typeNatKindCon, typeNatKind, typeStringKindCon, typeStringKind,
+ typeNatKindCon, typeNatKind, typeSymbolKindCon, typeSymbolKind,
-- * Parallel arrays
mkPArrTy,
@@ -152,7 +152,7 @@ wiredInTyCons = [ unitTyCon -- Not treated like other tuples, because
, parrTyCon
, eqTyCon
, typeNatKindCon
- , typeStringKindCon
+ , typeSymbolKindCon
]
++ (case cIntegerLibraryType of
IntegerGMP -> [integerTyCon]
@@ -199,9 +199,9 @@ doubleTyConName = mkWiredInTyConName UserSyntax gHC_TYPES (fsLit "Double")
doubleDataConName = mkWiredInDataConName UserSyntax gHC_TYPES (fsLit "D#") doubleDataConKey doubleDataCon
-- Kinds
-typeNatKindConName, typeStringKindConName :: Name
+typeNatKindConName, typeSymbolKindConName :: Name
typeNatKindConName = mkWiredInTyConName UserSyntax gHC_TYPELITS (fsLit "Nat") typeNatKindConNameKey typeNatKindCon
-typeStringKindConName = mkWiredInTyConName UserSyntax gHC_TYPELITS (fsLit "Symbol") typeStringKindConNameKey typeStringKindCon
+typeSymbolKindConName = mkWiredInTyConName UserSyntax gHC_TYPELITS (fsLit "Symbol") typeSymbolKindConNameKey typeSymbolKindCon
-- For integer-gmp only:
integerRealTyConName :: Name
@@ -304,15 +304,15 @@ pcDataConWithFixity' declared_infix dc_name wrk_key tyvars arg_tys tycon
%************************************************************************
\begin{code}
-typeNatKindCon, typeStringKindCon :: TyCon
+typeNatKindCon, typeSymbolKindCon :: TyCon
-- data Nat
-- data Symbol
-typeNatKindCon = pcNonRecDataTyCon typeNatKindConName Nothing [] []
-typeStringKindCon = pcNonRecDataTyCon typeStringKindConName Nothing [] []
+typeNatKindCon = pcTyCon False NonRecursive True typeNatKindConName Nothing [] []
+typeSymbolKindCon = pcTyCon False NonRecursive True typeSymbolKindConName Nothing [] []
-typeNatKind, typeStringKind :: Kind
+typeNatKind, typeSymbolKind :: Kind
typeNatKind = TyConApp (promoteTyCon typeNatKindCon) []
-typeStringKind = TyConApp (promoteTyCon typeStringKindCon) []
+typeSymbolKind = TyConApp (promoteTyCon typeSymbolKindCon) []
\end{code}
diff --git a/compiler/prelude/TysWiredIn.lhs-boot b/compiler/prelude/TysWiredIn.lhs-boot
index 65c03c8..b6dab8a 100644
--- a/compiler/prelude/TysWiredIn.lhs-boot
+++ b/compiler/prelude/TysWiredIn.lhs-boot
@@ -6,6 +6,6 @@ import {-# SOURCE #-} TypeRep (Type)
eqTyCon :: TyCon
-typeNatKind, typeStringKind :: Type
+typeNatKind, typeSymbolKind :: Type
mkBoxedTupleTy :: [Type] -> Type
\end{code}
diff --git a/compiler/typecheck/TcHsType.lhs b/compiler/typecheck/TcHsType.lhs
index 5e13116..cd5e029 100644
--- a/compiler/typecheck/TcHsType.lhs
+++ b/compiler/typecheck/TcHsType.lhs
@@ -511,8 +511,8 @@ tc_hs_type hs_ty@(HsTyLit (HsNumTy n)) exp_kind
; return (mkNumLitTy n) }
tc_hs_type hs_ty@(HsTyLit (HsStrTy s)) exp_kind
- = do { checkExpectedKind hs_ty typeStringKind exp_kind
- ; checkWiredInTyCon typeStringKindCon
+ = do { checkExpectedKind hs_ty typeSymbolKind exp_kind
+ ; checkWiredInTyCon typeSymbolKindCon
; return (mkStrLitTy s) }
---------------------------
diff --git a/compiler/types/Type.lhs b/compiler/types/Type.lhs
index efe8a3b..cbff4fa 100644
--- a/compiler/types/Type.lhs
+++ b/compiler/types/Type.lhs
@@ -154,7 +154,7 @@ import VarSet
import Class
import TyCon
import TysPrim
-import {-# SOURCE #-} TysWiredIn ( eqTyCon, typeNatKind, typeStringKind )
+import {-# SOURCE #-} TysWiredIn ( eqTyCon, typeNatKind, typeSymbolKind )
import PrelNames ( eqTyConKey, ipClassNameKey,
constraintKindTyConKey, liftedTypeKindTyConKey )
import CoAxiom
@@ -1630,7 +1630,7 @@ typeLiteralKind :: TyLit -> Kind
typeLiteralKind l =
case l of
NumTyLit _ -> typeNatKind
- StrTyLit _ -> typeStringKind
+ StrTyLit _ -> typeSymbolKind
\end{code}
Kind inference
More information about the ghc-commits
mailing list