Skip to content

Commit

Permalink
Add a missing addDeferredBinding
Browse files Browse the repository at this point in the history
I'd forgotten to add deferred bindings for user type
errors.  Fixes Trac #13487.
  • Loading branch information
Simon Peyton Jones committed Apr 6, 2017
1 parent 48daaaf commit 2f9f1f8
Show file tree
Hide file tree
Showing 4 changed files with 27 additions and 1 deletion.
3 changes: 2 additions & 1 deletion compiler/typecheck/TcErrors.hs
Original file line number Diff line number Diff line change
Expand Up @@ -611,7 +611,8 @@ mkHoleReporter ctxt
mkUserTypeErrorReporter :: Reporter
mkUserTypeErrorReporter ctxt
= mapM_ $ \ct -> do { err <- mkUserTypeError ctxt ct
; maybeReportError ctxt err }
; maybeReportError ctxt err
; addDeferredBinding ctxt err ct }

mkUserTypeError :: ReportErrCtxt -> Ct -> TcM ErrMsg
mkUserTypeError ctxt ct = mkErrorMsgFromCt ctxt ct
Expand Down
19 changes: 19 additions & 0 deletions testsuite/tests/typecheck/should_fail/T13487.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fdefer-type-errors #-}

module T13487 where

import Data.Kind (Constraint)
import GHC.TypeLits

data Foo a b where
K :: Error a b => a -> b -> Foo a b

type family Error a b :: Constraint where
Error Int Int = ()
Error _ _ = TypeError ('Text "GHC panic in 3... 2... 1...")

foo = K 'a' 'b'
5 changes: 5 additions & 0 deletions testsuite/tests/typecheck/should_fail/T13487.stderr
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@

T13487.hs:19:7: warning: [-Wdeferred-type-errors (in -Wdefault)]
• GHC panic in 3... 2... 1...
• In the expression: K 'a' 'b'
In an equation for ‘foo’: foo = K 'a' 'b'
1 change: 1 addition & 0 deletions testsuite/tests/typecheck/should_fail/all.T
Original file line number Diff line number Diff line change
Expand Up @@ -427,6 +427,7 @@ test('StrictBinds', normal, compile_fail, [''])
test('T13068', [extra_files(['T13068.hs', 'T13068a.hs', 'T13068.hs-boot', 'T13068m.hs'])], multimod_compile_fail, ['T13068m', ''])
test('T13105', normal, compile_fail, [''])
test('LevPolyBounded', normal, compile_fail, [''])
test('T13487', normal, compile, [''])
test('T13292', normal, multimod_compile, ['T13292', '-v0 -fdefer-type-errors'])
test('T13300', normal, compile_fail, [''])
test('T12709', normal, compile_fail, [''])
Expand Down

0 comments on commit 2f9f1f8

Please sign in to comment.