[commit: ghc] master: Do not check synonym RHS for ambiguity (3c29c77)

git at git.haskell.org git at git.haskell.org
Tue Mar 1 17:28:04 UTC 2016


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/3c29c770be7a8c7268dcb8d8624853428aa42071/ghc

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

commit 3c29c770be7a8c7268dcb8d8624853428aa42071
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Mon Feb 29 14:12:28 2016 +0000

    Do not check synonym RHS for ambiguity
    
    With this patch we no longer check the RHS of a type synonym
    declaration for ambiguity.  It only affects type synonyms with foralls
    on the RHS (which are rare in the first place), and it's arguably
    over-aggressive to check them for ambiguity.  See TcValidity
    Note [When we don't check for ambiguity]
    
    This fixes the ASSERT failures in
       th                        T3100
       typecheck/should_compile  T3692
       typecheck/should_fail     T3592


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

3c29c770be7a8c7268dcb8d8624853428aa42071
 compiler/typecheck/TcValidity.hs | 35 +++++++++++++++++++++++++----------
 1 file changed, 25 insertions(+), 10 deletions(-)

diff --git a/compiler/typecheck/TcValidity.hs b/compiler/typecheck/TcValidity.hs
index 784cfa0..99a9be3 100644
--- a/compiler/typecheck/TcValidity.hs
+++ b/compiler/typecheck/TcValidity.hs
@@ -216,13 +216,10 @@ checkAmbiguity ctxt ty
 
 wantAmbiguityCheck :: UserTypeCtxt -> Bool
 wantAmbiguityCheck ctxt
-  = case ctxt of
-      GhciCtxt -> False  -- Allow ambiguous types in GHCi's :kind command
-                         -- E.g.   type family T a :: *  -- T :: forall k. k -> *
-                         -- Then :k T should work in GHCi, not complain that
-                         -- (T k) is ambiguous!
-      _ -> True
-
+  = case ctxt of  -- See Note [When we don't check for ambiguity]
+      GhciCtxt     -> False
+      TySynCtxt {} -> False
+      _            -> True
 
 checkUserTypeError :: Type -> TcM ()
 -- Check to see if the type signature mentions "TypeError blah"
@@ -247,7 +244,26 @@ checkUserTypeError = check
                      ; failWithTcM (env1, pprUserTypeErrorTy tidy_msg) }
 
 
-{-
+{- Note [When we don't check for ambiguity]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+In a few places we do not want to check a user-specified type for ambiguity
+
+* GhciCtxt: Allow ambiguous types in GHCi's :kind command
+  E.g.   type family T a :: *  -- T :: forall k. k -> *
+  Then :k T should work in GHCi, not complain that
+  (T k) is ambiguous!
+
+* TySynCtxt: type T a b = C a b => blah
+  It may be that when we /use/ T, we'll give an 'a' or 'b' that somehow
+  cure the ambiguity.  So we defer the ambiguity check to the use site.
+
+  There is also an implementation reason (Trac #11608).  In the RHS of
+  a type synonym we don't (currently) instantiate 'a' and 'b' with
+  TcTyVars before calling checkValidType, so we get asertion failures
+  from doing an ambiguity check on a type with TyVars in it.  Fixing this
+  would not be hard, but let's wait till there's a reason.
+
+
 ************************************************************************
 *                                                                      *
           Checking validity of a user-defined type
@@ -472,13 +488,12 @@ check_type env ctxt rank ty
   where
     (tvs, theta, tau) = tcSplitSigmaTy ty
     tau_kind          = typeKind tau
+    (env', _)         = tidyTyCoVarBndrs env tvs
 
     phi_kind | null theta = tau_kind
              | otherwise  = liftedTypeKind
         -- If there are any constraints, the kind is *. (#11405)
 
-    (env', _)         = tidyTyCoVarBndrs env tvs
-
 check_type _ _ _ (TyVarTy _) = return ()
 
 check_type env ctxt rank (ForAllTy (Anon arg_ty) res_ty)



More information about the ghc-commits mailing list