[commit: ghc] master: Make :kind in GHCi do kind generalisation, always (Trac #7688) (ed21082)

Simon Peyton Jones simonpj at microsoft.com
Fri Feb 15 18:23:29 CET 2013


Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/ed2108267b93e6abd769192bdc8fe86cefef7a70

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

commit ed2108267b93e6abd769192bdc8fe86cefef7a70
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Fri Feb 15 17:14:36 2013 +0000

    Make :kind in GHCi do kind generalisation, always (Trac #7688)
    
    See Note [Kind-generalise in tcRnType] in TcRnDriver, and
    the notes in Trac #7688

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

 compiler/typecheck/TcRnDriver.lhs |   43 +++++++++++++++++++++++++------------
 1 files changed, 29 insertions(+), 14 deletions(-)

diff --git a/compiler/typecheck/TcRnDriver.lhs b/compiler/typecheck/TcRnDriver.lhs
index 4f4b166..cfd96e3 100644
--- a/compiler/typecheck/TcRnDriver.lhs
+++ b/compiler/typecheck/TcRnDriver.lhs
@@ -1575,27 +1575,42 @@ tcRnType :: HscEnv
          -> IO (Messages, Maybe (Type, Kind))
 tcRnType hsc_env ictxt normalise rdr_type
   = initTcPrintErrors hsc_env iNTERACTIVE $
-    setInteractiveContext hsc_env ictxt $ do {
-
-    (rn_type, _fvs) <- rnLHsType GHCiCtx rdr_type ;
-    failIfErrsM ;
+    setInteractiveContext hsc_env ictxt $ 
+    setXOptM Opt_PolyKinds $   -- See Note [Kind-generalise in tcRnType]
+    do { (rn_type, _fvs) <- rnLHsType GHCiCtx rdr_type
+       ; failIfErrsM
 
         -- Now kind-check the type
         -- It can have any rank or kind
-    ty <- tcHsSigType GhciCtxt rn_type ;
+       ; ty <- tcHsSigType GhciCtxt rn_type ;
 
-    ty' <- if normalise
-           then do { fam_envs <- tcGetFamInstEnvs
-                   ; return (snd (normaliseType fam_envs ty)) }
-                   -- normaliseType returns a coercion
-                   -- which we discard
-           else return ty ;
-
-    return (ty', typeKind ty)
-    }
+       ; ty' <- if normalise
+                then do { fam_envs <- tcGetFamInstEnvs
+                        ; return (snd (normaliseType fam_envs ty)) }
+                        -- normaliseType returns a coercion
+                        -- which we discard
+                else return ty ;
 
+       ; return (ty', typeKind ty) }
 \end{code}
 
+Note [Kind-generalise in tcRnType]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+We switch on PolyKinds when kind-checking a user type, so that we will
+kind-generalise the type.  This gives the right default behaviour at
+the GHCi prompt, where if you say ":k T", and T has a polymorphic
+kind, you'd like to see that polymorphism. Of course.  If T isn't
+kind-polymorphic you won't get anything unexpected, but the apparent
+*loss* of polymorphism, for types that you konw are polymorphic, is
+quite surprising.  See Trac #7688 for a discussion.
+
+
+%************************************************************************
+%*                                                                      *
+                 tcRnDeclsi
+%*                                                                      *
+%************************************************************************
+
 tcRnDeclsi exists to allow class, data, and other declarations in GHCi.
 
 \begin{code}





More information about the ghc-commits mailing list