summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSimon Peyton Jones <simonpj@microsoft.com>2015-06-18 08:54:11 +0100
committerSimon Peyton Jones <simonpj@microsoft.com>2015-06-18 08:54:11 +0100
commit5879d5aab929e9959d48e03dad456b824160b3bf (patch)
treed9c9d012dc9a06f2e0c77fc487ff5a58a8130df1
parent023a0ba938b69bbb89cb2ce48a07459b07783391 (diff)
downloadhaskell-5879d5aab929e9959d48e03dad456b824160b3bf.tar.gz
Report arity errors correctly despite kinds
Trac #10516 pointed out that when reporting arity errors (like "T needs 2 arguments but has been given 1"), we should not count kind arguments, since they are implicit. If we include kind args in the count, we get very confusing error messages indeed. I did a little bit of refactoring which make some error messages wobble around. But the payload of this fix is in TcValidity.tyConArityErr
-rw-r--r--compiler/typecheck/TcPat.hs4
-rw-r--r--compiler/typecheck/TcTyClsDecls.hs9
-rw-r--r--compiler/typecheck/TcValidity.hs51
-rw-r--r--compiler/types/TyCon.hs19
-rw-r--r--testsuite/tests/gadt/T3163.stderr10
-rw-r--r--testsuite/tests/gadt/gadt11.stderr12
-rw-r--r--testsuite/tests/gadt/gadtSyntaxFail001.stderr14
-rw-r--r--testsuite/tests/gadt/gadtSyntaxFail002.stderr14
-rw-r--r--testsuite/tests/gadt/gadtSyntaxFail003.stderr14
-rw-r--r--testsuite/tests/gadt/records-fail1.stderr10
-rw-r--r--testsuite/tests/ghci/scripts/T9293.stderr38
-rw-r--r--testsuite/tests/ghci/scripts/ghci057.stderr38
-rw-r--r--testsuite/tests/indexed-types/should_fail/BadSock.stderr10
-rw-r--r--testsuite/tests/indexed-types/should_fail/T2157.stderr8
-rw-r--r--testsuite/tests/indexed-types/should_fail/T9433.stderr4
-rw-r--r--testsuite/tests/module/mod60.stderr10
-rw-r--r--testsuite/tests/parser/should_fail/ParserNoBinaryLiterals2.stderr10
-rw-r--r--testsuite/tests/parser/should_fail/ParserNoBinaryLiterals3.stderr10
-rw-r--r--testsuite/tests/polykinds/T10516.hs9
-rw-r--r--testsuite/tests/polykinds/T10516.stderr4
-rw-r--r--testsuite/tests/polykinds/T9222.stderr48
-rw-r--r--testsuite/tests/polykinds/all.T1
-rw-r--r--testsuite/tests/typecheck/should_compile/T7050.stderr10
-rw-r--r--testsuite/tests/typecheck/should_compile/T7562.stderr10
-rw-r--r--testsuite/tests/typecheck/should_fail/T3966.stderr16
-rw-r--r--testsuite/tests/typecheck/should_fail/T7175.stderr12
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail100.stderr8
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail101.stderr8
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail107.stderr10
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail129.stderr24
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail140.stderr12
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail155.stderr12
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail187.stderr10
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail195.stderr10
-rw-r--r--testsuite/tests/typecheck/should_fail/tcfail209.stderr10
35 files changed, 268 insertions, 231 deletions
diff --git a/compiler/typecheck/TcPat.hs b/compiler/typecheck/TcPat.hs
index 7e5b4e34ed..7aafdf5d9a 100644
--- a/compiler/typecheck/TcPat.hs
+++ b/compiler/typecheck/TcPat.hs
@@ -989,7 +989,7 @@ tcConArgs :: ConLike -> [TcSigmaType]
tcConArgs con_like arg_tys (PrefixCon arg_pats) penv thing_inside
= do { checkTc (con_arity == no_of_args) -- Check correct arity
- (arityErr "Constructor" con_like con_arity no_of_args)
+ (arityErr "constructor" con_like con_arity no_of_args)
; let pats_w_tys = zipEqual "tcConArgs" arg_pats arg_tys
; (arg_pats', res) <- tcMultiple tcConArg pats_w_tys
penv thing_inside
@@ -1000,7 +1000,7 @@ tcConArgs con_like arg_tys (PrefixCon arg_pats) penv thing_inside
tcConArgs con_like arg_tys (InfixCon p1 p2) penv thing_inside
= do { checkTc (con_arity == 2) -- Check correct arity
- (arityErr "Constructor" con_like con_arity 2)
+ (arityErr "constructor" con_like con_arity 2)
; let [arg_ty1,arg_ty2] = arg_tys -- This can't fail after the arity check
; ([p1',p2'], res) <- tcMultiple tcConArg [(p1,arg_ty1),(p2,arg_ty2)]
penv thing_inside
diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs
index 1b324f668a..57ed460848 100644
--- a/compiler/typecheck/TcTyClsDecls.hs
+++ b/compiler/typecheck/TcTyClsDecls.hs
@@ -2305,14 +2305,7 @@ addTyThingCtxt thing
where
name = getName thing
flav = case thing of
- ATyCon tc
- | isClassTyCon tc -> ptext (sLit "class")
- | isTypeFamilyTyCon tc -> ptext (sLit "type family")
- | isDataFamilyTyCon tc -> ptext (sLit "data family")
- | isTypeSynonymTyCon tc -> ptext (sLit "type")
- | isNewTyCon tc -> ptext (sLit "newtype")
- | isDataTyCon tc -> ptext (sLit "data")
-
+ ATyCon tc -> text (tyConFlavour tc)
_ -> pprTrace "addTyThingCtxt strange" (ppr thing)
Outputable.empty
diff --git a/compiler/typecheck/TcValidity.hs b/compiler/typecheck/TcValidity.hs
index 826b3093e4..663990ffaa 100644
--- a/compiler/typecheck/TcValidity.hs
+++ b/compiler/typecheck/TcValidity.hs
@@ -23,7 +23,7 @@ import TcSimplify ( simplifyAmbiguityCheck )
import TypeRep
import TcType
import TcMType
-import TysWiredIn ( coercibleClass, eqTyConName )
+import TysWiredIn ( coercibleClass, eqTyCon )
import PrelNames
import Type
import Unify( tcMatchTyX )
@@ -439,7 +439,7 @@ check_syn_tc_app :: UserTypeCtxt -> Rank -> KindOrType
-- which must be saturated,
-- but not data families, which need not be saturated
check_syn_tc_app ctxt rank ty tc tys
- | tc_arity <= n_args -- Saturated
+ | tc_arity <= length tys -- Saturated
-- Check that the synonym has enough args
-- This applies equally to open and closed synonyms
-- It's OK to have an *over-applied* type synonym
@@ -462,11 +462,8 @@ check_syn_tc_app ctxt rank ty tc tys
= mapM_ check_arg tys
| otherwise
- = failWithTc (arityErr flavour (tyConName tc) tc_arity n_args)
+ = failWithTc (tyConArityErr tc tys)
where
- flavour | isTypeFamilyTyCon tc = "Type family"
- | otherwise = "Type synonym"
- n_args = length tys
tc_arity = tyConArity tc
check_arg | isTypeFamilyTyCon tc = check_arg_type ctxt rank
| otherwise = check_mono_type ctxt synArgMonoType
@@ -642,12 +639,10 @@ check_eq_pred :: DynFlags -> PredType -> [TcType] -> TcM ()
check_eq_pred dflags pred tys
= -- Equational constraints are valid in all contexts if type
-- families are permitted
- do { checkTc (n_tys == 3)
- (arityErr "Equality constraint" eqTyConName 3 n_tys)
+ do { checkTc (length tys == 3)
+ (tyConArityErr eqTyCon tys)
; checkTc (xopt Opt_TypeFamilies dflags || xopt Opt_GADTs dflags)
(eqPredTyErr pred) }
- where
- n_tys = length tys
check_tuple_pred :: Bool -> DynFlags -> UserTypeCtxt -> PredType -> [PredType] -> TcM ()
check_tuple_pred under_syn dflags ctxt pred ts
@@ -710,18 +705,15 @@ solved to add+canonicalise another (Foo a) constraint. -}
check_class_pred :: DynFlags -> UserTypeCtxt -> PredType -> Class -> [TcType] -> TcM ()
check_class_pred dflags ctxt pred cls tys
| isIPClass cls
- = do { checkTc (arity == n_tys) arity_err
- ; checkTc (okIPCtxt ctxt) (badIPPred pred) }
+ = do { check_arity
+ ; checkTc (okIPCtxt ctxt) (badIPPred pred) }
| otherwise
- = do { checkTc (arity == n_tys) arity_err
+ = do { check_arity
; checkTc arg_tys_ok (predTyVarErr pred) }
where
- class_name = className cls
- arity = classArity cls
- n_tys = length tys
- arity_err = arityErr "Class" class_name arity n_tys
-
+ check_arity = checkTc (classArity cls == length tys)
+ (tyConArityErr (classTyCon cls) tys)
flexible_contexts = xopt Opt_FlexibleContexts dflags
undecidable_ok = xopt Opt_UndecidableInstances dflags
@@ -806,9 +798,28 @@ constraintSynErr kind = hang (ptext (sLit "Illegal constraint synonym of kind:")
dupPredWarn :: [[PredType]] -> SDoc
dupPredWarn dups = ptext (sLit "Duplicate constraint(s):") <+> pprWithCommas pprType (map head dups)
+tyConArityErr :: TyCon -> [TcType] -> SDoc
+-- For type-constructor arity errors, be careful to report
+-- the number of /type/ arguments required and supplied,
+-- ignoring the /kind/ arguments, which the user does not see.
+-- (e.g. Trac #10516)
+tyConArityErr tc tks
+ = arityErr (tyConFlavour tc) (tyConName tc)
+ tc_type_arity tc_type_args
+ where
+ tvs = tyConTyVars tc
+
+ kbs :: [Bool] -- True for a Type arg, false for a Kind arg
+ kbs = map isTypeVar tvs
+
+ -- tc_type_arity = number of *type* args expected
+ -- tc_type_args = number of *type* args encountered
+ tc_type_arity = count id kbs
+ tc_type_args = count (id . fst) (kbs `zip` tks)
+
arityErr :: Outputable a => String -> a -> Int -> Int -> SDoc
-arityErr kind name n m
- = hsep [ text kind, quotes (ppr name), ptext (sLit "should have"),
+arityErr what name n m
+ = hsep [ ptext (sLit "The") <+> text what, quotes (ppr name), ptext (sLit "should have"),
n_arguments <> comma, text "but has been given",
if m==0 then text "none" else int m]
where
diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs
index 0a7ba6389b..e1cd1285a4 100644
--- a/compiler/types/TyCon.hs
+++ b/compiler/types/TyCon.hs
@@ -68,6 +68,7 @@ module TyCon(
tyConArity,
tyConRoles,
tyConParent,
+ tyConFlavour,
tyConTuple_maybe, tyConClass_maybe,
tyConFamInst_maybe, tyConFamInstSig_maybe, tyConFamilyCoercion_maybe,
synTyConDefn_maybe, synTyConRhs_maybe, famTyConFlav_maybe,
@@ -1763,6 +1764,24 @@ instance Outputable TyCon where
-- corresponding TyCon, so we add the quote to distinguish it here
ppr tc = pprPromotionQuote tc <> ppr (tyConName tc)
+tyConFlavour :: TyCon -> String
+tyConFlavour (AlgTyCon { algTcParent = parent, algTcRhs = rhs })
+ | ClassTyCon _ <- parent = "class"
+ | otherwise = case rhs of
+ TupleTyCon { tup_sort = sort }
+ | isBoxed (tupleSortBoxity sort) -> "tuple"
+ | otherwise -> "unboxed tuple"
+ DataTyCon {} -> "data type"
+ NewTyCon {} -> "newtype"
+ DataFamilyTyCon {} -> "data family"
+ AbstractTyCon {} -> "abstract type"
+tyConFlavour (FamilyTyCon {}) = "type family"
+tyConFlavour (SynonymTyCon {}) = "type synonym"
+tyConFlavour (FunTyCon {}) = "built-in type"
+tyConFlavour (PrimTyCon {}) = "built-in type"
+tyConFlavour (PromotedDataCon {}) = "promoted data constructor"
+tyConFlavour (PromotedTyCon {}) = "promoted type constructor"
+
pprPromotionQuote :: TyCon -> SDoc
pprPromotionQuote (PromotedDataCon {}) = char '\'' -- Quote promoted DataCons
-- in types
diff --git a/testsuite/tests/gadt/T3163.stderr b/testsuite/tests/gadt/T3163.stderr
index 5daca38050..095378b540 100644
--- a/testsuite/tests/gadt/T3163.stderr
+++ b/testsuite/tests/gadt/T3163.stderr
@@ -1,5 +1,5 @@
-
-T3163.hs:8:5:
- Illegal polymorphic or qualified type: forall s. s
- In the definition of data constructor ‘Unreached’
- In the data declaration for ‘Taker’
+
+T3163.hs:8:5: error:
+ Illegal polymorphic or qualified type: forall s. s
+ In the definition of data constructor ‘Unreached’
+ In the data type declaration for ‘Taker’
diff --git a/testsuite/tests/gadt/gadt11.stderr b/testsuite/tests/gadt/gadt11.stderr
index 016fd2bd75..1dba9b0a40 100644
--- a/testsuite/tests/gadt/gadt11.stderr
+++ b/testsuite/tests/gadt/gadt11.stderr
@@ -1,6 +1,6 @@
-
-gadt11.hs:12:3:
- Data constructor ‘L2’ returns type ‘T1 Bool’
- instead of an instance of its parent type ‘T2 a’
- In the definition of data constructor ‘L2’
- In the data declaration for ‘T2’
+
+gadt11.hs:12:3: error:
+ Data constructor ‘L2’ returns type ‘T1 Bool’
+ instead of an instance of its parent type ‘T2 a’
+ In the definition of data constructor ‘L2’
+ In the data type declaration for ‘T2’
diff --git a/testsuite/tests/gadt/gadtSyntaxFail001.stderr b/testsuite/tests/gadt/gadtSyntaxFail001.stderr
index 54fa5f992b..e92272d5c2 100644
--- a/testsuite/tests/gadt/gadtSyntaxFail001.stderr
+++ b/testsuite/tests/gadt/gadtSyntaxFail001.stderr
@@ -1,7 +1,7 @@
-
-gadtSyntaxFail001.hs:8:5:
- Data constructor ‘C2’ has existential type variables, a context, or a specialised result type
- C2 :: forall a. a -> Char -> Foo a Int
- (Use ExistentialQuantification or GADTs to allow this)
- In the definition of data constructor ‘C2’
- In the data declaration for ‘Foo’
+
+gadtSyntaxFail001.hs:8:5: error:
+ Data constructor ‘C2’ has existential type variables, a context, or a specialised result type
+ C2 :: forall a. a -> Char -> Foo a Int
+ (Use ExistentialQuantification or GADTs to allow this)
+ In the definition of data constructor ‘C2’
+ In the data type declaration for ‘Foo’
diff --git a/testsuite/tests/gadt/gadtSyntaxFail002.stderr b/testsuite/tests/gadt/gadtSyntaxFail002.stderr
index 194275b528..4a969aaa49 100644
--- a/testsuite/tests/gadt/gadtSyntaxFail002.stderr
+++ b/testsuite/tests/gadt/gadtSyntaxFail002.stderr
@@ -1,7 +1,7 @@
-
-gadtSyntaxFail002.hs:8:5:
- Data constructor ‘C2’ has existential type variables, a context, or a specialised result type
- C2 :: forall a. a -> Char -> Foo a a
- (Use ExistentialQuantification or GADTs to allow this)
- In the definition of data constructor ‘C2’
- In the data declaration for ‘Foo’
+
+gadtSyntaxFail002.hs:8:5: error:
+ Data constructor ‘C2’ has existential type variables, a context, or a specialised result type
+ C2 :: forall a. a -> Char -> Foo a a
+ (Use ExistentialQuantification or GADTs to allow this)
+ In the definition of data constructor ‘C2’
+ In the data type declaration for ‘Foo’
diff --git a/testsuite/tests/gadt/gadtSyntaxFail003.stderr b/testsuite/tests/gadt/gadtSyntaxFail003.stderr
index 22f1f41ea9..f8fbeff079 100644
--- a/testsuite/tests/gadt/gadtSyntaxFail003.stderr
+++ b/testsuite/tests/gadt/gadtSyntaxFail003.stderr
@@ -1,7 +1,7 @@
-
-gadtSyntaxFail003.hs:7:5:
- Data constructor ‘C1’ has existential type variables, a context, or a specialised result type
- C1 :: forall b a c. a -> Int -> c -> Foo b a
- (Use ExistentialQuantification or GADTs to allow this)
- In the definition of data constructor ‘C1’
- In the data declaration for ‘Foo’
+
+gadtSyntaxFail003.hs:7:5: error:
+ Data constructor ‘C1’ has existential type variables, a context, or a specialised result type
+ C1 :: forall b a c. a -> Int -> c -> Foo b a
+ (Use ExistentialQuantification or GADTs to allow this)
+ In the definition of data constructor ‘C1’
+ In the data type declaration for ‘Foo’
diff --git a/testsuite/tests/gadt/records-fail1.stderr b/testsuite/tests/gadt/records-fail1.stderr
index aca4d7fea8..6fd871cbf7 100644
--- a/testsuite/tests/gadt/records-fail1.stderr
+++ b/testsuite/tests/gadt/records-fail1.stderr
@@ -1,5 +1,5 @@
-
-records-fail1.hs:7:1:
- Constructors T1 and T4 have a common field ‘x’,
- but have different result types
- In the data declaration for ‘T’
+
+records-fail1.hs:7:1: error:
+ Constructors T1 and T4 have a common field ‘x’,
+ but have different result types
+ In the data type declaration for ‘T’
diff --git a/testsuite/tests/ghci/scripts/T9293.stderr b/testsuite/tests/ghci/scripts/T9293.stderr
index 089704d9b4..a663562a60 100644
--- a/testsuite/tests/ghci/scripts/T9293.stderr
+++ b/testsuite/tests/ghci/scripts/T9293.stderr
@@ -1,19 +1,19 @@
-
-<interactive>:5:1:
- Illegal generalised algebraic data declaration for ‘T’
- (Use GADTs to allow GADTs)
- In the data declaration for ‘T’
-
-ghci057.hs:3:3:
- Data constructor ‘C’ has existential type variables, a context, or a specialised result type
- C :: T Int
- (Use ExistentialQuantification or GADTs to allow this)
- In the definition of data constructor ‘C’
- In the data declaration for ‘T’
-
-ghci057.hs:3:3:
- Data constructor ‘C’ has existential type variables, a context, or a specialised result type
- C :: T Int
- (Use ExistentialQuantification or GADTs to allow this)
- In the definition of data constructor ‘C’
- In the data declaration for ‘T’
+
+<interactive>:5:1: error:
+ Illegal generalised algebraic data declaration for ‘T’
+ (Use GADTs to allow GADTs)
+ In the data declaration for ‘T’
+
+ghci057.hs:3:3: error:
+ Data constructor ‘C’ has existential type variables, a context, or a specialised result type
+ C :: T Int
+ (Use ExistentialQuantification or GADTs to allow this)
+ In the definition of data constructor ‘C’
+ In the data type declaration for ‘T’
+
+ghci057.hs:3:3: error:
+ Data constructor ‘C’ has existential type variables, a context, or a specialised result type
+ C :: T Int
+ (Use ExistentialQuantification or GADTs to allow this)
+ In the definition of data constructor ‘C’
+ In the data type declaration for ‘T’
diff --git a/testsuite/tests/ghci/scripts/ghci057.stderr b/testsuite/tests/ghci/scripts/ghci057.stderr
index 089704d9b4..a663562a60 100644
--- a/testsuite/tests/ghci/scripts/ghci057.stderr
+++ b/testsuite/tests/ghci/scripts/ghci057.stderr
@@ -1,19 +1,19 @@
-
-<interactive>:5:1:
- Illegal generalised algebraic data declaration for ‘T’
- (Use GADTs to allow GADTs)
- In the data declaration for ‘T’
-
-ghci057.hs:3:3:
- Data constructor ‘C’ has existential type variables, a context, or a specialised result type
- C :: T Int
- (Use ExistentialQuantification or GADTs to allow this)
- In the definition of data constructor ‘C’
- In the data declaration for ‘T’
-
-ghci057.hs:3:3:
- Data constructor ‘C’ has existential type variables, a context, or a specialised result type
- C :: T Int
- (Use ExistentialQuantification or GADTs to allow this)
- In the definition of data constructor ‘C’
- In the data declaration for ‘T’
+
+<interactive>:5:1: error:
+ Illegal generalised algebraic data declaration for ‘T’
+ (Use GADTs to allow GADTs)
+ In the data declaration for ‘T’
+
+ghci057.hs:3:3: error:
+ Data constructor ‘C’ has existential type variables, a context, or a specialised result type
+ C :: T Int
+ (Use ExistentialQuantification or GADTs to allow this)
+ In the definition of data constructor ‘C’
+ In the data type declaration for ‘T’
+
+ghci057.hs:3:3: error:
+ Data constructor ‘C’ has existential type variables, a context, or a specialised result type
+ C :: T Int
+ (Use ExistentialQuantification or GADTs to allow this)
+ In the definition of data constructor ‘C’
+ In the data type declaration for ‘T’
diff --git a/testsuite/tests/indexed-types/should_fail/BadSock.stderr b/testsuite/tests/indexed-types/should_fail/BadSock.stderr
index fc3fb54d0c..ed90d8932f 100644
--- a/testsuite/tests/indexed-types/should_fail/BadSock.stderr
+++ b/testsuite/tests/indexed-types/should_fail/BadSock.stderr
@@ -1,5 +1,5 @@
-
-BadSock.hs:30:5:
- Type family ‘Readable’ should have 1 argument, but has been given none
- In the equations for closed type family ‘Foo’
- In the type family declaration for ‘Foo’
+
+BadSock.hs:30:5: error:
+ The type family ‘Readable’ should have 1 argument, but has been given none
+ In the equations for closed type family ‘Foo’
+ In the type family declaration for ‘Foo’
diff --git a/testsuite/tests/indexed-types/should_fail/T2157.stderr b/testsuite/tests/indexed-types/should_fail/T2157.stderr
index 13d436ae43..d2ba6ae53d 100644
--- a/testsuite/tests/indexed-types/should_fail/T2157.stderr
+++ b/testsuite/tests/indexed-types/should_fail/T2157.stderr
@@ -1,4 +1,4 @@
-
-T2157.hs:7:15:
- Type synonym ‘S’ should have 2 arguments, but has been given 1
- In the type instance declaration for ‘F’
+
+T2157.hs:7:15: error:
+ The type synonym ‘S’ should have 2 arguments, but has been given 1
+ In the type instance declaration for ‘F’
diff --git a/testsuite/tests/indexed-types/should_fail/T9433.stderr b/testsuite/tests/indexed-types/should_fail/T9433.stderr
index 51780f177b..bd4ab42878 100644
--- a/testsuite/tests/indexed-types/should_fail/T9433.stderr
+++ b/testsuite/tests/indexed-types/should_fail/T9433.stderr
@@ -1,4 +1,4 @@
-T9433.hs:14:6:
- Type family ‘Id’ should have 1 argument, but has been given none
+T9433.hs:14:6: error:
+ The type family ‘Id’ should have 1 argument, but has been given none
In the type signature for ‘x’: x :: Map Id [Bool]
diff --git a/testsuite/tests/module/mod60.stderr b/testsuite/tests/module/mod60.stderr
index 1cf46b1253..cf94537bb9 100644
--- a/testsuite/tests/module/mod60.stderr
+++ b/testsuite/tests/module/mod60.stderr
@@ -1,5 +1,5 @@
-
-mod60.hs:3:4:
- Constructor ‘Left’ should have 1 argument, but has been given none
- In the pattern: Left
- In an equation for ‘f’: f (Left) = error "foo"
+
+mod60.hs:3:4: error:
+ The constructor ‘Left’ should have 1 argument, but has been given none
+ In the pattern: Left
+ In an equation for ‘f’: f (Left) = error "foo"
diff --git a/testsuite/tests/parser/should_fail/ParserNoBinaryLiterals2.stderr b/testsuite/tests/parser/should_fail/ParserNoBinaryLiterals2.stderr
index 4a756d6e27..6cbd7ca94b 100644
--- a/testsuite/tests/parser/should_fail/ParserNoBinaryLiterals2.stderr
+++ b/testsuite/tests/parser/should_fail/ParserNoBinaryLiterals2.stderr
@@ -1,5 +1,5 @@
-
-ParserNoBinaryLiterals2.hs:8:4:
- Constructor ‘W#’ should have 1 argument, but has been given 2
- In the pattern: W# 0 b0##
- In an equation for ‘f’: f (W# 0 b0##) = ()
+
+ParserNoBinaryLiterals2.hs:8:4: error:
+ The constructor ‘W#’ should have 1 argument, but has been given 2
+ In the pattern: W# 0 b0##
+ In an equation for ‘f’: f (W# 0 b0##) = ()
diff --git a/testsuite/tests/parser/should_fail/ParserNoBinaryLiterals3.stderr b/testsuite/tests/parser/should_fail/ParserNoBinaryLiterals3.stderr
index 32c27e6b8a..1e4c475904 100644
--- a/testsuite/tests/parser/should_fail/ParserNoBinaryLiterals3.stderr
+++ b/testsuite/tests/parser/should_fail/ParserNoBinaryLiterals3.stderr
@@ -1,5 +1,5 @@
-
-ParserNoBinaryLiterals3.hs:8:4:
- Constructor ‘I#’ should have 1 argument, but has been given 2
- In the pattern: I# 0 b0#
- In an equation for ‘f’: f (I# 0 b0#) = ()
+
+ParserNoBinaryLiterals3.hs:8:4: error:
+ The constructor ‘I#’ should have 1 argument, but has been given 2
+ In the pattern: I# 0 b0#
+ In an equation for ‘f’: f (I# 0 b0#) = ()
diff --git a/testsuite/tests/polykinds/T10516.hs b/testsuite/tests/polykinds/T10516.hs
new file mode 100644
index 0000000000..388f3421b8
--- /dev/null
+++ b/testsuite/tests/polykinds/T10516.hs
@@ -0,0 +1,9 @@
+{-# LANGUAGE PolyKinds #-}
+module T10516 where
+
+type App f a = f a
+
+newtype X f a = X (f a)
+
+f :: f a -> X (App f) a
+f = X
diff --git a/testsuite/tests/polykinds/T10516.stderr b/testsuite/tests/polykinds/T10516.stderr
new file mode 100644
index 0000000000..0242722ea5
--- /dev/null
+++ b/testsuite/tests/polykinds/T10516.stderr
@@ -0,0 +1,4 @@
+
+T10516.hs:8:6: error:
+ The type synonym ‘App’ should have 2 arguments, but has been given 1
+ In the type signature for ‘f’: f :: f a -> X (App f) a
diff --git a/testsuite/tests/polykinds/T9222.stderr b/testsuite/tests/polykinds/T9222.stderr
index 01869edd45..1d1a1df779 100644
--- a/testsuite/tests/polykinds/T9222.stderr
+++ b/testsuite/tests/polykinds/T9222.stderr
@@ -1,24 +1,24 @@
-
-T9222.hs:13:3:
- Couldn't match type ‘b0’ with ‘b’
- ‘b0’ is untouchable
- inside the constraints: a ~ '(b0, c0)
- bound by the type of the constructor ‘Want’:
- (a ~ '(b0, c0)) => Proxy b0
- at T9222.hs:13:3
- ‘b’ is a rigid type variable bound by
- the type of the constructor ‘Want’:
- ((a ~ '(b, c)) => Proxy b) -> Want a
- at T9222.hs:13:3
- Expected type: '(b, c)
- Actual type: a
- In the ambiguity check for the type of the constructor ‘Want’:
- Want :: forall (k :: BOX)
- (k1 :: BOX)
- (a :: (,) k k1)
- (b :: k)
- (c :: k1).
- ((a ~ '(b, c)) => Proxy b) -> Want a
- To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
- In the definition of data constructor ‘Want’
- In the data declaration for ‘Want’
+
+T9222.hs:13:3: error:
+ Couldn't match type ‘b0’ with ‘b’
+ ‘b0’ is untouchable
+ inside the constraints: a ~ '(b0, c0)
+ bound by the type of the constructor ‘Want’:
+ (a ~ '(b0, c0)) => Proxy b0
+ at T9222.hs:13:3
+ ‘b’ is a rigid type variable bound by
+ the type of the constructor ‘Want’:
+ ((a ~ '(b, c)) => Proxy b) -> Want a
+ at T9222.hs:13:3
+ Expected type: '(b, c)
+ Actual type: a
+ In the ambiguity check for the type of the constructor ‘Want’:
+ Want :: forall (k :: BOX)
+ (k1 :: BOX)
+ (a :: (,) k k1)
+ (b :: k)
+ (c :: k1).
+ ((a ~ '(b, c)) => Proxy b) -> Want a
+ To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
+ In the definition of data constructor ‘Want’
+ In the data type declaration for ‘Want’
diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T
index 75d2321aad..76af3ecf00 100644
--- a/testsuite/tests/polykinds/all.T
+++ b/testsuite/tests/polykinds/all.T
@@ -116,3 +116,4 @@ test('T9833', normal, compile, [''])
test('T7908', normal, compile, [''])
test('T10041', normal, compile, [''])
test('T10451', normal, compile_fail, [''])
+test('T10516', normal, compile_fail, [''])
diff --git a/testsuite/tests/typecheck/should_compile/T7050.stderr b/testsuite/tests/typecheck/should_compile/T7050.stderr
index a7154f67ac..8a2f9f97e4 100644
--- a/testsuite/tests/typecheck/should_compile/T7050.stderr
+++ b/testsuite/tests/typecheck/should_compile/T7050.stderr
@@ -1,5 +1,5 @@
-
-T7050.hs:3:14: Warning:
- Ignoring unusable UNPACK pragma on the first argument of ‘Foo’
- In the definition of data constructor ‘Foo’
- In the data declaration for ‘Foo’
+
+T7050.hs:3:14: warning:
+ Ignoring unusable UNPACK pragma on the first argument of ‘Foo’
+ In the definition of data constructor ‘Foo’
+ In the data type declaration for ‘Foo’
diff --git a/testsuite/tests/typecheck/should_compile/T7562.stderr b/testsuite/tests/typecheck/should_compile/T7562.stderr
index fb663fc639..448327f996 100644
--- a/testsuite/tests/typecheck/should_compile/T7562.stderr
+++ b/testsuite/tests/typecheck/should_compile/T7562.stderr
@@ -1,5 +1,5 @@
-
-T7562.hs:3:14: Warning:
- UNPACK pragma lacks '!' on the first argument of ‘Pair2’
- In the definition of data constructor ‘Pair2’
- In the data declaration for ‘Pair2’
+
+T7562.hs:3:14: warning:
+ UNPACK pragma lacks '!' on the first argument of ‘Pair2’
+ In the definition of data constructor ‘Pair2’
+ In the data type declaration for ‘Pair2’
diff --git a/testsuite/tests/typecheck/should_fail/T3966.stderr b/testsuite/tests/typecheck/should_fail/T3966.stderr
index 7c98948f0e..a76ede1185 100644
--- a/testsuite/tests/typecheck/should_fail/T3966.stderr
+++ b/testsuite/tests/typecheck/should_fail/T3966.stderr
@@ -1,8 +1,8 @@
-
-T3966.hs:5:16: Warning:
- Ignoring unusable UNPACK pragma on the first argument of ‘Foo’
- In the definition of data constructor ‘Foo’
- In the data declaration for ‘Foo’
-
-<no location info>:
-Failing due to -Werror.
+
+T3966.hs:5:16: warning:
+ Ignoring unusable UNPACK pragma on the first argument of ‘Foo’
+ In the definition of data constructor ‘Foo’
+ In the data type declaration for ‘Foo’
+
+<no location info>: error:
+Failing due to -Werror.
diff --git a/testsuite/tests/typecheck/should_fail/T7175.stderr b/testsuite/tests/typecheck/should_fail/T7175.stderr
index e6a5b1e5a3..25e9365f60 100644
--- a/testsuite/tests/typecheck/should_fail/T7175.stderr
+++ b/testsuite/tests/typecheck/should_fail/T7175.stderr
@@ -1,6 +1,6 @@
-
-T7175.hs:8:4:
- Data constructor ‘G1C’ returns type ‘F Int’
- instead of an instance of its parent type ‘G1 a’
- In the definition of data constructor ‘G1C’
- In the data declaration for ‘G1’
+
+T7175.hs:8:4: error:
+ Data constructor ‘G1C’ returns type ‘F Int’
+ instead of an instance of its parent type ‘G1 a’
+ In the definition of data constructor ‘G1C’
+ In the data type declaration for ‘G1’
diff --git a/testsuite/tests/typecheck/should_fail/tcfail100.stderr b/testsuite/tests/typecheck/should_fail/tcfail100.stderr
index c2bf429fd6..6ed4a4745f 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail100.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail100.stderr
@@ -1,4 +1,4 @@
-
-tcfail100.hs:7:1:
- Type synonym ‘A’ should have 1 argument, but has been given none
- In the type declaration for ‘B’
+
+tcfail100.hs:7:1: error:
+ The type synonym ‘A’ should have 1 argument, but has been given none
+ In the type synonym declaration for ‘B’
diff --git a/testsuite/tests/typecheck/should_fail/tcfail101.stderr b/testsuite/tests/typecheck/should_fail/tcfail101.stderr
index ddf8e433f0..b88b77475e 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail101.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail101.stderr
@@ -1,4 +1,4 @@
-
-tcfail101.hs:9:6:
- Type synonym ‘A’ should have 1 argument, but has been given none
- In the type signature for ‘f’: f :: T A
+
+tcfail101.hs:9:6: error:
+ The type synonym ‘A’ should have 1 argument, but has been given none
+ In the type signature for ‘f’: f :: T A
diff --git a/testsuite/tests/typecheck/should_fail/tcfail107.stderr b/testsuite/tests/typecheck/should_fail/tcfail107.stderr
index 43d0c2d1fd..85f9a2de07 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail107.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail107.stderr
@@ -1,5 +1,5 @@
-
-tcfail107.hs:13:9:
- Type synonym ‘Const’ should have 2 arguments, but has been given 1
- In the type signature for ‘test’:
- test :: Thing (Const Int) -> Thing (Const Int)
+
+tcfail107.hs:13:9: error:
+ The type synonym ‘Const’ should have 2 arguments, but has been given 1
+ In the type signature for ‘test’:
+ test :: Thing (Const Int) -> Thing (Const Int)
diff --git a/testsuite/tests/typecheck/should_fail/tcfail129.stderr b/testsuite/tests/typecheck/should_fail/tcfail129.stderr
index 2c1b4bfb72..331ce03696 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail129.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail129.stderr
@@ -1,12 +1,12 @@
-
-tcfail129.hs:12:21:
- Type synonym ‘Foo’ should have 1 argument, but has been given none
- In an expression type signature: Bar Foo
- In the expression: undefined :: Bar Foo
- In an equation for ‘blah’: blah = undefined :: Bar Foo
-
-tcfail129.hs:17:22:
- Type synonym ‘Foo1’ should have 1 argument, but has been given none
- In an expression type signature: Bar1 Foo1
- In the expression: undefined :: Bar1 Foo1
- In an equation for ‘blah1’: blah1 = undefined :: Bar1 Foo1
+
+tcfail129.hs:12:21: error:
+ The type synonym ‘Foo’ should have 1 argument, but has been given none
+ In an expression type signature: Bar Foo
+ In the expression: undefined :: Bar Foo
+ In an equation for ‘blah’: blah = undefined :: Bar Foo
+
+tcfail129.hs:17:22: error:
+ The type synonym ‘Foo1’ should have 1 argument, but has been given none
+ In an expression type signature: Bar1 Foo1
+ In the expression: undefined :: Bar1 Foo1
+ In an equation for ‘blah1’: blah1 = undefined :: Bar1 Foo1
diff --git a/testsuite/tests/typecheck/should_fail/tcfail140.stderr b/testsuite/tests/typecheck/should_fail/tcfail140.stderr
index 7593497fe2..6908f1d595 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail140.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail140.stderr
@@ -1,5 +1,5 @@
-tcfail140.hs:10:7:
+tcfail140.hs:10:7: error:
Couldn't match expected type ‘Integer -> t’ with actual type ‘Int’
Relevant bindings include bar :: t (bound at tcfail140.hs:10:1)
The function ‘f’ is applied to two arguments,
@@ -7,7 +7,7 @@ tcfail140.hs:10:7:
In the expression: f 3 9
In an equation for ‘bar’: bar = f 3 9
-tcfail140.hs:12:10:
+tcfail140.hs:12:10: error:
Couldn't match expected type ‘Integer -> t1’ with actual type ‘Int’
Relevant bindings include
rot :: t -> t1 (bound at tcfail140.hs:12:1)
@@ -16,7 +16,7 @@ tcfail140.hs:12:10:
In the expression: 3 `f` 4
In an equation for ‘rot’: rot xs = 3 `f` 4
-tcfail140.hs:14:15:
+tcfail140.hs:14:15: error:
Couldn't match expected type ‘a -> b’ with actual type ‘Int’
Relevant bindings include
xs :: [a] (bound at tcfail140.hs:14:5)
@@ -26,13 +26,13 @@ tcfail140.hs:14:15:
In the first argument of ‘map’, namely ‘(3 `f`)’
In the expression: map (3 `f`) xs
-tcfail140.hs:16:8:
- Constructor ‘Just’ should have 1 argument, but has been given none
+tcfail140.hs:16:8: error:
+ The constructor ‘Just’ should have 1 argument, but has been given none
In the pattern: Just
In the expression: (\ Just x -> x) :: Maybe a -> a
In the expression: ((\ Just x -> x) :: Maybe a -> a) (Just 1)
-tcfail140.hs:19:1:
+tcfail140.hs:19:1: error:
Couldn't match expected type ‘t0 -> Bool’ with actual type ‘Int’
The equation(s) for ‘g’ have two arguments,
but its type ‘Int -> Int’ has only one
diff --git a/testsuite/tests/typecheck/should_fail/tcfail155.stderr b/testsuite/tests/typecheck/should_fail/tcfail155.stderr
index 64583eba33..5716f770ee 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail155.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail155.stderr
@@ -1,6 +1,6 @@
-
-tcfail155.hs:8:6:
- Data constructor ‘P’ returns type ‘L2’
- instead of an instance of its parent type ‘T a’
- In the definition of data constructor ‘P’
- In the data declaration for ‘T’
+
+tcfail155.hs:8:6: error:
+ Data constructor ‘P’ returns type ‘L2’
+ instead of an instance of its parent type ‘T a’
+ In the definition of data constructor ‘P’
+ In the data type declaration for ‘T’
diff --git a/testsuite/tests/typecheck/should_fail/tcfail187.stderr b/testsuite/tests/typecheck/should_fail/tcfail187.stderr
index 799485a69f..9dec6bace6 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail187.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail187.stderr
@@ -1,5 +1,5 @@
-
-tcfail187.hs:7:6:
- Constructor ‘:::’ should have no arguments, but has been given 2
- In the pattern: x ::: y
- In an equation for ‘foo’: foo (x ::: y) = ()
+
+tcfail187.hs:7:6: error:
+ The constructor ‘:::’ should have no arguments, but has been given 2
+ In the pattern: x ::: y
+ In an equation for ‘foo’: foo (x ::: y) = ()
diff --git a/testsuite/tests/typecheck/should_fail/tcfail195.stderr b/testsuite/tests/typecheck/should_fail/tcfail195.stderr
index 96d968f8bf..c1cb85abce 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail195.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail195.stderr
@@ -1,5 +1,5 @@
-
-tcfail195.hs:6:3:
- Illegal polymorphic or qualified type: forall a. a
- In the definition of data constructor ‘Foo’
- In the data declaration for ‘Foo’
+
+tcfail195.hs:6:3: error:
+ Illegal polymorphic or qualified type: forall a. a
+ In the definition of data constructor ‘Foo’
+ In the data type declaration for ‘Foo’
diff --git a/testsuite/tests/typecheck/should_fail/tcfail209.stderr b/testsuite/tests/typecheck/should_fail/tcfail209.stderr
index d9a9ca37ae..f4384d9aa2 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail209.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail209.stderr
@@ -1,5 +1,5 @@
-
-tcfail209.hs:3:1:
- Illegal constraint synonym of kind: ‘* -> Constraint’
- (Use ConstraintKinds to permit this)
- In the type declaration for ‘Showish’
+
+tcfail209.hs:3:1: error:
+ Illegal constraint synonym of kind: ‘* -> Constraint’
+ (Use ConstraintKinds to permit this)
+ In the type synonym declaration for ‘Showish’