[commit: ghc] master: Make out-of-scope errors more prominent (08003e7)

git at git.haskell.org git at git.haskell.org
Fri Apr 27 16:21:46 UTC 2018


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/08003e7f4abafb0c9fe084e4670122ce67cf45dd/ghc

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

commit 08003e7f4abafb0c9fe084e4670122ce67cf45dd
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Fri Apr 27 16:15:25 2018 +0100

    Make out-of-scope errors more prominent
    
    Generally, when the type checker reports an error, more serious
    ones suppress less serious ones.
    
    A "variable out of scope" error is arguably the most serious of all,
    so this patch moves it to the front of the list instead of the end.
    
    This patch also fixes Trac #14149, which had
    -fdefer-out-of-scope-variables, but also had a solid type error.
    As things stood, the type error was not reported at all, and
    compilation "succeeded" with error code 0.  Yikes.
    
    Note that
    
    - "Hole errors" (including out of scope) are never suppressed.
      (maybeReportHoleError vs maybeReportError in TcErorrs)
      They can just get drowned by the noise.
    
    - But with the new orientation, out of scope errors will suppress
      type errors.  That would be easy to change.


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

08003e7f4abafb0c9fe084e4670122ce67cf45dd
 compiler/typecheck/TcErrors.hs                         | 18 +++++++++++++++---
 testsuite/tests/typecheck/should_compile/T14149.stderr |  7 +++++--
 testsuite/tests/typecheck/should_compile/all.T         |  2 +-
 testsuite/tests/typecheck/should_fail/T12406.stderr    |  9 ---------
 4 files changed, 21 insertions(+), 15 deletions(-)

diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs
index 27148af..dde7c3c 100644
--- a/compiler/typecheck/TcErrors.hs
+++ b/compiler/typecheck/TcErrors.hs
@@ -529,14 +529,15 @@ reportWanteds ctxt tc_lvl (WC { wc_simple = simples, wc_impl = implics })
     -- (see TcRnTypes.insolubleWantedCt) is caught here, otherwise
     -- we might suppress its error message, and proceed on past
     -- type checking to get a Lint error later
-    report1 = [ ("custom_error", is_user_type_error,True, mkUserTypeErrorReporter)
+    report1 = [ ("Out of scope", is_out_of_scope, out_of_scope_killer, mkHoleReporter tidy_cts)
+              , ("Holes",        is_hole,            False, mkHoleReporter tidy_cts)
+              , ("custom_error", is_user_type_error, True, mkUserTypeErrorReporter)
+
               , given_eq_spec
               , ("insoluble2",   utterly_wrong,  True, mkGroupReporter mkEqErr)
               , ("skolem eq1",   very_wrong,     True, mkSkolReporter)
               , ("skolem eq2",   skolem_eq,      True, mkSkolReporter)
               , ("non-tv eq",    non_tv_eq,      True, mkSkolReporter)
-              , ("Out of scope", is_out_of_scope,True, mkHoleReporter tidy_cts)
-              , ("Holes",        is_hole,        False, mkHoleReporter tidy_cts)
 
                   -- The only remaining equalities are alpha ~ ty,
                   -- where alpha is untouchable; and representational equalities
@@ -551,6 +552,15 @@ reportWanteds ctxt tc_lvl (WC { wc_simple = simples, wc_impl = implics })
               , ("Irreds",          is_irred,        False, mkGroupReporter mkIrredErr)
               , ("Dicts",           is_dict,         False, mkGroupReporter mkDictErr) ]
 
+    out_of_scope_killer :: Bool
+    out_of_scope_killer
+      = case cec_out_of_scope_holes ctxt of
+          HoleError -> True  -- Makes scope errors suppress type errors
+          _         -> False -- But if the scope-errors are warnings or deferred,
+                             -- do not suppress type errors; else you get an exit
+                             -- code of "success" even though there is
+                             -- a type error!
+
     -- rigid_nom_eq, rigid_nom_tv_eq,
     is_hole, is_dict,
       is_equality, is_ip, is_irred :: Ct -> PredTree -> Bool
@@ -789,6 +799,8 @@ reportGroup mk_err ctxt cts =
             _otherwise           -> False
 
 maybeReportHoleError :: ReportErrCtxt -> Ct -> ErrMsg -> TcM ()
+-- Unlike maybeReportError, these "hole" errors are
+-- /not/ suppressed by cec_suppress.  We want to see them!
 maybeReportHoleError ctxt ct err
   -- When -XPartialTypeSignatures is on, warnings (instead of errors) are
   -- generated for holes in partial type signatures.
diff --git a/testsuite/tests/typecheck/should_compile/T14149.stderr b/testsuite/tests/typecheck/should_compile/T14149.stderr
index 5e5306e..b1a8d37 100644
--- a/testsuite/tests/typecheck/should_compile/T14149.stderr
+++ b/testsuite/tests/typecheck/should_compile/T14149.stderr
@@ -1,3 +1,6 @@
 
-T14149.hs:8:13: warning: [-Wdeferred-out-of-scope-variables (in -Wdefault)]
-    Variable not in scope: k :: Int
+T14149.hs:8:5: error:
+    • Couldn't match representation of type ‘Int’ with that of ‘Bool’
+        arising from a use of ‘coerce’
+    • In the expression: coerce (k :: Int)
+      In an equation for ‘f’: f = coerce (k :: Int)
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index 80a8b0e..6a680f6 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -577,7 +577,7 @@ test('T13915a', normal, multimod_compile, ['T13915a', '-v0'])
 test('T13915b', normal, compile, [''])
 test('T13984', normal, compile, [''])
 test('T14128', normal, multimod_compile, ['T14128Main', '-v0'])
-test('T14149', normal, compile, [''])
+test('T14149', normal, compile_fail, [''])
 test('T14154', normal, compile, [''])
 test('T14158', normal, compile, [''])
 test('T13943', normal, compile, ['-fsolve-constant-dicts'])
diff --git a/testsuite/tests/typecheck/should_fail/T12406.stderr b/testsuite/tests/typecheck/should_fail/T12406.stderr
index 85096e6..5219a5f 100644
--- a/testsuite/tests/typecheck/should_fail/T12406.stderr
+++ b/testsuite/tests/typecheck/should_fail/T12406.stderr
@@ -1,12 +1,3 @@
 
-T12406.hs:20:7: error:
-    • Couldn't match type ‘Ref m0’ with ‘IORef’
-      Expected type: IO (Ref m0 (f0 ()))
-        Actual type: IO (Ref IO (f0 ()))
-      The type variable ‘m0’ is ambiguous
-    • In the first argument of ‘(>>=)’, namely ‘newRef (pure ())’
-      In the expression: newRef (pure ()) >>= join . readRef
-      In an equation for ‘foo’: foo = newRef (pure ()) >>= join . readRef
-
 T12406.hs:20:28: error:
     Variable not in scope: join :: m0 (f0 ()) -> IO ()



More information about the ghc-commits mailing list