From 9cd9efb4de3757fd5eaec006739f75cef288e5eb Mon Sep 17 00:00:00 2001 From: Vladislav Zavialov <vlad.z.4096@gmail.com> Date: Tue, 20 Feb 2024 01:49:04 +0300 Subject: [PATCH] Rephrase error message to say "visible arguments" (#24318) * Main change: make the error message generated by mkFunTysMsg more accurate by changing "value arguments" to "visible arguments". * Refactor: define a new type synonym VisArity and use it instead of Arity in a few places. It might be the case that there other places in the compiler that should talk about visible arguments rather than value arguments, but I haven't tried to find them all, focusing only on the error message reported in the ticket. --- compiler/GHC/Tc/Gen/Match.hs | 6 +- compiler/GHC/Tc/Utils/Unify.hs | 25 +++---- compiler/GHC/Types/Basic.hs | 71 ++++++++++++++++++- testsuite/tests/ado/ado002.stderr | 4 +- testsuite/tests/ghci/scripts/Defer02.stderr | 4 +- .../should_compile/T10806.stderr | 2 +- .../indexed-types/should_fail/T8518.stderr | 2 +- testsuite/tests/rep-poly/T23903.stderr | 2 +- testsuite/tests/th/T5358.stderr | 8 +-- .../typecheck/should_fail/DoExpansion2.stderr | 2 +- .../typecheck/should_fail/DoExpansion3.stderr | 2 +- .../tests/typecheck/should_fail/FD1.stderr | 2 +- .../tests/typecheck/should_fail/T13902.stderr | 2 +- .../tests/typecheck/should_fail/T17139.stderr | 2 +- .../tests/typecheck/should_fail/T24318.hs | 8 +++ .../tests/typecheck/should_fail/T24318.stderr | 5 ++ .../tests/typecheck/should_fail/T8603.stderr | 2 +- .../tests/typecheck/should_fail/T9605.stderr | 2 +- testsuite/tests/typecheck/should_fail/all.T | 1 + .../typecheck/should_fail/tcfail001.stderr | 2 +- .../typecheck/should_fail/tcfail140.stderr | 8 +-- .../typecheck/should_fail/tcfail175.stderr | 2 +- .../should_fail/T22326_fail_n_args.stderr | 2 +- .../should_fail/CaretDiagnostics1.stderr | 2 +- 24 files changed, 124 insertions(+), 44 deletions(-) create mode 100644 testsuite/tests/typecheck/should_fail/T24318.hs create mode 100644 testsuite/tests/typecheck/should_fail/T24318.stderr diff --git a/compiler/GHC/Tc/Gen/Match.hs b/compiler/GHC/Tc/Gen/Match.hs index a4b681e7bab1..5ff24e770015 100644 --- a/compiler/GHC/Tc/Gen/Match.hs +++ b/compiler/GHC/Tc/Gen/Match.hs @@ -75,7 +75,7 @@ import GHC.Driver.DynFlags ( getDynFlags ) import GHC.Types.Name import GHC.Types.Id import GHC.Types.SrcLoc -import GHC.Types.Basic( Arity, isDoExpansionGenerated ) +import GHC.Types.Basic( VisArity, isDoExpansionGenerated ) import Control.Monad import Control.Arrow ( second ) @@ -1207,7 +1207,7 @@ the variables they bind into scope, and typecheck the thing_inside. -- The MatchGroup for `f` has arity 2, not 3 checkArgCounts :: AnnoBody body => MatchGroup GhcRn (LocatedA (body GhcRn)) - -> TcM Arity + -> TcM VisArity checkArgCounts (MG { mg_alts = L _ [] }) = return 1 -- See Note [Empty MatchGroups] in GHC.Rename.Bind -- case e of {} or \case {} @@ -1227,6 +1227,6 @@ checkArgCounts (MG { mg_alts = L _ (match1:matches) }) n_args1 = reqd_args_in_match match1 mb_bad_matches = NE.nonEmpty [m | m <- matches, reqd_args_in_match m /= n_args1] - reqd_args_in_match :: LocatedA (Match GhcRn body1) -> Arity + reqd_args_in_match :: LocatedA (Match GhcRn body1) -> VisArity -- Counts the number of /required/ args in the match reqd_args_in_match (L _ (Match { m_pats = pats })) = count (isVisArgPat . unLoc) pats diff --git a/compiler/GHC/Tc/Utils/Unify.hs b/compiler/GHC/Tc/Utils/Unify.hs index 43de138d4aef..18ca79320e1f 100644 --- a/compiler/GHC/Tc/Utils/Unify.hs +++ b/compiler/GHC/Tc/Utils/Unify.hs @@ -751,7 +751,7 @@ Example: matchExpectedFunTys :: forall a. ExpectedFunTyOrigin -- See Note [Herald for matchExpectedFunTys] -> UserTypeCtxt - -> Arity + -> VisArity -> ExpSigmaType -> ([ExpPatType] -> ExpRhoType -> TcM a) -> TcM (HsWrapper, a) @@ -777,7 +777,7 @@ matchExpectedFunTys herald _ arity (Infer inf_res) thing_inside matchExpectedFunTys herald ctx arity (Check top_ty) thing_inside = check 0 [] top_ty where - check :: Arity -> [ExpPatType] -> TcSigmaType -> TcM (HsWrapper, a) + check :: VisArity -> [ExpPatType] -> TcSigmaType -> TcM (HsWrapper, a) -- `check` is called only in the Check{} case -- It collects rev_pat_tys in reversed order -- n_so_far is the number of /visible/ arguments seen so far: @@ -875,7 +875,7 @@ matchExpectedFunTys herald ctx arity (Check top_ty) thing_inside defer n_so_far rev_pat_tys res_ty ------------ - defer :: Arity -> [ExpPatType] -> TcRhoType -> TcM (HsWrapper, a) + defer :: VisArity -> [ExpPatType] -> TcRhoType -> TcM (HsWrapper, a) defer n_so_far rev_pat_tys fun_ty = do { more_arg_tys <- mapM (new_check_arg_ty herald) [n_so_far + 1 .. arity] ; let all_pats = reverse rev_pat_tys ++ map mkCheckExpFunPatTy more_arg_tys @@ -898,19 +898,15 @@ new_check_arg_ty herald arg_pos -- Position for error messages only ; return (mkScaled mult arg_ty) } mkFunTysMsg :: ExpectedFunTyOrigin - -> (Arity, TcType) + -> (VisArity, TcType) -> TidyEnv -> ZonkM (TidyEnv, SDoc) -- See Note [Reporting application arity errors] -mkFunTysMsg herald (n_val_args_in_call, fun_ty) env +mkFunTysMsg herald (n_vis_args_in_call, fun_ty) env = do { (env', fun_ty) <- zonkTidyTcType env fun_ty ; let (pi_ty_bndrs, _) = splitPiTys fun_ty - - -- `all_arg_tys` contains visible quantifiers only, so their number matches - -- the number of arguments that the user needs to pass to the function. n_fun_args = count isVisiblePiTyBinder pi_ty_bndrs - - msg | n_val_args_in_call <= n_fun_args -- Enough args, in the end + msg | n_vis_args_in_call <= n_fun_args -- Enough args, in the end = text "In the result of a function call" | otherwise = hang (full_herald <> comma) @@ -921,7 +917,8 @@ mkFunTysMsg herald (n_val_args_in_call, fun_ty) env ; return (env', msg) } where full_herald = pprExpectedFunTyHerald herald - <+> speakNOf n_val_args_in_call (text "value argument") + <+> speakNOf n_vis_args_in_call (text "visible argument") + -- What are "visible" arguments? See Note [Visibility and arity] in GHC.Types.Basic {- Note [Reporting application arity errors] @@ -931,8 +928,8 @@ and the call foo = f 3 4 5 We'd like to get an error like: • Couldn't match expected type ‘t0 -> t’ with actual type ‘Int’ - • The function ‘f’ is applied to three value arguments, - but its type ‘Int -> Int -> Int’ has only two + • The function ‘f’ is applied to three visible arguments, -- What are "visible" arguments? + but its type ‘Int -> Int -> Int’ has only two -- See Note [Visibility and arity] in GHC.Types.Basic That is what `mkFunTysMsg` tries to do. But what is the "type of the function". Most obviously, we can report its full, polymorphic type; that is simple and @@ -943,7 +940,7 @@ We get this error: • Couldn't match type ‘Int’ with ‘t0 -> t’ Expected: Int -> t0 -> t Actual: Int -> Int - • The function ‘f’ is applied to three value arguments, + • The function ‘f’ is applied to three visible arguments, but its type ‘Bool -> t Int Int’ has only one That's not /quite/ right beause we can instantiate `t` to an arrow and get diff --git a/compiler/GHC/Types/Basic.hs b/compiler/GHC/Types/Basic.hs index 45c353895a6e..5d174347036f 100644 --- a/compiler/GHC/Types/Basic.hs +++ b/compiler/GHC/Types/Basic.hs @@ -28,7 +28,7 @@ module GHC.Types.Basic ( ConTag, ConTagZ, fIRST_TAG, - Arity, RepArity, JoinArity, FullArgCount, + Arity, VisArity, RepArity, JoinArity, FullArgCount, JoinPointHood(..), isJoinPoint, Alignment, mkAlignment, alignmentOf, alignmentBytes, @@ -183,6 +183,10 @@ instance Binary LeftOrRight where -- See also Note [Definition of arity] in "GHC.Core.Opt.Arity" type Arity = Int +-- | Syntactic (visibility) arity, i.e. the number of visible arguments. +-- See Note [Visibility and arity] +type VisArity = Int + -- | Representation Arity -- -- The number of represented arguments that can be applied to a value before it does @@ -203,6 +207,71 @@ type JoinArity = Int -- both type and value arguments! type FullArgCount = Int +{- Note [Visibility and arity] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Arity is the number of arguments that a function expects. In a curried language +like Haskell, there is more than one way to count those arguments. + +* `Arity` is the classic notion of arity, concerned with evalution, so it counts + the number of /value/ arguments that need to be supplied before evaluation can + take place, as described in notes + Note [Definition of arity] in GHC.Core.Opt.Arity + Note [Arity and function types] in GHC.Types.Id.Info + + Examples: + Int has arity == 0 + Int -> Int has arity <= 1 + Int -> Bool -> Int has arity <= 2 + We write (<=) rather than (==) as sometimes evaluation can occur before all + value arguments are supplied, depending on the actual function definition. + + This evaluation-focused notion of arity ignores type arguments, so: + forall a. a has arity == 0 + forall a. a -> a has arity <= 1 + forall a b. a -> b -> a has arity <= 2 + This is true regardless of ForAllTyFlag, so the arity is also unaffected by + (forall {a}. ty) or (forall a -> ty). + + Class dictionaries count towards the arity, as they are passed at runtime + forall a. (Num a) => a has arity <= 1 + forall a. (Num a) => a -> a has arity <= 2 + forall a b. (Num a, Ord b) => a -> b -> a has arity <= 4 + +* `VisArity` is the syntactic notion of arity. It is the number of /visible/ + arguments, i.e. arguments that occur visibly in the source code. + + In a function call `f x y z`, we can confidently say that f's vis-arity >= 3, + simply because we see three arguments [x,y,z]. We write (>=) rather than (==) + as this could be a partial application. + + At definition sites, we can acquire an underapproximation of vis-arity by + counting the patterns on the LHS, e.g. `f a b = rhs` has vis-arity >= 2. + The actual vis-arity can be higher if there is a lambda on the RHS, + e.g. `f a b = \c -> rhs`. + + If we look at the types, we can observe the following + * function arrows (a -> b) add to the vis-arity + * visible foralls (forall a -> b) add to the vis-arity + * constraint arrows (a => b) do not affect the vis-arity + * invisible foralls (forall a. b) do not affect the vis-arity + + This means that ForAllTyFlag matters for VisArity (in contrast to Arity), + while the type/value distinction is unimportant (again in contrast to Arity). + + Examples: + Int -- vis-arity == 0 (no args) + Int -> Int -- vis-arity == 1 (1 funarg) + forall a. a -> a -- vis-arity == 1 (1 funarg) + forall a. Num a => a -> a -- vis-arity == 1 (1 funarg) + forall a -> Num a => a -- vis-arity == 1 (1 req tyarg, 0 funargs) + forall a -> a -> a -- vis-arity == 2 (1 req tyarg, 1 funarg) + Int -> forall a -> Int -- vis-arity == 2 (1 funarg, 1 req tyarg) + + Wrinkle: with TypeApplications and TypeAbstractions, it is possible to visibly + bind and pass invisible arguments, e.g. `f @a x = ...` or `f @Int 42`. Those + @-prefixed arguments are ignored for the purposes of vis-arity. +-} + {- ************************************************************************ * * diff --git a/testsuite/tests/ado/ado002.stderr b/testsuite/tests/ado/ado002.stderr index e27585060b2a..bac041915e0c 100644 --- a/testsuite/tests/ado/ado002.stderr +++ b/testsuite/tests/ado/ado002.stderr @@ -2,7 +2,7 @@ ado002.hs:8:8: error: [GHC-83865] • Couldn't match expected type: Char -> IO b0 with actual type: IO Char - • The function ‘getChar’ is applied to one value argument, + • The function ‘getChar’ is applied to one visible argument, but its type ‘IO Char’ has none In a stmt of a 'do' block: y <- getChar 'a' In the expression: @@ -45,7 +45,7 @@ ado002.hs:15:13: error: [GHC-83865] ado002.hs:23:9: error: [GHC-83865] • Couldn't match expected type: Char -> IO a0 with actual type: IO Char - • The function ‘getChar’ is applied to one value argument, + • The function ‘getChar’ is applied to one visible argument, but its type ‘IO Char’ has none In a stmt of a 'do' block: x5 <- getChar x4 In the expression: diff --git a/testsuite/tests/ghci/scripts/Defer02.stderr b/testsuite/tests/ghci/scripts/Defer02.stderr index f0698cf8cc7c..b855c0f82062 100644 --- a/testsuite/tests/ghci/scripts/Defer02.stderr +++ b/testsuite/tests/ghci/scripts/Defer02.stderr @@ -26,7 +26,7 @@ Defer01.hs:24:4: warning: [GHC-40564] [-Winaccessible-code (in -Wdefault)] Defer01.hs:30:5: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)] • Couldn't match expected type ‘Char -> t’ with actual type ‘Char’ - • The function ‘e’ is applied to one value argument, + • The function ‘e’ is applied to one visible argument, but its type ‘Char’ has none In the expression: e 'q' In an equation for ‘f’: f = e 'q' @@ -95,7 +95,7 @@ Defer01.hs:49:5: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)] (deferred type error) *** Exception: Defer01.hs:30:5: error: [GHC-83865] • Couldn't match expected type ‘Char -> t’ with actual type ‘Char’ - • The function ‘e’ is applied to one value argument, + • The function ‘e’ is applied to one visible argument, but its type ‘Char’ has none In the expression: e 'q' In an equation for ‘f’: f = e 'q' diff --git a/testsuite/tests/indexed-types/should_compile/T10806.stderr b/testsuite/tests/indexed-types/should_compile/T10806.stderr index 79183d9d478c..48a7c24a35f7 100644 --- a/testsuite/tests/indexed-types/should_compile/T10806.stderr +++ b/testsuite/tests/indexed-types/should_compile/T10806.stderr @@ -2,7 +2,7 @@ T10806.hs:11:32: error: [GHC-83865] • Couldn't match expected type: Char -> Bool with actual type: IO () - • The function ‘print’ is applied to two value arguments, + • The function ‘print’ is applied to two visible arguments, but its type ‘Show a => a -> IO ()’ has only one In the expression: print 'x' 'y' In an equation for ‘triggersLoop’: diff --git a/testsuite/tests/indexed-types/should_fail/T8518.stderr b/testsuite/tests/indexed-types/should_fail/T8518.stderr index 1e79ce4324a5..8caeee43f65b 100644 --- a/testsuite/tests/indexed-types/should_fail/T8518.stderr +++ b/testsuite/tests/indexed-types/should_fail/T8518.stderr @@ -2,7 +2,7 @@ T8518.hs:14:18: error: [GHC-83865] • Couldn't match expected type: Z c -> B c -> t0 with actual type: F c - • The function ‘rpt’ is applied to four value arguments, + • The function ‘rpt’ is applied to four visible arguments, but its type ‘t1 -> t2 -> F t2’ has only two In the expression: rpt (4 :: Int) c z b In an equation for ‘callCont’: diff --git a/testsuite/tests/rep-poly/T23903.stderr b/testsuite/tests/rep-poly/T23903.stderr index ec4ba3b21c92..d8a0fc3d6622 100644 --- a/testsuite/tests/rep-poly/T23903.stderr +++ b/testsuite/tests/rep-poly/T23903.stderr @@ -6,5 +6,5 @@ T23903.hs:21:1: error: [GHC-55287] t0 :: TYPE cx0 Cannot unify ‘Rep a’ with the type variable ‘cx0’ because the former is not a concrete ‘RuntimeRep’. - • The equation for ‘f’ has one value argument, + • The equation for ‘f’ has one visible argument, but its type ‘a #-> ()’ has none diff --git a/testsuite/tests/th/T5358.stderr b/testsuite/tests/th/T5358.stderr index efca289b75b3..fc753fedde64 100644 --- a/testsuite/tests/th/T5358.stderr +++ b/testsuite/tests/th/T5358.stderr @@ -1,17 +1,17 @@ T5358.hs:7:1: error: [GHC-83865] • Couldn't match expected type ‘Int’ with actual type ‘t1 -> t1’ - • The equation for ‘t1’ has one value argument, + • The equation for ‘t1’ has one visible argument, but its type ‘Int’ has none T5358.hs:8:1: error: [GHC-83865] • Couldn't match expected type ‘Int’ with actual type ‘t0 -> t0’ - • The equation for ‘t2’ has one value argument, + • The equation for ‘t2’ has one visible argument, but its type ‘Int’ has none T5358.hs:10:13: error: [GHC-83865] • Couldn't match expected type ‘t -> a0’ with actual type ‘Int’ - • The function ‘t1’ is applied to one value argument, + • The function ‘t1’ is applied to one visible argument, but its type ‘Int’ has none In the first argument of ‘(==)’, namely ‘t1 x’ In the expression: t1 x == t2 x @@ -21,7 +21,7 @@ T5358.hs:10:13: error: [GHC-83865] T5358.hs:10:21: error: [GHC-83865] • Couldn't match expected type ‘t -> a0’ with actual type ‘Int’ - • The function ‘t2’ is applied to one value argument, + • The function ‘t2’ is applied to one visible argument, but its type ‘Int’ has none In the second argument of ‘(==)’, namely ‘t2 x’ In the expression: t1 x == t2 x diff --git a/testsuite/tests/typecheck/should_fail/DoExpansion2.stderr b/testsuite/tests/typecheck/should_fail/DoExpansion2.stderr index 044fb871169b..1889099522d1 100644 --- a/testsuite/tests/typecheck/should_fail/DoExpansion2.stderr +++ b/testsuite/tests/typecheck/should_fail/DoExpansion2.stderr @@ -55,7 +55,7 @@ DoExpansion2.hs:31:19: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefaul DoExpansion2.hs:34:22: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)] • Couldn't match expected type: t0 -> IO (Maybe Int) with actual type: IO String - • The function ‘getVal’ is applied to two value arguments, + • The function ‘getVal’ is applied to two visible arguments, but its type ‘Int -> IO String’ has only one In a stmt of a 'do' block: Just x <- getVal 3 4 In the expression: diff --git a/testsuite/tests/typecheck/should_fail/DoExpansion3.stderr b/testsuite/tests/typecheck/should_fail/DoExpansion3.stderr index 1dd19692edb4..4843d69b8b98 100644 --- a/testsuite/tests/typecheck/should_fail/DoExpansion3.stderr +++ b/testsuite/tests/typecheck/should_fail/DoExpansion3.stderr @@ -10,7 +10,7 @@ DoExpansion3.hs:15:20: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefaul DoExpansion3.hs:18:20: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)] • Couldn't match expected type: t0 -> t with actual type: IO Char - • The function ‘getChar’ is applied to one value argument, + • The function ‘getChar’ is applied to one visible argument, but its type ‘IO Char’ has none In the expression: getChar 2 In an equation for ‘y’: y = getChar 2 diff --git a/testsuite/tests/typecheck/should_fail/FD1.stderr b/testsuite/tests/typecheck/should_fail/FD1.stderr index e8543108355d..cfabb8c63bc4 100644 --- a/testsuite/tests/typecheck/should_fail/FD1.stderr +++ b/testsuite/tests/typecheck/should_fail/FD1.stderr @@ -5,6 +5,6 @@ FD1.hs:16:1: error: [GHC-25897] the type signature for: plus :: forall a. E a (Int -> Int) => Int -> a at FD1.hs:15:1-38 - • The equation for ‘plus’ has two value arguments, + • The equation for ‘plus’ has two visible arguments, but its type ‘Int -> a’ has only one • Relevant bindings include plus :: Int -> a (bound at FD1.hs:16:1) diff --git a/testsuite/tests/typecheck/should_fail/T13902.stderr b/testsuite/tests/typecheck/should_fail/T13902.stderr index 9a274da40755..33c54cc4e9b4 100644 --- a/testsuite/tests/typecheck/should_fail/T13902.stderr +++ b/testsuite/tests/typecheck/should_fail/T13902.stderr @@ -1,7 +1,7 @@ T13902.hs:8:5: error: [GHC-83865] • Couldn't match expected type ‘t0 -> Int’ with actual type ‘Int’ - • The function ‘f’ is applied to two value arguments, + • The function ‘f’ is applied to two visible arguments, but its type ‘a -> a’ has only one In the expression: f @Int 42 5 In an equation for ‘g’: g = f @Int 42 5 diff --git a/testsuite/tests/typecheck/should_fail/T17139.stderr b/testsuite/tests/typecheck/should_fail/T17139.stderr index e30aa2f5b00b..9293183adbd4 100644 --- a/testsuite/tests/typecheck/should_fail/T17139.stderr +++ b/testsuite/tests/typecheck/should_fail/T17139.stderr @@ -7,7 +7,7 @@ T17139.hs:15:16: error: [GHC-88464] lift :: forall a b (f :: * -> *). (a -> b) -> TypeFam f (a -> b) at T17139.hs:14:1-38 • In the expression: _ (f <*> x) - The lambda expression ‘\ x -> ...’ has one value argument, + The lambda expression ‘\ x -> ...’ has one visible argument, but its type ‘TypeFam f (a -> b)’ has none In the expression: \ x -> _ (f <*> x) • Relevant bindings include diff --git a/testsuite/tests/typecheck/should_fail/T24318.hs b/testsuite/tests/typecheck/should_fail/T24318.hs new file mode 100644 index 000000000000..bb4d2097895f --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T24318.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE ExplicitNamespaces, RequiredTypeArguments #-} + +module T24318 where + +import Data.Kind + +f :: forall (a :: Type) -> Bool +f (type t) x = True diff --git a/testsuite/tests/typecheck/should_fail/T24318.stderr b/testsuite/tests/typecheck/should_fail/T24318.stderr new file mode 100644 index 000000000000..58249ae53855 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T24318.stderr @@ -0,0 +1,5 @@ + +T24318.hs:8:1: error: [GHC-83865] + • Couldn't match expected type ‘Bool’ with actual type ‘t0 -> Bool’ + • The equation for ‘f’ has two visible arguments, + but its type ‘forall a -> Bool’ has only one diff --git a/testsuite/tests/typecheck/should_fail/T8603.stderr b/testsuite/tests/typecheck/should_fail/T8603.stderr index c4cea94e5199..4e9a4349c2a4 100644 --- a/testsuite/tests/typecheck/should_fail/T8603.stderr +++ b/testsuite/tests/typecheck/should_fail/T8603.stderr @@ -6,7 +6,7 @@ T8603.hs:33:17: error: [GHC-18872] [a2] :: * Expected: [a2] -> StateT s RV a0 Actual: t0 ((->) [a1]) (StateT s RV a0) - • The function ‘lift’ is applied to two value arguments, + • The function ‘lift’ is applied to two visible arguments, but its type ‘(Control.Monad.Trans.Class.MonadTrans t, Monad m) => m a -> t m a’ has only one diff --git a/testsuite/tests/typecheck/should_fail/T9605.stderr b/testsuite/tests/typecheck/should_fail/T9605.stderr index 9bb8a11b3ad5..8cac9562a532 100644 --- a/testsuite/tests/typecheck/should_fail/T9605.stderr +++ b/testsuite/tests/typecheck/should_fail/T9605.stderr @@ -3,7 +3,7 @@ T9605.hs:7:6: error: [GHC-83865] • Couldn't match type ‘Bool’ with ‘m Bool’ Expected: t0 -> m Bool Actual: t0 -> Bool - • The function ‘f1’ is applied to one value argument, + • The function ‘f1’ is applied to one visible argument, but its type ‘Monad m => m Bool’ has none In the expression: f1 undefined In an equation for ‘f2’: f2 = f1 undefined diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 6aa934348f51..1c782f971df7 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -712,6 +712,7 @@ test('ErrorIndexLinks', normal, compile_fail, ['-fprint-error-index-links=always test('T24064', normal, compile_fail, ['']) test('T24298', normal, compile_fail, ['']) test('T24279', normal, compile_fail, ['']) +test('T24318', normal, compile_fail, ['']) # all the various do expansion fail messages test('DoExpansion1', normal, compile, ['-fdefer-type-errors']) diff --git a/testsuite/tests/typecheck/should_fail/tcfail001.stderr b/testsuite/tests/typecheck/should_fail/tcfail001.stderr index eecffc35c4ac..a60135664c71 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail001.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail001.stderr @@ -2,7 +2,7 @@ tcfail001.hs:9:2: error: [GHC-83865] • Couldn't match expected type: [a] with actual type: [a0] -> [a1] - • The equation for ‘op’ has one value argument, + • The equation for ‘op’ has one visible argument, but its type ‘[a]’ has none In the instance declaration for ‘A [a]’ • Relevant bindings include op :: [a] (bound at tcfail001.hs:9:2) diff --git a/testsuite/tests/typecheck/should_fail/tcfail140.stderr b/testsuite/tests/typecheck/should_fail/tcfail140.stderr index baad29fe53c5..dc3b262fcad3 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail140.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail140.stderr @@ -1,7 +1,7 @@ tcfail140.hs:11:7: error: [GHC-83865] • Couldn't match expected type ‘t1 -> t’ with actual type ‘Int’ - • The function ‘f’ is applied to two value arguments, + • The function ‘f’ is applied to two visible arguments, but its type ‘Int -> Int’ has only one In the expression: f 3 9 In an equation for ‘bar’: bar = f 3 9 @@ -9,7 +9,7 @@ tcfail140.hs:11:7: error: [GHC-83865] tcfail140.hs:13:10: error: [GHC-83865] • Couldn't match expected type ‘t2 -> t’ with actual type ‘Int’ - • The function ‘f’ is applied to two value arguments, + • The function ‘f’ is applied to two visible arguments, but its type ‘Int -> Int’ has only one In the expression: 3 `f` 4 In an equation for ‘rot’: rot xs = 3 `f` 4 @@ -28,11 +28,11 @@ tcfail140.hs:15:15: error: [GHC-83865] tcfail140.hs:17:8: error: [GHC-27346] • The data constructor ‘Just’ should have 1 argument, but has been given none • In the pattern: Just - The lambda expression ‘\ Just x -> ...’ has two value arguments, + The lambda expression ‘\ Just x -> ...’ has two visible arguments, but its type ‘Maybe a -> a’ has only one In the expression: ((\ Just x -> x) :: Maybe a -> a) (Just 1) tcfail140.hs:20:1: error: [GHC-83865] • Couldn't match expected type ‘Int’ with actual type ‘t0 -> Bool’ - • The equation for ‘g’ has two value arguments, + • The equation for ‘g’ has two visible arguments, but its type ‘Int -> Int’ has only one diff --git a/testsuite/tests/typecheck/should_fail/tcfail175.stderr b/testsuite/tests/typecheck/should_fail/tcfail175.stderr index 1ceec972d48b..43718760a86c 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail175.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail175.stderr @@ -6,7 +6,7 @@ tcfail175.hs:11:1: error: [GHC-25897] the type signature for: evalRHS :: forall a. Int -> a at tcfail175.hs:10:1-19 - • The equation for ‘evalRHS’ has three value arguments, + • The equation for ‘evalRHS’ has three visible arguments, but its type ‘Int -> a’ has only one • Relevant bindings include evalRHS :: Int -> a (bound at tcfail175.hs:11:1) diff --git a/testsuite/tests/vdq-rta/should_fail/T22326_fail_n_args.stderr b/testsuite/tests/vdq-rta/should_fail/T22326_fail_n_args.stderr index 32984f57391b..3e991c9fb605 100644 --- a/testsuite/tests/vdq-rta/should_fail/T22326_fail_n_args.stderr +++ b/testsuite/tests/vdq-rta/should_fail/T22326_fail_n_args.stderr @@ -5,5 +5,5 @@ T22326_fail_n_args.hs:6:1: error: [GHC-25897] the type signature for: f :: a -> forall b -> b at T22326_fail_n_args.hs:6:1-26 - • The equation for ‘f’ has three value arguments, + • The equation for ‘f’ has three visible arguments, but its type ‘a -> forall b -> b’ has only two diff --git a/testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr b/testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr index 354ccadaa0b5..b3f74bae0dbb 100644 --- a/testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr +++ b/testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr @@ -37,7 +37,7 @@ CaretDiagnostics1.hs:13:7-11: error: [GHC-83865] CaretDiagnostics1.hs:(13,16)-(14,13): error: [GHC-83865] • Couldn't match expected type ‘Char -> t0’ with actual type ‘()’ - • The function ‘()’ is applied to one value argument, + • The function ‘()’ is applied to one visible argument, but its type ‘()’ has none In the expression: () '0' In a case alternative: "γηξ" -> () '0' -- GitLab