[commit: ghc] master: When printing types in the interactive UI, take account of free variables (2cc42db)

Simon Peyton Jones simonpj at microsoft.com
Thu Jan 24 14:22:50 CET 2013


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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/2cc42dbb6ff09f4105fe44fe1afe9ac08a140d44

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

commit 2cc42dbb6ff09f4105fe44fe1afe9ac08a140d44
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Tue Jan 22 17:01:30 2013 +0000

    When printing types in the interactive UI, take account of free variables
    
    Often the types we print are full-generalised, but in fact *kinds* are
    not, so we need to use tidyOpenType.
    
    Fixes Trac #7587

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

 compiler/main/HscMain.hs          |    2 ++
 compiler/main/InteractiveEval.hs  |    1 +
 compiler/main/PprTyThing.hs       |    7 ++++++-
 compiler/typecheck/TcRnDriver.lhs |    1 +
 4 files changed, 10 insertions(+), 1 deletions(-)

diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs
index 3562f27..2f2b53e 100644
--- a/compiler/main/HscMain.hs
+++ b/compiler/main/HscMain.hs
@@ -1614,6 +1614,7 @@ hscImport hsc_env str = runInteractiveHsc hsc_env $ do
                      ptext (sLit "parse error in import declaration")
 
 -- | Typecheck an expression (but don't run it)
+-- Returns its most general type
 hscTcExpr :: HscEnv
           -> String -- ^ The expression
           -> IO Type
@@ -1628,6 +1629,7 @@ hscTcExpr hsc_env0 expr = runInteractiveHsc hsc_env0 $ do
                 (text "not an expression:" <+> quotes (text expr))
 
 -- | Find the kind of a type
+-- Currently this does *not* generalise the kinds of the type
 hscKcType
   :: HscEnv
   -> Bool            -- ^ Normalise the type
diff --git a/compiler/main/InteractiveEval.hs b/compiler/main/InteractiveEval.hs
index 7fa156a..8d64900 100644
--- a/compiler/main/InteractiveEval.hs
+++ b/compiler/main/InteractiveEval.hs
@@ -972,6 +972,7 @@ parseName str = withSession $ \hsc_env -> do
 -- Getting the type of an expression
 
 -- | Get the type of an expression
+-- Returns its most general type
 exprType :: GhcMonad m => String -> m Type
 exprType expr = withSession $ \hsc_env -> do
    ty <- liftIO $ hscTcExpr hsc_env expr
diff --git a/compiler/main/PprTyThing.hs b/compiler/main/PprTyThing.hs
index 932b46c..a606441 100644
--- a/compiler/main/PprTyThing.hs
+++ b/compiler/main/PprTyThing.hs
@@ -33,6 +33,7 @@ import Coercion( pprCoAxiom )
 import HscTypes( tyThingParent_maybe )
 import TcType
 import Name
+import VarEnv( emptyTidyEnv )
 import StaticFlags( opt_PprStyle_Debug )
 import Outputable
 import FastString
@@ -161,8 +162,12 @@ pprTypeForUser print_foralls ty
   | print_foralls = ppr tidy_ty
   | otherwise     = ppr (mkPhiTy ctxt ty')
   where
-    tidy_ty     = tidyTopType ty
     (_, ctxt, ty') = tcSplitSigmaTy tidy_ty
+    (_, tidy_ty)   = tidyOpenType emptyTidyEnv ty
+     -- Often the types/kinds we print in ghci are fully generalised
+     -- and have no free variables, but it turns out that we sometimes
+     -- print un-generalised kinds (eg when doing :k T), so it's
+     -- better to use tidyOpenType here
 
 pprTyCon :: PrintExplicitForalls -> ShowSub -> TyCon -> SDoc
 pprTyCon pefas ss tyCon
diff --git a/compiler/typecheck/TcRnDriver.lhs b/compiler/typecheck/TcRnDriver.lhs
index eadcffe..2da7023 100644
--- a/compiler/typecheck/TcRnDriver.lhs
+++ b/compiler/typecheck/TcRnDriver.lhs
@@ -1529,6 +1529,7 @@ tcRnExpr :: HscEnv
          -> InteractiveContext
          -> LHsExpr RdrName
          -> IO (Messages, Maybe Type)
+-- Type checks the expression and returns its most general type
 tcRnExpr hsc_env ictxt rdr_expr
   = initTcPrintErrors hsc_env iNTERACTIVE $
     setInteractiveContext hsc_env ictxt $ do {





More information about the ghc-commits mailing list