diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index cd08570af6b0f646f5472c8310fca2598cfdce65..7436b0d690f0812133501d272a462b6e3d8fc83c 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -2538,8 +2538,8 @@ checkValidTyConTyVars tc ------------------------------- checkValidDataCon :: DynFlags -> Bool -> TyCon -> DataCon -> TcM () checkValidDataCon dflags existential_ok tc con - = setSrcSpan (srcLocSpan (getSrcLoc con)) $ - addErrCtxt (dataConCtxt con) $ + = setSrcSpan (getSrcSpan con) $ + addErrCtxt (dataConCtxt con) $ do { -- Check that the return type of the data constructor -- matches the type constructor; eg reject this: -- data T a where { MkT :: Bogus a } diff --git a/testsuite/tests/gadt/T14719.hs b/testsuite/tests/gadt/T14719.hs new file mode 100644 index 0000000000000000000000000000000000000000..004116dcc6ef330b59f621d6b9dd976d9d69abd1 --- /dev/null +++ b/testsuite/tests/gadt/T14719.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE GADTs #-} +module T14719 where + +data Foo1 where + MkFoo1 :: Bool + +newtype Foo2 where + MkFoo2 :: Foo2 diff --git a/testsuite/tests/gadt/T14719.stderr b/testsuite/tests/gadt/T14719.stderr new file mode 100644 index 0000000000000000000000000000000000000000..cfac00c0c0f1082fdb7628916d3e1055071c414f --- /dev/null +++ b/testsuite/tests/gadt/T14719.stderr @@ -0,0 +1,18 @@ + +T14719.hs:5:3: error: + • Data constructor ‘MkFoo1’ returns type ‘Bool’ + instead of an instance of its parent type ‘Foo1’ + • In the definition of data constructor ‘MkFoo1’ + In the data type declaration for ‘Foo1’ + | +5 | MkFoo1 :: Bool + | ^^^^^^^^^^^^^^ + +T14719.hs:8:3: error: + • The constructor of a newtype must have exactly one field + but ‘MkFoo2’ has none + • In the definition of data constructor ‘MkFoo2’ + In the newtype declaration for ‘Foo2’ + | +8 | MkFoo2 :: Foo2 + | ^^^^^^^^^^^^^^ diff --git a/testsuite/tests/gadt/all.T b/testsuite/tests/gadt/all.T index c81ab80c0479974343d1b1eff524818eebfb9f25..59ec307d588132f2d0da7308b1426a53ef115619 100644 --- a/testsuite/tests/gadt/all.T +++ b/testsuite/tests/gadt/all.T @@ -115,3 +115,4 @@ test('T9380', normal, compile_and_run, ['']) test('T12087', normal, compile_fail, ['']) test('T12468', normal, compile_fail, ['']) test('T14320', normal, compile, ['']) +test('T14719', normal, compile_fail, ['-fdiagnostics-show-caret']) diff --git a/testsuite/tests/polykinds/T9222.stderr b/testsuite/tests/polykinds/T9222.stderr index 6e143e0cf9684af54fec2d91d35015c3c02aefd5..604cc1b7ecb125b6e87e7e9c61c7a03dd49c416e 100644 --- a/testsuite/tests/polykinds/T9222.stderr +++ b/testsuite/tests/polykinds/T9222.stderr @@ -5,12 +5,12 @@ T9222.hs:13:3: error: inside the constraints: a ~ '(b0, c0) bound by the type of the constructor ‘Want’: (a ~ '(b0, c0)) => Proxy b0 - at T9222.hs:13:3 + at T9222.hs:13:3-43 ‘c’ is a rigid type variable bound by the type of the constructor ‘Want’: forall i1 j1 (a :: (i1, j1)) (b :: i1) (c :: j1). ((a ~ '(b, c)) => Proxy b) -> Want a - at T9222.hs:13:3 + at T9222.hs:13:3-43 • In the ambiguity check for ‘Want’ To defer the ambiguity check to use sites, enable AllowAmbiguousTypes In the definition of data constructor ‘Want’