[commit: ghc] master: Comments only, about Typeable/TypeRep/KindRep (2a09700)

git at git.haskell.org git at git.haskell.org
Thu May 4 16:27:28 UTC 2017


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/2a09700149732df529cfcb506932c524e7851b4a/ghc

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

commit 2a09700149732df529cfcb506932c524e7851b4a
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Thu May 4 17:26:41 2017 +0100

    Comments only, about Typeable/TypeRep/KindRep


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

2a09700149732df529cfcb506932c524e7851b4a
 compiler/typecheck/TcTypeable.hs | 55 ++++++++++++++++++++++------------------
 compiler/types/TyCon.hs          |  5 +++-
 libraries/ghc-prim/GHC/Types.hs  |  2 +-
 3 files changed, 35 insertions(+), 27 deletions(-)

diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs
index d30a722..4c6076e 100644
--- a/compiler/typecheck/TcTypeable.hs
+++ b/compiler/typecheck/TcTypeable.hs
@@ -72,7 +72,7 @@ The overall plan is this:
    Here 0# is the number of arguments expected by the tycon to fully determine
    its kind. kind_rep is a value of type GHC.Types.KindRep, which gives a
    recipe for computing the kind of an instantiation of the tycon (see
-   Note [Representing TyCon kinds] later in this file for details).
+   Note [Representing TyCon kinds: KindRep] later in this file for details).
 
    We define (in TyCon)
 
@@ -640,54 +640,59 @@ word64 dflags n
   | otherwise             = HsWordPrim   NoSourceText (toInteger n)
 
 {-
-Note [Representing TyCon kinds]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-
+Note [Representing TyCon kinds: KindRep]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 One of the operations supported by Typeable is typeRepKind,
 
     typeRepKind :: TypeRep (a :: k) -> TypeRep k
 
-Implementing this is a bit tricky. To see why let's consider the TypeRep
-encoding of `Proxy Int` where
+Implementing this is a bit tricky for poly-kinded types like
 
     data Proxy (a :: k) :: Type
+    -- Proxy :: forall k. k -> Type
 
-which looks like,
+The TypeRep encoding of `Proxy Type Int` looks like this:
 
-    $tcProxy :: TyCon
+    $tcProxy :: GHC.Types.TyCon
     $trInt   :: TypeRep Int
     $trType  :: TypeRep Type
 
-    $trProxyType :: TypeRep (Proxy :: Type -> Type)
+    $trProxyType :: TypeRep (Proxy Type :: Type -> Type)
     $trProxyType = TrTyCon $tcProxy
                            [$trType]  -- kind variable instantiation
 
-    $trProxy :: TypeRep (Proxy Int)
+    $trProxy :: TypeRep (Proxy Type Int)
     $trProxy = TrApp $trProxyType $trInt
 
-Note how $trProxyType encodes only the kind variables of the TyCon
-instantiation. To compute the kind (Proxy Int) we need to have a recipe to
-compute the kind of a concrete instantiation of Proxy. We call this recipe a
-KindRep and store it in the TyCon produced for Proxy,
+    $tkProxy :: GHC.Types.KindRep
+    $tkProxy = KindRepFun (KindRepVar 0) (KindRepTyConApp $trType [])
 
-    type KindBndr = Int   -- de Bruijn index
+Note how $trProxyType cannot use 'TrApp', because TypeRep cannot represent
+polymorphic types.  So instead
 
-    data KindRep = KindRepTyConApp TyCon [KindRep]
-                 | KindRepVar !KindBndr
-                 | KindRepApp KindRep KindRep
-                 | KindRepFun KindRep KindRep
+ * $trProxyType uses 'TrTyCon' to apply Proxy to (the representations)
+   of all its kind arguments. We can't represent a tycon that is
+   applied to only some of its kind arguments.
 
-The KindRep for Proxy would look like,
+ * In $tcProxy, the GHC.Types.TyCon structure for Proxy, we store a
+   GHC.Types.KindRep, which represents the polymorphic kind of Proxy
+       Proxy :: forall k. k->Type
 
-    $tkProxy :: KindRep
-    $tkProxy = KindRepFun (KindRepVar 0) (KindRepTyConApp $trType [])
+ * A KindRep is just a recipe that we can instantiate with the
+   argument kinds, using Data.Typeable.Internal.instantiateKindRep.
 
+   Data.Typeable.Internal.typeRepKind uses instantiateKindRep
 
-data Maybe a = Nothing | Just a
+ * In a KindRep, the kind variables are represented by 0-indexed
+   de Bruijn numbers:
 
-'Just :: a -> Maybe a
+    type KindBndr = Int   -- de Bruijn index
 
-F :: forall k. k -> forall k'. k' -> Type
+    data KindRep = KindRepTyConApp TyCon [KindRep]
+                 | KindRepVar !KindBndr
+                 | KindRepApp KindRep KindRep
+                 | KindRepFun KindRep KindRep
+                 ...
 -}
 
 mkList :: Type -> [LHsExpr Id] -> LHsExpr Id
diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs
index 99a20af..9f6486b 100644
--- a/compiler/types/TyCon.hs
+++ b/compiler/types/TyCon.hs
@@ -403,6 +403,9 @@ tyConBinderArgFlag (TvBndr _ (NamedTCB vis)) = vis
 tyConBinderArgFlag (TvBndr _ AnonTCB)        = Required
 
 isNamedTyConBinder :: TyConBinder -> Bool
+-- Identifies kind variables
+-- E.g. data T k (a:k) = blah
+-- Here 'k' is a NamedTCB, a variable used in the kind of other binders
 isNamedTyConBinder (TvBndr _ (NamedTCB {})) = True
 isNamedTyConBinder _                        = False
 
@@ -427,7 +430,7 @@ mkTyConKind bndrs res_kind = foldr mk res_kind bndrs
 All TyCons have this group of fields
   tyConBinders :: [TyConBinder]
   tyConResKind :: Kind
-  tyConTyVars  :: [TyVra] -- Cached = binderVars tyConBinders
+  tyConTyVars  :: [TyVar] -- Cached = binderVars tyConBinders
   tyConKind    :: Kind    -- Cached = mkTyConKind tyConBinders tyConResKind
   tyConArity   :: Arity   -- Cached = length tyConBinders
 
diff --git a/libraries/ghc-prim/GHC/Types.hs b/libraries/ghc-prim/GHC/Types.hs
index a4b7a91..3756c58 100644
--- a/libraries/ghc-prim/GHC/Types.hs
+++ b/libraries/ghc-prim/GHC/Types.hs
@@ -450,7 +450,7 @@ type KindBndr = Int
 #endif
 
 -- | The representation produced by GHC for conjuring up the kind of a
--- 'TypeRep'.
+-- 'TypeRep'.  See Note [Representing TyCon kinds: KindRep] in TcTypeable.
 data KindRep = KindRepTyConApp TyCon [KindRep]
              | KindRepVar !KindBndr
              | KindRepApp KindRep KindRep



More information about the ghc-commits mailing list