[commit: ghc] master: Remove the check_lifted check in TcValidity (07afe44)

git at git.haskell.org git at git.haskell.org
Thu Jan 21 10:08:42 UTC 2016


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/07afe448c3a83d7239054baf9d54681ca19766b0/ghc

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

commit 07afe448c3a83d7239054baf9d54681ca19766b0
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Wed Jan 20 16:02:22 2016 +0000

    Remove the check_lifted check in TcValidity
    
    This patch fixes Trac #11465.  The check_unlifted check really isn't
    necessary, as discussed in Trac #11120 comment:19.
    
    Removing it made just one test-suite change,
    in indexed-types/should_fail/T9357, by allowing
    
       type family F (a :: k1) :: k2
       type instance F Int# = Int
    
    to be accepted.  And indeed that seems entirely reasonable.


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

07afe448c3a83d7239054baf9d54681ca19766b0
 compiler/typecheck/TcValidity.hs                       | 17 ++++++++++++++---
 testsuite/tests/indexed-types/should_fail/T9357.hs     |  5 +++++
 testsuite/tests/indexed-types/should_fail/T9357.stderr | 10 +++-------
 3 files changed, 22 insertions(+), 10 deletions(-)

diff --git a/compiler/typecheck/TcValidity.hs b/compiler/typecheck/TcValidity.hs
index 49cbb42..21accdb 100644
--- a/compiler/typecheck/TcValidity.hs
+++ b/compiler/typecheck/TcValidity.hs
@@ -430,9 +430,21 @@ forAllAllowed _                         = False
 ----------------------------------------
 -- | Fail with error message if the type is unlifted
 check_lifted :: TidyEnv -> Type -> TcM ()
+check_lifted _ _ = return ()
+
+{- ------ Legacy comment ---------
+The check_unlifted function seems entirely redundant.  The
+kind system should check for uses of unlifted types.  So I've
+removed the check.  See Trac #11120 comment:19.
+
 check_lifted env ty
   = checkTcM (not (isUnLiftedType ty)) (unliftedArgErr env ty)
 
+unliftedArgErr :: TidyEnv -> Type -> (TidyEnv, SDoc)
+unliftedArgErr env ty = (env, sep [text "Illegal unlifted type:", ppr_tidy env ty])
+------ End of legacy comment --------- -}
+
+
 check_type :: TidyEnv -> UserTypeCtxt -> Rank -> Type -> TcM ()
 -- The args say what the *type context* requires, independent
 -- of *flag* settings.  You test the flag settings at usage sites.
@@ -598,9 +610,8 @@ forAllEscapeErr env ty tau_kind
          2 (vcat [ text "   type:" <+> ppr_tidy env ty
                  , text "of kind:" <+> ppr_tidy env tau_kind ]) )
 
-unliftedArgErr, ubxArgTyErr :: TidyEnv -> Type -> (TidyEnv, SDoc)
-unliftedArgErr  env ty = (env, sep [text "Illegal unlifted type:", ppr_tidy env ty])
-ubxArgTyErr     env ty = (env, sep [text "Illegal unboxed tuple type as function argument:", ppr_tidy env ty])
+ubxArgTyErr :: TidyEnv -> Type -> (TidyEnv, SDoc)
+ubxArgTyErr env ty = (env, sep [text "Illegal unboxed tuple type as function argument:", ppr_tidy env ty])
 
 kindErr :: TidyEnv -> Kind -> (TidyEnv, SDoc)
 kindErr env kind = (env, sep [text "Expecting an ordinary type, but found a type of kind", ppr_tidy env kind])
diff --git a/testsuite/tests/indexed-types/should_fail/T9357.hs b/testsuite/tests/indexed-types/should_fail/T9357.hs
index 29c57f4..9365663 100644
--- a/testsuite/tests/indexed-types/should_fail/T9357.hs
+++ b/testsuite/tests/indexed-types/should_fail/T9357.hs
@@ -4,5 +4,10 @@ module T9357 where
 import GHC.Exts
 
 type family F (a :: k1) :: k2
+
 type instance F Int# = Int
+ -- This one is actually OK (F is poly-kinded;
+ -- c.f. Trac #11120 comment:19
+
 type instance F (forall a. a->a) = Int
+ -- But this one is not (impredicative)
diff --git a/testsuite/tests/indexed-types/should_fail/T9357.stderr b/testsuite/tests/indexed-types/should_fail/T9357.stderr
index cc483c5..32331e5 100644
--- a/testsuite/tests/indexed-types/should_fail/T9357.stderr
+++ b/testsuite/tests/indexed-types/should_fail/T9357.stderr
@@ -1,8 +1,4 @@
 
-T9357.hs:7:15:
-    Illegal unlifted type: Int#
-    In the type instance declaration for ‘F’
-
-T9357.hs:8:15:
-    Illegal polymorphic or qualified type: forall a1. a1 -> a1
-    In the type instance declaration for ‘F’
+T9357.hs:12:15: error:
+    • Illegal polymorphic or qualified type: forall a1. a1 -> a1
+    • In the type instance declaration for ‘F’



More information about the ghc-commits mailing list