From ad56fd846a829f0ae287defc37b84265f3d4af39 Mon Sep 17 00:00:00 2001 From: Jade <Nils.Jadefalke@gmail.com> Date: Mon, 20 May 2024 22:45:51 +0200 Subject: [PATCH] Replace 'NB' with 'Note' in error messages --- compiler/GHC/Tc/Errors/Ppr.hs | 78 ++++++++----------- .../backpack/should_fail/bkpfail24.stderr | 12 +-- .../backpack/should_fail/bkpfail49.stderr | 10 +-- .../should_fail/BadTelescope4.stderr | 8 +- .../dependent/should_fail/T14066g.stderr | 4 +- .../dependent/should_fail/T15591b.stderr | 5 +- .../dependent/should_fail/T15591c.stderr | 5 +- .../dependent/should_fail/T15743c.stderr | 5 +- .../dependent/should_fail/T15743d.stderr | 4 +- .../tests/deriving/should_fail/T1496.stderr | 6 +- .../tests/deriving/should_fail/T5498.stderr | 6 +- .../tests/deriving/should_fail/T8984.stderr | 6 +- testsuite/tests/ghci/scripts/T2452.stderr | 6 +- testsuite/tests/ghci/scripts/T8639.stderr | 4 +- testsuite/tests/ghci/scripts/T8649.stderr | 6 +- testsuite/tests/ghci/scripts/ghci036.stderr | 4 +- testsuite/tests/ghci/scripts/ghci051.stderr | 6 +- testsuite/tests/ghci/scripts/ghci052.stderr | 18 ++--- testsuite/tests/ghci/scripts/ghci053.stderr | 10 +-- .../should_compile/T3208b.stderr | 4 +- .../should_fail/NoMatchErr.stderr | 6 +- .../indexed-types/should_fail/T14887.stderr | 4 +- .../indexed-types/should_fail/T15764.stderr | 8 +- .../indexed-types/should_fail/T1897b.stderr | 6 +- .../indexed-types/should_fail/T1900.stderr | 6 +- .../indexed-types/should_fail/T2544.stderr | 10 +-- .../indexed-types/should_fail/T4099.stderr | 8 +- .../indexed-types/should_fail/T4179.stderr | 4 +- .../indexed-types/should_fail/T9036.stderr | 6 +- .../indexed-types/should_fail/T9171.stderr | 6 +- testsuite/tests/module/mod180.stderr | 6 +- testsuite/tests/module/mod73.stderr | 4 +- testsuite/tests/module/mod74.stderr | 4 +- .../should_fail/T21946.stderr | 4 +- .../quantified-constraints/T15290a.stderr | 6 +- .../quantified-constraints/T15290b.stderr | 6 +- .../tests/rename/should_compile/T20472.stderr | 6 +- .../tests/rename/should_fail/T10781.stderr | 4 +- .../tests/rename/should_fail/T11071.stderr | 12 +-- .../tests/rename/should_fail/T19843k.stderr | 4 +- .../tests/rename/should_fail/T21605a.stderr | 4 +- .../tests/rename/should_fail/T21605b.stderr | 4 +- .../tests/rename/should_fail/T2901.stderr | 4 +- .../tests/rename/should_fail/T5657.stderr | 4 +- .../tests/rename/should_fail/rnfail055.stderr | 7 +- .../tests/roles/should_fail/Roles12.stderr | 4 +- .../tests/roles/should_fail/T23252.stderr | 4 +- .../tests/roles/should_fail/T9204.stderr | 4 +- testsuite/tests/safeHaskell/ghci/p4.stderr | 4 +- .../tests/typecheck/bug1465/bug1465.stderr | 6 +- .../typecheck/should_compile/T15368.stderr | 6 +- .../typecheck/should_compile/T23156.stderr | 6 +- .../tests/typecheck/should_fail/T19627.stderr | 8 +- .../tests/typecheck/should_fail/T21158.stderr | 10 +-- .../should_fail/T22560_fail_a.stderr | 6 +- .../should_fail/T22560_fail_b.stderr | 6 +- .../tests/typecheck/should_fail/T8030.stderr | 10 +-- .../tests/typecheck/should_fail/T8034.stderr | 6 +- .../should_fail/TcCoercibleFail.stderr | 6 +- .../typecheck/should_fail/tcfail182.stderr | 10 +-- .../warnings/should_compile/T18862b.stderr | 8 +- 61 files changed, 223 insertions(+), 231 deletions(-) diff --git a/compiler/GHC/Tc/Errors/Ppr.hs b/compiler/GHC/Tc/Errors/Ppr.hs index 9a14a02010d1..cba874bb5a88 100644 --- a/compiler/GHC/Tc/Errors/Ppr.hs +++ b/compiler/GHC/Tc/Errors/Ppr.hs @@ -7,6 +7,7 @@ {-# LANGUAGE ViewPatterns #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE OverloadedStrings #-} {-# OPTIONS_GHC -fno-warn-orphans #-} -- instance Diagnostic TcRnMessage {-# LANGUAGE InstanceSigs #-} @@ -738,7 +739,7 @@ instance Diagnostic TcRnMessage where what = text "type constructor" <+> quotes (ppr (RecSelData tc)) pat_syn_msg | any (\case { RecSelPatSyn {} -> True; _ -> False}) pars - = text "NB: type-directed disambiguation is not supported for pattern synonym record fields." + = note "Type-directed disambiguation is not supported for pattern synonym record fields" | otherwise = empty TcRnStaticFormNotClosed name reason @@ -798,9 +799,9 @@ instance Diagnostic TcRnMessage where -> mkDecorated [ text "The" <+> quotes (text "~") <+> text "operator is out of scope." $$ text "Assuming it to stand for an equality constraint." - , text "NB:" <+> (quotes (text "~") <+> text "used to be built-in syntax but now is a regular type operator" $$ - text "exported from Data.Type.Equality and Prelude.") $$ - text "If you are using a custom Prelude, consider re-exporting it." + , note $ quotes "~" <+> "used to be built-in syntax but now is a regular type operator" $$ + "exported from Data.Type.Equality and Prelude." $$ + "If you are using a custom Prelude, consider re-exporting it" , text "This will become an error in a future GHC release." ] TcRnTypeEqualityRequiresOperators -> mkSimpleDecorated $ @@ -1544,15 +1545,14 @@ instance Diagnostic TcRnMessage where | null inferred_tvs && null specified_tvs = empty | null inferred_tvs - = hang (text "NB: Specified variables") - 2 (sep [pp_spec, text "always come first"]) + = note $ "Specified variables" <+> pp_spec <+> "always come first" | null specified_tvs - = hang (text "NB: Inferred variables") - 2 (sep [pp_inf, text "always come first"]) + = note inf_always_first | otherwise - = hang (text "NB: Inferred variables") - 2 (vcat [ sep [ pp_inf, text "always come first"] - , sep [text "then Specified variables", pp_spec]]) + = note $ inf_always_first $$ + "then specified variables" <+> pp_spec + + inf_always_first = "Inferred variables" <+> pp_inf $$ "always come first" pp_inf = parens (text "namely:" <+> pprTyVars inferred_tvs) pp_spec = parens (text "namely:" <+> pprTyVars specified_tvs) @@ -1864,9 +1864,9 @@ instance Diagnostic TcRnMessage where 2 (ppr hs_bndr) , text "There is no matching forall-bound variable" , text "in the standalone kind signature for" <+> quotes (ppr name) <> dot - , text "NB." <+> vcat [ - text "Only" <+> quotes (text "forall a.") <+> text "-quantification matches invisible binders,", - text "whereas" <+> quotes (text "forall {a}.") <+> text "and" <+> quotes (text "forall a ->") <+> text "do not." + , note $ vcat [ + "Only" <+> quotes "forall a." <+> "-quantification matches invisible binders,", + "whereas" <+> quotes "forall {a}." <+> "and" <+> quotes "forall a ->" <+> "do not" ]] TcRnDeprecatedInvisTyArgInConPat -> @@ -3255,6 +3255,10 @@ instance Diagnostic TcRnMessage where diagnosticCode = constructorCode + +note :: SDoc -> SDoc +note note = "Note" <> colon <+> note <> dot + -- | Change [x] to "x", [x, y] to "x and y", [x, y, z] to "x, y, and z", -- and so on. The `and` stands for any `conjunction`, which is passed in. commafyWith :: SDoc -> [SDoc] -> [SDoc] @@ -4279,7 +4283,7 @@ pprMismatchMsg ctxt _ -> Nothing -- Must be TupleRep [r1..rn] | otherwise = Nothing - starts_with_vowel (c:_) = c `elem` "AEIOU" + starts_with_vowel (c:_) = c `elem` ("AEIOU" :: String) starts_with_vowel [] = False pprMismatchMsg ctxt (CouldNotDeduce useful_givens (item :| others) mb_extra) @@ -4590,13 +4594,10 @@ pprExpectedActualInfo _ pprCoercibleMsg :: CoercibleMsg -> SDoc pprCoercibleMsg (UnknownRoles ty) = - hang (text "NB: We cannot know what roles the parameters to" <+> - quotes (ppr ty) <+> text "have;") - 2 (text "we must assume that the role is nominal") + note $ "We cannot know what roles the parameters to" <+> quotes (ppr ty) <+> "have;" $$ + "we must assume that the role is nominal" pprCoercibleMsg (TyConIsAbstract tc) = - hsep [ text "NB: The type constructor" - , quotes (pprSourceTyCon tc) - , text "is abstract" ] + note $ "The type constructor" <+> quotes (pprSourceTyCon tc) <+> "is abstract" pprCoercibleMsg (OutOfScopeNewtypeConstructor tc dc) = hang (text "The data constructor" <+> quotes (ppr $ dataConName dc)) 2 (sep [ text "of newtype" <+> quotes (pprSourceTyCon tc) @@ -4658,12 +4659,11 @@ pprAmbiguityInfo (Ambiguity prepend_msg (ambig_kvs, ambig_tvs)) = msg = text "The" <+> what <+> text "variable" <> plural tkvs <+> pprQuotedList tkvs <+> isOrAre tkvs <+> text "ambiguous" pprAmbiguityInfo (NonInjectiveTyFam tc) = - text "NB:" <+> quotes (ppr tc) - <+> text "is a non-injective type family" + note $ quotes (ppr tc) <+> text "is a non-injective type family" pprSameOccInfo :: SameOccInfo -> SDoc pprSameOccInfo (SameOcc same_pkg n1 n2) = - text "NB:" <+> (ppr_from same_pkg n1 $$ ppr_from same_pkg n2) + note (ppr_from same_pkg n1 $$ ppr_from same_pkg n2) where ppr_from same_pkg nm | isGoodSrcSpan loc @@ -4939,25 +4939,14 @@ This initially came up in #8968, concerning pattern synonyms. **********************************************************************-} instance Outputable ImportError where - ppr (MissingModule mod_name) = - hsep - [ text "NB: no module named" - , quotes (ppr mod_name) - , text "is imported." - ] - ppr (ModulesDoNotExport mods occ_name) - | mod NE.:| [] <- mods - = hsep - [ text "NB: the module" - , quotes (ppr mod) - , text "does not export" - , quotes (ppr occ_name) <> dot ] - | otherwise - = hsep - [ text "NB: neither" - , quotedListWithNor (map ppr $ NE.toList mods) - , text "export" - , quotes (ppr occ_name) <> dot ] + ppr err = note $ case err of + MissingModule mod_name -> "No module named" <+> quoted mod_name <+> "is imported" + ModulesDoNotExport mods occ_name + | mod NE.:| [] <- mods -> "The module" <+> quoted mod <+> "does not export" <+> quoted occ_name + | otherwise -> "Neither" <+> quotedListWithNor (map ppr $ NE.toList mods) <+> "export" <+> quoted occ_name + where + quoted :: Outputable a => a -> SDoc + quoted = quotes . ppr {- ********************************************************************* * * @@ -5919,8 +5908,7 @@ pprBootTyConMismatch boot_or_sig tc1 tc2 = \case else text "The roles do not match." $$ if boot_or_sig == HsBoot - then text "NB: roles on abstract types default to" <+> - quotes (text "representational") <+> text "in hs-boot files." + then note $ "Roles on abstract types default to" <+> quotes "representational" <+> "in hs-boot files" else empty TyConSynonymMismatch {} -> empty -- nothing interesting to say TyConFlavourMismatch fam_flav1 fam_flav2 -> diff --git a/testsuite/tests/backpack/should_fail/bkpfail24.stderr b/testsuite/tests/backpack/should_fail/bkpfail24.stderr index aa335397571c..1a80c99610db 100644 --- a/testsuite/tests/backpack/should_fail/bkpfail24.stderr +++ b/testsuite/tests/backpack/should_fail/bkpfail24.stderr @@ -1,8 +1,7 @@ [1 of 1] Processing p - [1 of 3] Compiling H1[sig] ( p\H1.hsig, nothing ) - [2 of 3] Compiling H2[sig] ( p\H2.hsig, nothing ) - [3 of 3] Compiling M ( p\M.hs, nothing ) - + [1 of 3] Compiling H1[sig] ( p/H1.hsig, nothing ) + [2 of 3] Compiling H2[sig] ( p/H2.hsig, nothing ) + [3 of 3] Compiling M ( p/M.hs, nothing ) bkpfail24.bkp:14:15: error: [GHC-25897] • Could not deduce ‘a ~ b’ from the context: {H1.T} ~ {H2.T} @@ -25,7 +24,8 @@ bkpfail24.bkp:14:15: error: [GHC-25897] bkpfail24.bkp:19:15: error: [GHC-83865] • Couldn't match expected type ‘{H2.T}’ with actual type ‘{H1.T}’ - NB: ‘{H2.T}’ is defined at bkpfail24.bkp:6:9-14 - ‘{H1.T}’ is defined at bkpfail24.bkp:4:9-14 + Note: ‘{H2.T}’ is defined at bkpfail24.bkp:6:9-14 + ‘{H1.T}’ is defined at bkpfail24.bkp:4:9-14. • In the expression: x In an equation for ‘g’: g x = x + diff --git a/testsuite/tests/backpack/should_fail/bkpfail49.stderr b/testsuite/tests/backpack/should_fail/bkpfail49.stderr index fa1fa5420769..e6617ad34319 100644 --- a/testsuite/tests/backpack/should_fail/bkpfail49.stderr +++ b/testsuite/tests/backpack/should_fail/bkpfail49.stderr @@ -1,10 +1,10 @@ [1 of 2] Processing p - [1 of 1] Compiling A[sig] ( p\A.hsig, nothing ) + [1 of 1] Compiling A[sig] ( p/A.hsig, nothing ) [2 of 2] Processing q - [1 of 3] Compiling A[sig] ( q\A.hsig, nothing ) - [2 of 3] Compiling M ( q\M.hs, nothing ) - + [1 of 3] Compiling A[sig] ( q/A.hsig, nothing ) + [2 of 3] Compiling M ( q/M.hs, nothing ) bkpfail49.bkp:11:13: error: [GHC-76037] Not in scope: data constructor ‘A.True’ - NB: the module ‘A’ does not export ‘True’. + Note: The module ‘A’ does not export ‘True’. + [3 of 3] Instantiating p diff --git a/testsuite/tests/dependent/should_fail/BadTelescope4.stderr b/testsuite/tests/dependent/should_fail/BadTelescope4.stderr index c0e55d40d203..a3ad2c2dc8e0 100644 --- a/testsuite/tests/dependent/should_fail/BadTelescope4.stderr +++ b/testsuite/tests/dependent/should_fail/BadTelescope4.stderr @@ -1,12 +1,11 @@ - BadTelescope4.hs:9:1: error: [GHC-87279] • The kind of ‘Bad’ is ill-scoped Inferred kind: Bad :: forall {k} (b :: Proxy a). forall (a :: k) -> Proxy b -> forall (d :: Proxy a) -> SameKind b d -> * - NB: Inferred variables - (namely: k) always come first - then Specified variables (namely: (b :: Proxy a)) + Note: Inferred variables (namely: k) + always come first + then specified variables (namely: (b :: Proxy a)). Perhaps try this order instead: k (a :: k) @@ -15,3 +14,4 @@ BadTelescope4.hs:9:1: error: [GHC-87279] (d :: Proxy a) (x :: SameKind b d) • In the data type declaration for ‘Bad’ + diff --git a/testsuite/tests/dependent/should_fail/T14066g.stderr b/testsuite/tests/dependent/should_fail/T14066g.stderr index e1e23127dfb2..9a64777cc101 100644 --- a/testsuite/tests/dependent/should_fail/T14066g.stderr +++ b/testsuite/tests/dependent/should_fail/T14066g.stderr @@ -1,9 +1,9 @@ - T14066g.hs:9:1: error: [GHC-87279] • The kind of ‘Q’ is ill-scoped Inferred kind: Q :: forall (c :: a). forall a (b :: a) -> SameKind c b -> * - NB: Specified variables (namely: (c :: a)) always come first + Note: Specified variables (namely: (c :: a)) always come first. Perhaps try this order instead: a (c :: a) (b :: a) (d :: SameKind c b) • In the data type declaration for ‘Q’ + diff --git a/testsuite/tests/dependent/should_fail/T15591b.stderr b/testsuite/tests/dependent/should_fail/T15591b.stderr index 78f9bca9be1e..0468a6bd8216 100644 --- a/testsuite/tests/dependent/should_fail/T15591b.stderr +++ b/testsuite/tests/dependent/should_fail/T15591b.stderr @@ -1,8 +1,9 @@ - T15591b.hs:9:3: error: [GHC-87279] • The kind of ‘T4’ is ill-scoped Inferred kind: T4 :: forall {b :: Proxy a}. forall a -> Proxy b -> * - NB: Inferred variables (namely: (b :: Proxy a)) always come first + Note: Inferred variables (namely: (b :: Proxy a)) + always come first. Perhaps try this order instead: a (b :: Proxy a) (c :: Proxy b) • In the associated type family declaration for ‘T4’ + diff --git a/testsuite/tests/dependent/should_fail/T15591c.stderr b/testsuite/tests/dependent/should_fail/T15591c.stderr index bd9fcbedd080..b2b485303723 100644 --- a/testsuite/tests/dependent/should_fail/T15591c.stderr +++ b/testsuite/tests/dependent/should_fail/T15591c.stderr @@ -1,8 +1,9 @@ - T15591c.hs:9:3: error: [GHC-87279] • The kind of ‘T5’ is ill-scoped Inferred kind: T5 :: forall {b :: Proxy a}. Proxy b -> forall a -> * - NB: Inferred variables (namely: (b :: Proxy a)) always come first + Note: Inferred variables (namely: (b :: Proxy a)) + always come first. Perhaps try this order instead: a (b :: Proxy a) (c :: Proxy b) • In the associated type family declaration for ‘T5’ + diff --git a/testsuite/tests/dependent/should_fail/T15743c.stderr b/testsuite/tests/dependent/should_fail/T15743c.stderr index d7fd3e807ded..2adbacc50787 100644 --- a/testsuite/tests/dependent/should_fail/T15743c.stderr +++ b/testsuite/tests/dependent/should_fail/T15743c.stderr @@ -1,10 +1,10 @@ - T15743c.hs:10:1: error: [GHC-87279] • The kind of ‘T’ is ill-scoped Inferred kind: T :: forall {d :: k}. forall k (c :: k) (a :: Proxy c) (b :: Proxy d) -> SimilarKind a b -> * - NB: Inferred variables (namely: (d :: k)) always come first + Note: Inferred variables (namely: (d :: k)) + always come first. Perhaps try this order instead: k (d :: k) @@ -13,3 +13,4 @@ T15743c.hs:10:1: error: [GHC-87279] (b :: Proxy d) (x :: SimilarKind a b) • In the data type declaration for ‘T’ + diff --git a/testsuite/tests/dependent/should_fail/T15743d.stderr b/testsuite/tests/dependent/should_fail/T15743d.stderr index ba5da289f308..973953cca941 100644 --- a/testsuite/tests/dependent/should_fail/T15743d.stderr +++ b/testsuite/tests/dependent/should_fail/T15743d.stderr @@ -1,10 +1,9 @@ - T15743d.hs:10:1: error: [GHC-87279] • The kind of ‘T2’ is ill-scoped Inferred kind: T2 :: forall (d :: k). forall k (c :: k) (a :: Proxy c) (b :: Proxy d) -> SimilarKind a b -> * - NB: Specified variables (namely: (d :: k)) always come first + Note: Specified variables (namely: (d :: k)) always come first. Perhaps try this order instead: k (d :: k) @@ -13,3 +12,4 @@ T15743d.hs:10:1: error: [GHC-87279] (b :: Proxy d) (x :: SimilarKind a b) • In the data type declaration for ‘T2’ + diff --git a/testsuite/tests/deriving/should_fail/T1496.stderr b/testsuite/tests/deriving/should_fail/T1496.stderr index 73f1f7e34f14..2cc3ff48c6c3 100644 --- a/testsuite/tests/deriving/should_fail/T1496.stderr +++ b/testsuite/tests/deriving/should_fail/T1496.stderr @@ -1,10 +1,10 @@ - T1496.hs:10:32: error: [GHC-18872] • Couldn't match representation of type: c Int with that of: c Moo arising from the coercion of the method ‘isInt’ from type ‘forall (c :: * -> *). c Int -> c Int’ to type ‘forall (c :: * -> *). c Int -> c Moo’ - NB: We cannot know what roles the parameters to ‘c’ have; - we must assume that the role is nominal + Note: We cannot know what roles the parameters to ‘c’ have; + we must assume that the role is nominal. • When deriving the instance for (IsInt Moo) + diff --git a/testsuite/tests/deriving/should_fail/T5498.stderr b/testsuite/tests/deriving/should_fail/T5498.stderr index d6638f4332f6..2c4a234dac30 100644 --- a/testsuite/tests/deriving/should_fail/T5498.stderr +++ b/testsuite/tests/deriving/should_fail/T5498.stderr @@ -1,10 +1,10 @@ - T5498.hs:30:39: error: [GHC-18872] • Couldn't match representation of type: c a with that of: c (Down a) arising from the coercion of the method ‘intIso’ from type ‘forall (c :: * -> *). c a -> c Int’ to type ‘forall (c :: * -> *). c (Down a) -> c Int’ - NB: We cannot know what roles the parameters to ‘c’ have; - we must assume that the role is nominal + Note: We cannot know what roles the parameters to ‘c’ have; + we must assume that the role is nominal. • When deriving the instance for (IntIso (Down a)) + diff --git a/testsuite/tests/deriving/should_fail/T8984.stderr b/testsuite/tests/deriving/should_fail/T8984.stderr index 8a23250d4dc2..d49e3f41c25c 100644 --- a/testsuite/tests/deriving/should_fail/T8984.stderr +++ b/testsuite/tests/deriving/should_fail/T8984.stderr @@ -1,9 +1,9 @@ - T8984.hs:7:46: error: [GHC-18872] • Couldn't match representation of type: cat a (N cat a Int) with that of: cat a (cat a Int) arising from the coercion of the method ‘app’ from type ‘cat a (cat a Int)’ to type ‘N cat a (N cat a Int)’ - NB: We cannot know what roles the parameters to ‘cat a’ have; - we must assume that the role is nominal + Note: We cannot know what roles the parameters to ‘cat a’ have; + we must assume that the role is nominal. • When deriving the instance for (C (N cat a)) + diff --git a/testsuite/tests/ghci/scripts/T2452.stderr b/testsuite/tests/ghci/scripts/T2452.stderr index 05de0373e974..62b390fd3d4b 100644 --- a/testsuite/tests/ghci/scripts/T2452.stderr +++ b/testsuite/tests/ghci/scripts/T2452.stderr @@ -1,8 +1,8 @@ - <interactive>:1:1: error: [GHC-76037] Not in scope: ‘System.IO.hPutStrLn’ - NB: no module named ‘System.IO’ is imported. + Note: No module named ‘System.IO’ is imported. <interactive>:1:1: error: [GHC-76037] Not in scope: ‘System.IO.hPutStrLn’ - NB: no module named ‘System.IO’ is imported. + Note: No module named ‘System.IO’ is imported. + diff --git a/testsuite/tests/ghci/scripts/T8639.stderr b/testsuite/tests/ghci/scripts/T8639.stderr index be69a84d9e54..51b346868587 100644 --- a/testsuite/tests/ghci/scripts/T8639.stderr +++ b/testsuite/tests/ghci/scripts/T8639.stderr @@ -1,5 +1,5 @@ - <interactive>:1:1: error: [GHC-76037] Not in scope: ‘H.bit’ - NB: no module named ‘H’ is imported. + Note: No module named ‘H’ is imported. Suggested fix: Perhaps use ‘Q.bit’ (imported from T8639) + diff --git a/testsuite/tests/ghci/scripts/T8649.stderr b/testsuite/tests/ghci/scripts/T8649.stderr index 19edacbc188a..e6840e56d744 100644 --- a/testsuite/tests/ghci/scripts/T8649.stderr +++ b/testsuite/tests/ghci/scripts/T8649.stderr @@ -1,8 +1,8 @@ - <interactive>:4:4: error: [GHC-83865] • Couldn't match expected type ‘Ghci1.X’ with actual type ‘X’ - NB: ‘Ghci1.X’ is defined at <interactive>:1:1-14 - ‘X’ is defined at <interactive>:3:1-25 + Note: ‘Ghci1.X’ is defined at <interactive>:1:1-14 + ‘X’ is defined at <interactive>:3:1-25. • In the first argument of ‘f’, namely ‘(Y 3)’ In the expression: f (Y 3) In an equation for ‘it’: it = f (Y 3) + diff --git a/testsuite/tests/ghci/scripts/ghci036.stderr b/testsuite/tests/ghci/scripts/ghci036.stderr index 0f15f7a2a2e5..1ecae302f292 100644 --- a/testsuite/tests/ghci/scripts/ghci036.stderr +++ b/testsuite/tests/ghci/scripts/ghci036.stderr @@ -1,4 +1,3 @@ - <interactive>:1:1: error: [GHC-88464] Variable not in scope: nubBy <interactive>:1:1: error: [GHC-88464] Variable not in scope: nub @@ -13,6 +12,7 @@ <interactive>:1:1: error: [GHC-76037] Not in scope: ‘L.nub’ - NB: no module named ‘L’ is imported. + Note: No module named ‘L’ is imported. <interactive>:1:1: error: [GHC-88464] Variable not in scope: nub + diff --git a/testsuite/tests/ghci/scripts/ghci051.stderr b/testsuite/tests/ghci/scripts/ghci051.stderr index cbbc9e053917..95f79eefca3d 100644 --- a/testsuite/tests/ghci/scripts/ghci051.stderr +++ b/testsuite/tests/ghci/scripts/ghci051.stderr @@ -1,9 +1,9 @@ - <interactive>:6:9: error: [GHC-83865] • Couldn't match type ‘T’ with ‘Ghci1.T’ Expected: T' Actual: T - NB: ‘Ghci1.T’ is defined at <interactive>:2:1-14 - ‘T’ is defined at <interactive>:5:1-16 + Note: ‘Ghci1.T’ is defined at <interactive>:2:1-14 + ‘T’ is defined at <interactive>:5:1-16. • In the expression: C :: T' In an equation for ‘c’: c = C :: T' + diff --git a/testsuite/tests/ghci/scripts/ghci052.stderr b/testsuite/tests/ghci/scripts/ghci052.stderr index 1cdd5597753e..aab63c864cb9 100644 --- a/testsuite/tests/ghci/scripts/ghci052.stderr +++ b/testsuite/tests/ghci/scripts/ghci052.stderr @@ -1,9 +1,8 @@ - <interactive>:8:4: error: [GHC-83865] • Couldn't match expected type ‘Ghci1.Planet’ with actual type ‘Planet’ - NB: ‘Ghci1.Planet’ is defined at <interactive>:4:1-37 - ‘Planet’ is defined at <interactive>:7:1-36 + Note: ‘Ghci1.Planet’ is defined at <interactive>:4:1-37 + ‘Planet’ is defined at <interactive>:7:1-36. • In the first argument of ‘pn’, namely ‘Mercury’ In the expression: pn Mercury In an equation for ‘it’: it = pn Mercury @@ -11,8 +10,8 @@ <interactive>:9:4: error: [GHC-83865] • Couldn't match expected type ‘Ghci1.Planet’ with actual type ‘Planet’ - NB: ‘Ghci1.Planet’ is defined at <interactive>:4:1-37 - ‘Planet’ is defined at <interactive>:7:1-36 + Note: ‘Ghci1.Planet’ is defined at <interactive>:4:1-37 + ‘Planet’ is defined at <interactive>:7:1-36. • In the first argument of ‘pn’, namely ‘Venus’ In the expression: pn Venus In an equation for ‘it’: it = pn Venus @@ -20,8 +19,8 @@ <interactive>:10:4: error: [GHC-83865] • Couldn't match expected type ‘Ghci1.Planet’ with actual type ‘Planet’ - NB: ‘Ghci1.Planet’ is defined at <interactive>:4:1-37 - ‘Planet’ is defined at <interactive>:7:1-36 + Note: ‘Ghci1.Planet’ is defined at <interactive>:4:1-37 + ‘Planet’ is defined at <interactive>:7:1-36. • In the first argument of ‘pn’, namely ‘Mars’ In the expression: pn Mars In an equation for ‘it’: it = pn Mars @@ -29,7 +28,8 @@ <interactive>:12:44: error: [GHC-83865] • Couldn't match expected type ‘Planet’ with actual type ‘Ghci1.Planet’ - NB: ‘Planet’ is defined at <interactive>:7:1-36 - ‘Ghci1.Planet’ is defined at <interactive>:4:1-37 + Note: ‘Planet’ is defined at <interactive>:7:1-36 + ‘Ghci1.Planet’ is defined at <interactive>:4:1-37. • In the pattern: Earth In an equation for ‘pn’: pn Earth = "E" + diff --git a/testsuite/tests/ghci/scripts/ghci053.stderr b/testsuite/tests/ghci/scripts/ghci053.stderr index 7cf1a64b88c0..1f5ad4e99472 100644 --- a/testsuite/tests/ghci/scripts/ghci053.stderr +++ b/testsuite/tests/ghci/scripts/ghci053.stderr @@ -1,9 +1,8 @@ - <interactive>:9:12: error: [GHC-83865] • Couldn't match expected type ‘Ghci1.Planet’ with actual type ‘Planet’ - NB: ‘Ghci1.Planet’ is defined at <interactive>:4:1-49 - ‘Planet’ is defined at <interactive>:7:1-41 + Note: ‘Ghci1.Planet’ is defined at <interactive>:4:1-49 + ‘Planet’ is defined at <interactive>:7:1-41. • In the second argument of ‘(==)’, namely ‘Mercury’ In the expression: mercury == Mercury In an equation for ‘it’: it = mercury == Mercury @@ -11,8 +10,9 @@ <interactive>:11:10: error: [GHC-83865] • Couldn't match expected type ‘Planet’ with actual type ‘Ghci1.Planet’ - NB: ‘Planet’ is defined at <interactive>:7:1-41 - ‘Ghci1.Planet’ is defined at <interactive>:4:1-49 + Note: ‘Planet’ is defined at <interactive>:7:1-41 + ‘Ghci1.Planet’ is defined at <interactive>:4:1-49. • In the second argument of ‘(==)’, namely ‘Earth’ In the expression: Venus == Earth In an equation for ‘it’: it = Venus == Earth + diff --git a/testsuite/tests/indexed-types/should_compile/T3208b.stderr b/testsuite/tests/indexed-types/should_compile/T3208b.stderr index 9cb267050531..559f35cf46aa 100644 --- a/testsuite/tests/indexed-types/should_compile/T3208b.stderr +++ b/testsuite/tests/indexed-types/should_compile/T3208b.stderr @@ -1,4 +1,3 @@ - T3208b.hs:15:10: error: [GHC-05617] • Could not deduce ‘STerm o0 ~ OTerm a’ arising from a use of ‘fce’ from the context: (OTerm a ~ STerm a, OBJECT a, SUBST a) @@ -23,7 +22,7 @@ T3208b.hs:15:15: error: [GHC-05617] (OTerm a ~ STerm a, OBJECT a, SUBST a) => a -> c at T3208b.hs:14:1-56 - NB: ‘OTerm’ is a non-injective type family + Note: ‘OTerm’ is a non-injective type family. The type variable ‘o0’ is ambiguous • In the first argument of ‘fce’, namely ‘(apply f)’ In the expression: fce (apply f) @@ -31,3 +30,4 @@ T3208b.hs:15:15: error: [GHC-05617] • Relevant bindings include f :: a (bound at T3208b.hs:15:6) fce' :: a -> c (bound at T3208b.hs:15:1) + diff --git a/testsuite/tests/indexed-types/should_fail/NoMatchErr.stderr b/testsuite/tests/indexed-types/should_fail/NoMatchErr.stderr index fe9520345fb0..61cec4c91bdb 100644 --- a/testsuite/tests/indexed-types/should_fail/NoMatchErr.stderr +++ b/testsuite/tests/indexed-types/should_fail/NoMatchErr.stderr @@ -1,11 +1,11 @@ - NoMatchErr.hs:19:7: error: [GHC-83865] • Couldn't match type: Memo d0 with: Memo d Expected: Memo d a -> Memo d a Actual: Memo d0 a -> Memo d0 a - NB: ‘Memo’ is a non-injective type family - The type variable ‘d0’ is ambiguous + Note: ‘Memo’ is a non-injective type family. + The type variable ‘d0’ is ambiguous • In the ambiguity check for ‘f’ To defer the ambiguity check to use sites, enable AllowAmbiguousTypes In the type signature: f :: (Fun d) => Memo d a -> Memo d a + diff --git a/testsuite/tests/indexed-types/should_fail/T14887.stderr b/testsuite/tests/indexed-types/should_fail/T14887.stderr index dd91d0c44610..bdc8cc866d41 100644 --- a/testsuite/tests/indexed-types/should_fail/T14887.stderr +++ b/testsuite/tests/indexed-types/should_fail/T14887.stderr @@ -1,7 +1,7 @@ - T14887.hs:15:1: error: [GHC-87279] • The kind of ‘Foo2’ is ill-scoped Inferred kind: Foo2 :: forall (a :: k). forall k -> (a :~: a) -> * - NB: Specified variables (namely: (a :: k)) always come first + Note: Specified variables (namely: (a :: k)) always come first. Perhaps try this order instead: k (a :: k) (e :: a :~: a) • In the type family declaration for ‘Foo2’ + diff --git a/testsuite/tests/indexed-types/should_fail/T15764.stderr b/testsuite/tests/indexed-types/should_fail/T15764.stderr index 98ce75575d05..c306b57780b8 100644 --- a/testsuite/tests/indexed-types/should_fail/T15764.stderr +++ b/testsuite/tests/indexed-types/should_fail/T15764.stderr @@ -1,11 +1,11 @@ - T15764.hs:14:2: error: [GHC-87279] • The kind of ‘T6’ is ill-scoped Inferred kind: T6 :: forall {a :: k} k (b :: Proxy a). Proxy '(k, b) -> * - NB: Inferred variables - (namely: (a :: k)) always come first - then Specified variables (namely: k (b :: Proxy a)) + Note: Inferred variables (namely: (a :: k)) + always come first + then specified variables (namely: k (b :: Proxy a)). Perhaps try this order instead: k (a :: k) (b :: Proxy a) (proxy :: Proxy '(k, b)) • In the associated type family declaration for ‘T6’ + diff --git a/testsuite/tests/indexed-types/should_fail/T1897b.stderr b/testsuite/tests/indexed-types/should_fail/T1897b.stderr index ef291b87ce2e..bbf15a81a27d 100644 --- a/testsuite/tests/indexed-types/should_fail/T1897b.stderr +++ b/testsuite/tests/indexed-types/should_fail/T1897b.stderr @@ -1,14 +1,14 @@ - T1897b.hs:16:1: error: [GHC-83865] • Couldn't match type: Depend a0 with: Depend a Expected: t (Depend a) -> Bool Actual: t (Depend a0) -> Bool - NB: ‘Depend’ is a non-injective type family - The type variable ‘a0’ is ambiguous + Note: ‘Depend’ is a non-injective type family. + The type variable ‘a0’ is ambiguous • In the ambiguity check for the inferred type for ‘isValid’ To defer the ambiguity check to use sites, enable AllowAmbiguousTypes When checking the inferred type isValid :: forall {t :: * -> *} {a}. (Foldable t, Bug a) => t (Depend a) -> Bool + diff --git a/testsuite/tests/indexed-types/should_fail/T1900.stderr b/testsuite/tests/indexed-types/should_fail/T1900.stderr index 8b245af562d9..572c85dd7190 100644 --- a/testsuite/tests/indexed-types/should_fail/T1900.stderr +++ b/testsuite/tests/indexed-types/should_fail/T1900.stderr @@ -1,13 +1,13 @@ - T1900.hs:8:3: error: [GHC-83865] • Couldn't match type: Depend s0 with: Depend s Expected: Depend s -> Depend s Actual: Depend s0 -> Depend s0 - NB: ‘Depend’ is a non-injective type family - The type variable ‘s0’ is ambiguous + Note: ‘Depend’ is a non-injective type family. + The type variable ‘s0’ is ambiguous • In the ambiguity check for ‘trans’ To defer the ambiguity check to use sites, enable AllowAmbiguousTypes When checking the class method: trans :: forall s. Bug s => Depend s -> Depend s In the class declaration for ‘Bug’ + diff --git a/testsuite/tests/indexed-types/should_fail/T2544.stderr b/testsuite/tests/indexed-types/should_fail/T2544.stderr index 1f0d70f90457..c226a77c361b 100644 --- a/testsuite/tests/indexed-types/should_fail/T2544.stderr +++ b/testsuite/tests/indexed-types/should_fail/T2544.stderr @@ -1,11 +1,10 @@ - T2544.hs:19:18: error: [GHC-83865] • Couldn't match type: IxMap i0 with: IxMap l Expected: IxMap l [Int] Actual: IxMap i0 [Int] - NB: ‘IxMap’ is a non-injective type family - The type variable ‘i0’ is ambiguous + Note: ‘IxMap’ is a non-injective type family. + The type variable ‘i0’ is ambiguous • In the first argument of ‘BiApp’, namely ‘empty’ In the expression: BiApp empty empty In an equation for ‘empty’: empty = BiApp empty empty @@ -17,10 +16,11 @@ T2544.hs:19:24: error: [GHC-83865] with: IxMap r Expected: IxMap r [Int] Actual: IxMap i1 [Int] - NB: ‘IxMap’ is a non-injective type family - The type variable ‘i1’ is ambiguous + Note: ‘IxMap’ is a non-injective type family. + The type variable ‘i1’ is ambiguous • In the second argument of ‘BiApp’, namely ‘empty’ In the expression: BiApp empty empty In an equation for ‘empty’: empty = BiApp empty empty • Relevant bindings include empty :: IxMap (l :|: r) [Int] (bound at T2544.hs:19:4) + diff --git a/testsuite/tests/indexed-types/should_fail/T4099.stderr b/testsuite/tests/indexed-types/should_fail/T4099.stderr index 9f0f528cc103..d0ad25646c74 100644 --- a/testsuite/tests/indexed-types/should_fail/T4099.stderr +++ b/testsuite/tests/indexed-types/should_fail/T4099.stderr @@ -1,9 +1,8 @@ - T4099.hs:11:30: error: [GHC-83865] • Couldn't match expected type: T a0 with actual type: T b - NB: ‘T’ is a non-injective type family - The type variable ‘a0’ is ambiguous + Note: ‘T’ is a non-injective type family. + The type variable ‘a0’ is ambiguous • In the second argument of ‘foo’, namely ‘x’ In the expression: foo (error "urk") x In an equation for ‘bar1’: bar1 a x = foo (error "urk") x @@ -15,7 +14,7 @@ T4099.hs:11:30: error: [GHC-83865] T4099.hs:14:30: error: [GHC-83865] • Couldn't match expected type: T a1 with actual type: Maybe b - The type variable ‘a1’ is ambiguous + The type variable ‘a1’ is ambiguous • In the second argument of ‘foo’, namely ‘x’ In the expression: foo (error "urk") x In an equation for ‘bar2’: bar2 a x = foo (error "urk") x @@ -23,3 +22,4 @@ T4099.hs:14:30: error: [GHC-83865] x :: Maybe b (bound at T4099.hs:14:8) a :: b (bound at T4099.hs:14:6) bar2 :: b -> Maybe b -> Int (bound at T4099.hs:14:1) + diff --git a/testsuite/tests/indexed-types/should_fail/T4179.stderr b/testsuite/tests/indexed-types/should_fail/T4179.stderr index 701006258a46..05eac234eec0 100644 --- a/testsuite/tests/indexed-types/should_fail/T4179.stderr +++ b/testsuite/tests/indexed-types/should_fail/T4179.stderr @@ -1,4 +1,3 @@ - T4179.hs:26:16: error: [GHC-83865] • Couldn't match type: A2 (x (A2 (FCon x) -> A3 (FCon x))) with: A2 (FCon x) @@ -7,10 +6,11 @@ T4179.hs:26:16: error: [GHC-83865] Actual: x (A2 (FCon x) -> A3 (FCon x)) -> A2 (x (A2 (FCon x) -> A3 (FCon x))) -> A3 (x (A2 (FCon x) -> A3 (FCon x))) - NB: ‘A2’ is a non-injective type family + Note: ‘A2’ is a non-injective type family. • In the first argument of ‘foldDoC’, namely ‘op’ In the expression: foldDoC op In an equation for ‘fCon’: fCon = foldDoC op • Relevant bindings include fCon :: Con x -> A2 (FCon x) -> A3 (FCon x) (bound at T4179.hs:26:1) + diff --git a/testsuite/tests/indexed-types/should_fail/T9036.stderr b/testsuite/tests/indexed-types/should_fail/T9036.stderr index bb1143891667..9a094184ba06 100644 --- a/testsuite/tests/indexed-types/should_fail/T9036.stderr +++ b/testsuite/tests/indexed-types/should_fail/T9036.stderr @@ -1,12 +1,12 @@ - T9036.hs:18:17: error: [GHC-83865] • Couldn't match type: GetMonad t0 with: GetMonad t Expected: Maybe (GetMonad t after) -> Curried t [t] Actual: Maybe (GetMonad t0 after) -> Curried t0 [t0] - NB: ‘GetMonad’ is a non-injective type family - The type variable ‘t0’ is ambiguous + Note: ‘GetMonad’ is a non-injective type family. + The type variable ‘t0’ is ambiguous • In the ambiguity check for ‘simpleLogger’ To defer the ambiguity check to use sites, enable AllowAmbiguousTypes In the type signature: simpleLogger :: Maybe (GetMonad t after) -> t `Curried` [t] + diff --git a/testsuite/tests/indexed-types/should_fail/T9171.stderr b/testsuite/tests/indexed-types/should_fail/T9171.stderr index 7d93c7aa8e33..9da0276702c4 100644 --- a/testsuite/tests/indexed-types/should_fail/T9171.stderr +++ b/testsuite/tests/indexed-types/should_fail/T9171.stderr @@ -1,12 +1,12 @@ - T9171.hs:10:20: error: [GHC-83865] • Couldn't match expected type: GetParam @(*) @k2 @(*) Base (GetParam @(*) @(*) @k2 Base Int) with actual type: GetParam @(*) @k20 @(*) Base (GetParam @(*) @(*) @k20 Base Int) - NB: ‘GetParam’ is a non-injective type family - The type variable ‘k20’ is ambiguous + Note: ‘GetParam’ is a non-injective type family. + The type variable ‘k20’ is ambiguous • In the ambiguity check for an expression type signature To defer the ambiguity check to use sites, enable AllowAmbiguousTypes In an expression type signature: GetParam Base (GetParam Base Int) In the expression: undefined :: GetParam Base (GetParam Base Int) + diff --git a/testsuite/tests/module/mod180.stderr b/testsuite/tests/module/mod180.stderr index 6971e65f1ddf..1971b6292382 100644 --- a/testsuite/tests/module/mod180.stderr +++ b/testsuite/tests/module/mod180.stderr @@ -1,8 +1,8 @@ - mod180.hs:8:5: error: [GHC-83865] • Couldn't match expected type ‘T’ with actual type ‘main:Mod180_A.T’ - NB: ‘T’ is defined at Mod180_B.hs:3:1-10 - ‘main:Mod180_A.T’ is defined at Mod180_A.hs:3:1-10 + Note: ‘T’ is defined at Mod180_B.hs:3:1-10 + ‘main:Mod180_A.T’ is defined at Mod180_A.hs:3:1-10. • In the expression: x In an equation for ‘z’: z = x + diff --git a/testsuite/tests/module/mod73.stderr b/testsuite/tests/module/mod73.stderr index 9e990911012b..173f4a2546b0 100644 --- a/testsuite/tests/module/mod73.stderr +++ b/testsuite/tests/module/mod73.stderr @@ -1,9 +1,9 @@ - mod73.hs:3:7: error: [GHC-76037] Not in scope: ‘Prelude.g’ - NB: the module ‘Prelude’ does not export ‘g’. + Note: The module ‘Prelude’ does not export ‘g’. Suggested fix: Perhaps use one of these: data constructor ‘Prelude.EQ’ (imported from Prelude), data constructor ‘Prelude.GT’ (imported from Prelude), data constructor ‘Prelude.LT’ (imported from Prelude) + diff --git a/testsuite/tests/module/mod74.stderr b/testsuite/tests/module/mod74.stderr index 7570cfbcc396..7077d332da68 100644 --- a/testsuite/tests/module/mod74.stderr +++ b/testsuite/tests/module/mod74.stderr @@ -1,4 +1,4 @@ - mod74.hs:3:7: error: [GHC-76037] Not in scope: ‘N.g’ - NB: no module named ‘N’ is imported. + Note: No module named ‘N’ is imported. + diff --git a/testsuite/tests/overloadedrecflds/should_fail/T21946.stderr b/testsuite/tests/overloadedrecflds/should_fail/T21946.stderr index 61254e3e3d56..434ceb7cef1f 100644 --- a/testsuite/tests/overloadedrecflds/should_fail/T21946.stderr +++ b/testsuite/tests/overloadedrecflds/should_fail/T21946.stderr @@ -1,8 +1,8 @@ - T21946.hs:11:7: error: [GHC-33238] • No data constructor of type constructor ‘Int’ has all of the fields: ‘fld’ - NB: type-directed disambiguation is not supported for pattern synonym record fields. + Note: Type-directed disambiguation is not supported for pattern synonym record fields. • In the expression: (r :: Int) {fld = undefined} In an equation for ‘f’: f r = (r :: Int) {fld = undefined} + diff --git a/testsuite/tests/quantified-constraints/T15290a.stderr b/testsuite/tests/quantified-constraints/T15290a.stderr index 0153a1a937ce..94c21b7b5eac 100644 --- a/testsuite/tests/quantified-constraints/T15290a.stderr +++ b/testsuite/tests/quantified-constraints/T15290a.stderr @@ -1,10 +1,9 @@ - T15290a.hs:25:12: error: [GHC-18872] • Couldn't match representation of type: m (Int, IntStateT m a1) with that of: m (Int, StateT Int m a1) arising from a use of ‘coerce’ - NB: We cannot know what roles the parameters to ‘m’ have; - we must assume that the role is nominal + Note: We cannot know what roles the parameters to ‘m’ have; + we must assume that the role is nominal. • In the expression: coerce @(forall a. StateT Int m (StateT Int m a) -> StateT Int m a) @@ -18,3 +17,4 @@ T15290a.hs:25:12: error: [GHC-18872] • Relevant bindings include join :: IntStateT m (IntStateT m a) -> IntStateT m a (bound at T15290a.hs:25:5) + diff --git a/testsuite/tests/quantified-constraints/T15290b.stderr b/testsuite/tests/quantified-constraints/T15290b.stderr index e2a426b70abf..adc0e816a3d4 100644 --- a/testsuite/tests/quantified-constraints/T15290b.stderr +++ b/testsuite/tests/quantified-constraints/T15290b.stderr @@ -1,4 +1,3 @@ - T15290b.hs:28:49: error: [GHC-18872] • Couldn't match representation of type: f (m b) with that of: f (T1 m b) @@ -9,6 +8,7 @@ T15290b.hs:28:49: error: [GHC-18872] to type ‘forall (f :: * -> *) a b. Applicative' f => (a -> f b) -> T1 m a -> f (T1 m b)’ - NB: We cannot know what roles the parameters to ‘f’ have; - we must assume that the role is nominal + Note: We cannot know what roles the parameters to ‘f’ have; + we must assume that the role is nominal. • When deriving the instance for (Traversable' (T1 m)) + diff --git a/testsuite/tests/rename/should_compile/T20472.stderr b/testsuite/tests/rename/should_compile/T20472.stderr index 11e4e830d9d2..74f607289d50 100644 --- a/testsuite/tests/rename/should_compile/T20472.stderr +++ b/testsuite/tests/rename/should_compile/T20472.stderr @@ -1,11 +1,11 @@ - T20472.hs:5:5: warning: [GHC-88464] [-Wdeferred-out-of-scope-variables (in -Wdefault)] Variable not in scope: nonexistent T20472.hs:6:5: warning: [GHC-88464] [-Wdeferred-out-of-scope-variables (in -Wdefault)] Variable not in scope: Prelude.nonexistent - NB: the module ‘Prelude’ does not export ‘nonexistent’. + Note: The module ‘Prelude’ does not export ‘nonexistent’. T20472.hs:8:5: warning: [GHC-88464] [-Wdeferred-out-of-scope-variables (in -Wdefault)] Variable not in scope: Nonexistent.x - NB: no module named ‘Nonexistent’ is imported. + Note: No module named ‘Nonexistent’ is imported. + diff --git a/testsuite/tests/rename/should_fail/T10781.stderr b/testsuite/tests/rename/should_fail/T10781.stderr index 7a7f01744236..c4a65927dd1d 100644 --- a/testsuite/tests/rename/should_fail/T10781.stderr +++ b/testsuite/tests/rename/should_fail/T10781.stderr @@ -1,4 +1,4 @@ - T10781.hs:12:5: error: [GHC-76037] Not in scope: ‘Foo._name’ - NB: no module named ‘Foo’ is imported. + Note: No module named ‘Foo’ is imported. + diff --git a/testsuite/tests/rename/should_fail/T11071.stderr b/testsuite/tests/rename/should_fail/T11071.stderr index efe9501a95bc..e2e1ba492d4c 100644 --- a/testsuite/tests/rename/should_fail/T11071.stderr +++ b/testsuite/tests/rename/should_fail/T11071.stderr @@ -1,20 +1,19 @@ - T11071.hs:19:12: error: [GHC-76037] Not in scope: ‘NoSuchModule.foo’ - NB: no module named ‘NoSuchModule’ is imported. + Note: No module named ‘NoSuchModule’ is imported. T11071.hs:20:12: error: [GHC-76037] Not in scope: ‘Data.List.foobar’ - NB: the module ‘Data.List’ does not export ‘foobar’. + Note: The module ‘Data.List’ does not export ‘foobar’. T11071.hs:21:12: error: [GHC-76037] Not in scope: ‘M.foobar’ - NB: neither ‘Data.IntMap’ nor ‘Data.Map’ export ‘foobar’. + Note: Neither ‘Data.IntMap’ nor ‘Data.Map’ export ‘foobar’. T11071.hs:22:12: error: [GHC-76037] Not in scope: ‘M'.foobar’ - NB: neither ‘System.IO’, - ‘Data.IntMap’ nor ‘Data.Map’ export ‘foobar’. + Note: Neither ‘System.IO’, + ‘Data.IntMap’ nor ‘Data.Map’ export ‘foobar’. T11071.hs:23:12: error: [GHC-76037] Not in scope: ‘Data.List.sort’ @@ -57,3 +56,4 @@ T11071.hs:28:12: error: [GHC-76037] Remove ‘size’ from the hiding clauses in one of these imports: ‘Data.IntMap’ (at T11071.hs:12:1-48) ‘Data.Map’ (at T11071.hs:10:1-53) + diff --git a/testsuite/tests/rename/should_fail/T19843k.stderr b/testsuite/tests/rename/should_fail/T19843k.stderr index 266b45e2457d..f566bd9fc2b9 100644 --- a/testsuite/tests/rename/should_fail/T19843k.stderr +++ b/testsuite/tests/rename/should_fail/T19843k.stderr @@ -1,4 +1,4 @@ - T19843k.hs:5:8: error: [GHC-76037] Not in scope: ‘M.doesn'tExist’ - NB: the module ‘Data.Monoid’ does not export ‘doesn'tExist’. + Note: The module ‘Data.Monoid’ does not export ‘doesn'tExist’. + diff --git a/testsuite/tests/rename/should_fail/T21605a.stderr b/testsuite/tests/rename/should_fail/T21605a.stderr index ce199cfb8f9d..7301a8fccae4 100644 --- a/testsuite/tests/rename/should_fail/T21605a.stderr +++ b/testsuite/tests/rename/should_fail/T21605a.stderr @@ -1,9 +1,9 @@ - T21605a.hs:5:13: error: [GHC-76037] Not in scope: ‘Prelude.true’ - NB: the module ‘Prelude’ does not export ‘true’. + Note: The module ‘Prelude’ does not export ‘true’. Suggested fix: Perhaps use one of these: data constructor ‘Prelude.True’ (imported from Prelude), type constructor or class ‘Prelude.Num’ (imported from Prelude), type constructor or class ‘Prelude.Ord’ (imported from Prelude) + diff --git a/testsuite/tests/rename/should_fail/T21605b.stderr b/testsuite/tests/rename/should_fail/T21605b.stderr index ebb74bad48b6..ba7e1b9ff8a5 100644 --- a/testsuite/tests/rename/should_fail/T21605b.stderr +++ b/testsuite/tests/rename/should_fail/T21605b.stderr @@ -1,9 +1,9 @@ - T21605b.hs:6:13: error: [GHC-76037] Not in scope: ‘Prelude.true’ - NB: the module ‘Prelude’ does not export ‘true’. + Note: The module ‘Prelude’ does not export ‘true’. Suggested fix: Perhaps use one of these: data constructor ‘Prelude.True’ (imported from Prelude), type constructor or class ‘Prelude.Num’ (imported from Prelude), type constructor or class ‘Prelude.Ord’ (imported from Prelude) + diff --git a/testsuite/tests/rename/should_fail/T2901.stderr b/testsuite/tests/rename/should_fail/T2901.stderr index ba1bbcebc898..321de2fc3a7e 100644 --- a/testsuite/tests/rename/should_fail/T2901.stderr +++ b/testsuite/tests/rename/should_fail/T2901.stderr @@ -1,4 +1,4 @@ - T2901.hs:6:5: error: [GHC-76037] Not in scope: data constructor ‘F.Foo’ - NB: no module named ‘F’ is imported. + Note: No module named ‘F’ is imported. + diff --git a/testsuite/tests/rename/should_fail/T5657.stderr b/testsuite/tests/rename/should_fail/T5657.stderr index ee0ca60032aa..ec6620ae6b6d 100644 --- a/testsuite/tests/rename/should_fail/T5657.stderr +++ b/testsuite/tests/rename/should_fail/T5657.stderr @@ -1,7 +1,7 @@ - T5657.hs:3:8: error: [GHC-76037] Not in scope: ‘LT..’ - NB: no module named ‘LT’ is imported. + Note: No module named ‘LT’ is imported. T5657.hs:3:8: error: [GHC-95880] A section must be enclosed in parentheses thus: (LT.. GT) + diff --git a/testsuite/tests/rename/should_fail/rnfail055.stderr b/testsuite/tests/rename/should_fail/rnfail055.stderr index 8d6a189dded6..99cc205a6aea 100644 --- a/testsuite/tests/rename/should_fail/rnfail055.stderr +++ b/testsuite/tests/rename/should_fail/rnfail055.stderr @@ -22,7 +22,7 @@ RnFail055.hs-boot:9:1: error: [GHC-15843] Boot file: type S2 :: * -> * -> * type S2 a b = forall b1. (a, b1) The roles do not match. - NB: roles on abstract types default to ‘representational’ in hs-boot files. + Note: Roles on abstract types default to ‘representational’ in hs-boot files. • In the type synonym declaration for ‘S2’ RnFail055.hs-boot:13:1: error: [GHC-15843] @@ -45,7 +45,7 @@ RnFail055.hs-boot:15:1: error: [GHC-15843] type T2 :: * -> * -> * data Eq a => T2 a b = T2 a The roles do not match. - NB: roles on abstract types default to ‘representational’ in hs-boot files. + Note: Roles on abstract types default to ‘representational’ in hs-boot files. The datatype contexts do not match. The constructors do not match: The types for ‘T2’ differ. • In the data type declaration for ‘T2’ @@ -101,7 +101,7 @@ RnFail055.hs-boot:26:1: error: [GHC-15843] Boot file: type T7 :: * -> * data T7 a = forall b. T7 a The roles do not match. - NB: roles on abstract types default to ‘representational’ in hs-boot files. + Note: Roles on abstract types default to ‘representational’ in hs-boot files. The constructors do not match: The types for ‘T7’ differ. • In the data type declaration for ‘T7’ @@ -144,3 +144,4 @@ RnFail055.hs-boot:30:1: error: [GHC-15843] class (Ord a, Eq a) => C3 a The superclass constraints do not match. • In the class declaration for ‘C3’ + diff --git a/testsuite/tests/roles/should_fail/Roles12.stderr b/testsuite/tests/roles/should_fail/Roles12.stderr index 1d0dc0ba7b68..20c27550afcd 100644 --- a/testsuite/tests/roles/should_fail/Roles12.stderr +++ b/testsuite/tests/roles/should_fail/Roles12.stderr @@ -1,4 +1,3 @@ - Roles12.hs:6:1: error: [GHC-15843] • Type constructor ‘T’ has conflicting definitions in the module and its hs-boot file. @@ -8,5 +7,6 @@ Roles12.hs:6:1: error: [GHC-15843] Boot file: type T :: * -> * data T a The roles do not match. - NB: roles on abstract types default to ‘representational’ in hs-boot files. + Note: Roles on abstract types default to ‘representational’ in hs-boot files. • In the data type declaration for ‘T’ + diff --git a/testsuite/tests/roles/should_fail/T23252.stderr b/testsuite/tests/roles/should_fail/T23252.stderr index 44bbcbd97c03..b2e8f62e4479 100644 --- a/testsuite/tests/roles/should_fail/T23252.stderr +++ b/testsuite/tests/roles/should_fail/T23252.stderr @@ -1,10 +1,9 @@ - T23252.hs:11:1: error: [GHC-87279] • The kind of ‘T2’ is ill-scoped Inferred kind: T2 :: forall (d :: k). forall k (c :: k) (a :: Proxy c) (b :: Proxy d) -> SimilarKind a b -> * - NB: Specified variables (namely: (d :: k)) always come first + Note: Specified variables (namely: (d :: k)) always come first. Perhaps try this order instead: k (d :: k) @@ -13,3 +12,4 @@ T23252.hs:11:1: error: [GHC-87279] (b :: Proxy d) (x :: SimilarKind a b) • In the data type declaration for ‘T2’ + diff --git a/testsuite/tests/roles/should_fail/T9204.stderr b/testsuite/tests/roles/should_fail/T9204.stderr index 181529677f43..714f61e44609 100644 --- a/testsuite/tests/roles/should_fail/T9204.stderr +++ b/testsuite/tests/roles/should_fail/T9204.stderr @@ -1,4 +1,3 @@ - T9204.hs:7:1: error: [GHC-15843] • Type constructor ‘D’ has conflicting definitions in the module and its hs-boot file. @@ -8,5 +7,6 @@ T9204.hs:7:1: error: [GHC-15843] Boot file: type D :: * -> * data D a The roles do not match. - NB: roles on abstract types default to ‘representational’ in hs-boot files. + Note: Roles on abstract types default to ‘representational’ in hs-boot files. • In the data type declaration for ‘D’ + diff --git a/testsuite/tests/safeHaskell/ghci/p4.stderr b/testsuite/tests/safeHaskell/ghci/p4.stderr index 3e9c555143de..b1b8e9b98f37 100644 --- a/testsuite/tests/safeHaskell/ghci/p4.stderr +++ b/testsuite/tests/safeHaskell/ghci/p4.stderr @@ -1,9 +1,9 @@ - <interactive>:6:9: error: [GHC-76037] Not in scope: ‘System.IO.Unsafe.unsafePerformIO’ - NB: no module named ‘System.IO.Unsafe’ is imported. + Note: No module named ‘System.IO.Unsafe’ is imported. <interactive>:7:9: error: [GHC-88464] Variable not in scope: x :: IO b0 -> t <interactive>:8:1: error: [GHC-88464] Variable not in scope: y + diff --git a/testsuite/tests/typecheck/bug1465/bug1465.stderr b/testsuite/tests/typecheck/bug1465/bug1465.stderr index 28448db00824..f6b56249cdc9 100644 --- a/testsuite/tests/typecheck/bug1465/bug1465.stderr +++ b/testsuite/tests/typecheck/bug1465/bug1465.stderr @@ -1,9 +1,9 @@ - C.hs:6:11: error: [GHC-83865] • Couldn't match expected type ‘bug1465-1.0:A.T’ with actual type ‘A.T’ - NB: ‘bug1465-1.0:A.T’ is defined in ‘A’ in package ‘bug1465-1.0’ - ‘A.T’ is defined in ‘A’ in package ‘bug1465-2.0’ + Note: ‘bug1465-1.0:A.T’ is defined in ‘A’ in package ‘bug1465-1.0’ + ‘A.T’ is defined in ‘A’ in package ‘bug1465-2.0’. • In the expression: B2.f In the expression: [B1.f, B2.f] In an equation for ‘x’: x = [B1.f, B2.f] + diff --git a/testsuite/tests/typecheck/should_compile/T15368.stderr b/testsuite/tests/typecheck/should_compile/T15368.stderr index 314297802897..ea5607d01877 100644 --- a/testsuite/tests/typecheck/should_compile/T15368.stderr +++ b/testsuite/tests/typecheck/should_compile/T15368.stderr @@ -1,4 +1,3 @@ - T15368.hs:11:15: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] • Found hole: _ :: (F a b, F a0 b0) Where: ‘a0’ is an ambiguous type variable @@ -19,8 +18,8 @@ T15368.hs:11:30: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)] with: F b a Expected: (F a0 b0, F b a) Actual: (F a0 b0, F b0 a0) - NB: ‘F’ is a non-injective type family - The type variables ‘b0’, ‘a0’ are ambiguous + Note: ‘F’ is a non-injective type family. + The type variables ‘b0’, ‘a0’ are ambiguous • In the second argument of ‘transitive’, namely ‘trigger _ _’ In the expression: _ `transitive` trigger _ _ In an equation for ‘trigger’: @@ -45,3 +44,4 @@ T15368.hs:11:40: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] In the expression: _ `transitive` trigger _ _ • Relevant bindings include trigger :: a -> b -> (F a b, F b a) (bound at T15368.hs:11:1) + diff --git a/testsuite/tests/typecheck/should_compile/T23156.stderr b/testsuite/tests/typecheck/should_compile/T23156.stderr index c72e97171b91..7eaf320683b2 100644 --- a/testsuite/tests/typecheck/should_compile/T23156.stderr +++ b/testsuite/tests/typecheck/should_compile/T23156.stderr @@ -1,11 +1,10 @@ - T23156.hs:51:6: warning: [GHC-05617] [-Wdeferred-type-errors (in -Wdefault)] • Could not deduce ‘BooleanOf2 (TensorOf2 1 r0) ~ BooleanOf2 r0’ from the context: ADReady r bound by the type signature for: f :: forall r. ADReady r => () at T23156.hs:51:6-33 - NB: ‘BooleanOf2’ is a non-injective type family + Note: ‘BooleanOf2’ is a non-injective type family. The type variables ‘r0’, ‘r0’ are ambiguous • In the ambiguity check for ‘f’ To defer the ambiguity check to use sites, enable AllowAmbiguousTypes @@ -19,7 +18,8 @@ T23156.hs:56:5: warning: [GHC-18872] [-Wdeferred-type-errors (in -Wdefault)] • Couldn't match type: BooleanOf2 (TensorOf2 1 r0) with: BooleanOf2 r0 arising from a use of ‘f’ - NB: ‘BooleanOf2’ is a non-injective type family + Note: ‘BooleanOf2’ is a non-injective type family. The type variables ‘r0’, ‘r0’ are ambiguous • In the expression: f In an equation for ‘g’: g = f + diff --git a/testsuite/tests/typecheck/should_fail/T19627.stderr b/testsuite/tests/typecheck/should_fail/T19627.stderr index af80fdc74dc7..7aebbb9cd81b 100644 --- a/testsuite/tests/typecheck/should_fail/T19627.stderr +++ b/testsuite/tests/typecheck/should_fail/T19627.stderr @@ -1,4 +1,3 @@ - T19627.hs:108:3: error: [GHC-05617] • Could not deduce ‘Not (p0 a b) ~ Not (p a b)’ from the context: Lol p @@ -9,8 +8,8 @@ T19627.hs:108:3: error: [GHC-05617] at T19627.hs:108:3-34 Expected: Not (p a b) -> b <#- a Actual: Not (p0 a b) -> b <#- a - NB: ‘Not’ is a non-injective type family - The type variable ‘p0’ is ambiguous + Note: ‘Not’ is a non-injective type family. + The type variable ‘p0’ is ambiguous • In the ambiguity check for ‘apartR’ To defer the ambiguity check to use sites, enable AllowAmbiguousTypes When checking the class method: @@ -35,7 +34,7 @@ T19627.hs:108:3: error: [GHC-05617] at T19627.hs:108:3-34 or from: (Prop a1, Prop b1) bound by a quantified context at T19627.hs:108:3-34 - The type variable ‘p0’ is ambiguous + The type variable ‘p0’ is ambiguous • In the ambiguity check for ‘apartR’ To defer the ambiguity check to use sites, enable AllowAmbiguousTypes When checking the class method: @@ -43,3 +42,4 @@ T19627.hs:108:3: error: [GHC-05617] Lol p => Not (p a b) -> b <#- a In the class declaration for ‘Lol’ + diff --git a/testsuite/tests/typecheck/should_fail/T21158.stderr b/testsuite/tests/typecheck/should_fail/T21158.stderr index fe5002d6c42d..28d2e68f6a22 100644 --- a/testsuite/tests/typecheck/should_fail/T21158.stderr +++ b/testsuite/tests/typecheck/should_fail/T21158.stderr @@ -1,11 +1,10 @@ - T21158.hs:12:14: error: [GHC-83865] • Couldn't match type: F b0 with: F b Expected: [F b] Actual: [F b0] - NB: ‘F’ is a non-injective type family - The type variable ‘b0’ is ambiguous + Note: ‘F’ is a non-injective type family. + The type variable ‘b0’ is ambiguous • In a record update at field ‘x’, with type constructor ‘T’ and data constructor ‘MkT’. @@ -19,11 +18,12 @@ T21158.hs:15:49: error: [GHC-83865] with: F b Expected: [F b] Actual: [F b1] - NB: ‘F’ is a non-injective type family - The type variable ‘b1’ is ambiguous + Note: ‘F’ is a non-injective type family. + The type variable ‘b1’ is ambiguous • In the second argument of ‘MkT’, namely ‘y’ In the expression: MkT newx y In a case alternative: MkT x y -> MkT newx y • Relevant bindings include y :: [F b1] (bound at T21158.hs:15:35) foo2 :: [Int] -> T b (bound at T21158.hs:15:1) + diff --git a/testsuite/tests/typecheck/should_fail/T22560_fail_a.stderr b/testsuite/tests/typecheck/should_fail/T22560_fail_a.stderr index 6bc23fec635f..6d29fdd07e68 100644 --- a/testsuite/tests/typecheck/should_fail/T22560_fail_a.stderr +++ b/testsuite/tests/typecheck/should_fail/T22560_fail_a.stderr @@ -1,8 +1,8 @@ - T22560_fail_a.hs:9:1: error: [GHC-57916] • Invalid invisible type variable binder: @k There is no matching forall-bound variable in the standalone kind signature for ‘P’. - NB. Only ‘forall a.’ -quantification matches invisible binders, - whereas ‘forall {a}.’ and ‘forall a ->’ do not. + Note: Only ‘forall a.’ -quantification matches invisible binders, + whereas ‘forall {a}.’ and ‘forall a ->’ do not. • In the data type declaration for ‘P’ + diff --git a/testsuite/tests/typecheck/should_fail/T22560_fail_b.stderr b/testsuite/tests/typecheck/should_fail/T22560_fail_b.stderr index b9a0eee4742f..c77d4d3360ed 100644 --- a/testsuite/tests/typecheck/should_fail/T22560_fail_b.stderr +++ b/testsuite/tests/typecheck/should_fail/T22560_fail_b.stderr @@ -1,8 +1,8 @@ - T22560_fail_b.hs:8:1: error: [GHC-57916] • Invalid invisible type variable binder: @a There is no matching forall-bound variable in the standalone kind signature for ‘P’. - NB. Only ‘forall a.’ -quantification matches invisible binders, - whereas ‘forall {a}.’ and ‘forall a ->’ do not. + Note: Only ‘forall a.’ -quantification matches invisible binders, + whereas ‘forall {a}.’ and ‘forall a ->’ do not. • In the data type declaration for ‘P’ + diff --git a/testsuite/tests/typecheck/should_fail/T8030.stderr b/testsuite/tests/typecheck/should_fail/T8030.stderr index e3a3b6a40b5d..65f1f4901fcb 100644 --- a/testsuite/tests/typecheck/should_fail/T8030.stderr +++ b/testsuite/tests/typecheck/should_fail/T8030.stderr @@ -1,9 +1,8 @@ - T8030.hs:9:3: error: [GHC-83865] • Couldn't match expected type: Pr a with actual type: Pr a0 - NB: ‘Pr’ is a non-injective type family - The type variable ‘a0’ is ambiguous + Note: ‘Pr’ is a non-injective type family. + The type variable ‘a0’ is ambiguous • In the ambiguity check for ‘op1’ To defer the ambiguity check to use sites, enable AllowAmbiguousTypes When checking the class method: @@ -15,10 +14,11 @@ T8030.hs:10:3: error: [GHC-83865] with: Pr a Expected: Pr a -> Pr a -> Pr a Actual: Pr a0 -> Pr a0 -> Pr a0 - NB: ‘Pr’ is a non-injective type family - The type variable ‘a0’ is ambiguous + Note: ‘Pr’ is a non-injective type family. + The type variable ‘a0’ is ambiguous • In the ambiguity check for ‘op2’ To defer the ambiguity check to use sites, enable AllowAmbiguousTypes When checking the class method: op2 :: forall k (a :: k). C a => Pr a -> Pr a -> Pr a In the class declaration for ‘C’ + diff --git a/testsuite/tests/typecheck/should_fail/T8034.stderr b/testsuite/tests/typecheck/should_fail/T8034.stderr index 04ba80c9adc5..2af8088e566f 100644 --- a/testsuite/tests/typecheck/should_fail/T8034.stderr +++ b/testsuite/tests/typecheck/should_fail/T8034.stderr @@ -1,12 +1,12 @@ - T8034.hs:7:3: error: [GHC-83865] • Couldn't match type: F a0 with: F a Expected: F a -> F a Actual: F a0 -> F a0 - NB: ‘F’ is a non-injective type family - The type variable ‘a0’ is ambiguous + Note: ‘F’ is a non-injective type family. + The type variable ‘a0’ is ambiguous • In the ambiguity check for ‘foo’ To defer the ambiguity check to use sites, enable AllowAmbiguousTypes When checking the class method: foo :: forall a. C a => F a -> F a In the class declaration for ‘C’ + diff --git a/testsuite/tests/typecheck/should_fail/TcCoercibleFail.stderr b/testsuite/tests/typecheck/should_fail/TcCoercibleFail.stderr index 593c164b5819..d1bfbf02ab55 100644 --- a/testsuite/tests/typecheck/should_fail/TcCoercibleFail.stderr +++ b/testsuite/tests/typecheck/should_fail/TcCoercibleFail.stderr @@ -1,4 +1,3 @@ - TcCoercibleFail.hs:11:8: error: [GHC-18872] • Couldn't match representation of type ‘Int’ with that of ‘()’ arising from a use of ‘coerce’ @@ -10,8 +9,8 @@ TcCoercibleFail.hs:14:8: error: [GHC-18872] • Couldn't match representation of type: m Int with that of: m Age arising from a use of ‘coerce’ - NB: We cannot know what roles the parameters to ‘m’ have; - we must assume that the role is nominal + Note: We cannot know what roles the parameters to ‘m’ have; + we must assume that the role is nominal. • In the first argument of ‘($)’, namely ‘coerce’ In the expression: coerce $ (return one :: m Int) In an equation for ‘foo2’: foo2 = coerce $ (return one :: m Int) @@ -67,3 +66,4 @@ TcCoercibleFail.hs:36:8: error: [GHC-18872] arising from a use of ‘coerce’ • In the expression: coerce :: Fix (Either Int) -> () In an equation for ‘foo7’: foo7 = coerce :: Fix (Either Int) -> () + diff --git a/testsuite/tests/typecheck/should_fail/tcfail182.stderr b/testsuite/tests/typecheck/should_fail/tcfail182.stderr index 3fed7c733e9e..d8b551586011 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail182.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail182.stderr @@ -1,12 +1,12 @@ - tcfail182.hs:9:3: error: [GHC-83865] • Couldn't match expected type: Prelude.Maybe a with actual type: Maybe a0 - NB: ‘Prelude.Maybe’ - is defined in ‘GHC.Internal.Maybe’ - in package ‘ghc-internal-0.1.0.0’ - ‘Maybe’ is defined at tcfail182.hs:6:1-18 + Note: ‘Prelude.Maybe’ + is defined in ‘GHC.Internal.Maybe’ + in package ‘ghc-internal-9.1001.0’ + ‘Maybe’ is defined at tcfail182.hs:6:1-18. • In the pattern: Foo In an equation for ‘f’: f Foo = 3 • Relevant bindings include f :: Prelude.Maybe a -> Int (bound at tcfail182.hs:9:1) + diff --git a/testsuite/tests/warnings/should_compile/T18862b.stderr b/testsuite/tests/warnings/should_compile/T18862b.stderr index 9ef46e6edc97..bd437eb272ae 100644 --- a/testsuite/tests/warnings/should_compile/T18862b.stderr +++ b/testsuite/tests/warnings/should_compile/T18862b.stderr @@ -1,8 +1,8 @@ - T18862b.hs:7:9: warning: [GHC-12003] [-Wtype-equality-out-of-scope (in -Wdefault)] • The ‘~’ operator is out of scope. Assuming it to stand for an equality constraint. - • NB: ‘~’ used to be built-in syntax but now is a regular type operator - exported from Data.Type.Equality and Prelude. - If you are using a custom Prelude, consider re-exporting it. + • Note: ‘~’ used to be built-in syntax but now is a regular type operator + exported from Data.Type.Equality and Prelude. + If you are using a custom Prelude, consider re-exporting it. • This will become an error in a future GHC release. + -- GitLab