[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: testsuite: Rename isCross() predicate to needsTargetWrapper()

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Thu Apr 18 10:22:52 UTC 2024



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
e1fbb34f by Matthew Pickering at 2024-04-18T06:22:25-04:00
testsuite: Rename isCross() predicate to needsTargetWrapper()

isCross() was a misnamed because it assumed that all cross targets would
provide a target wrapper, but the two most common cross targets
(javascript, wasm) don't need a target wrapper.

Therefore we rename this predicate to `needsTargetWrapper()` so
situations in the testsuite where we can check whether running
executables requires a target wrapper or not.

- - - - -
b51469e3 by Jade at 2024-04-18T06:22:26-04:00
Put the newline after errors instead of before them

This mainly has consequences for GHCi but also slightly alters how the
output of GHC on the commandline looks.

Fixes: #22499

- - - - -
fad2bd46 by Alan Zimmerman at 2024-04-18T06:22:26-04:00
EPA: Fix comments in mkListSyntaxTy0

Also extend the test to confirm.

Addresses #24669, 1 of 4

- - - - -
f58154ad by Serge S. Gulin at 2024-04-18T06:22:30-04:00
JS: set image `x86_64-linux-deb11-emsdk-closure` for build

- - - - -
768d72be by Alan Zimmerman at 2024-04-18T06:22:31-04:00
EPA: Provide correct span for PatBind

And remove unused parameter in checkPatBind

Contributes to #24669

- - - - -


26 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Utils/Logger.hs
- testsuite/driver/testglobals.py
- testsuite/driver/testlib.py
- testsuite/tests/ghci/prog018/prog018.stdout
- testsuite/tests/ghci/scripts/T9140.stdout
- testsuite/tests/layout/layout001.stdout
- testsuite/tests/layout/layout003.stdout
- testsuite/tests/layout/layout004.stdout
- testsuite/tests/layout/layout006.stdout
- testsuite/tests/linear/should_fail/LinearLet6.stderr
- testsuite/tests/linear/should_fail/LinearLet7.stderr
- testsuite/tests/overloadedrecflds/ghci/GHCiDRF.stdout
- testsuite/tests/overloadedrecflds/ghci/T19314.stdout
- testsuite/tests/overloadedrecflds/ghci/duplicaterecfldsghci01.stdout
- testsuite/tests/printer/AnnotationNoListTuplePuns.hs
- + testsuite/tests/printer/AnnotationNoListTuplePuns.stdout
- testsuite/tests/rename/should_compile/T13839.stdout
- testsuite/tests/th/T7276a.stdout
- testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -2,7 +2,7 @@ variables:
   GIT_SSL_NO_VERIFY: "1"
 
   # Commit of ghc/ci-images repository from which to pull Docker images
-  DOCKER_REV: a9297a370025101b479cfd4977f8f910814e03ab
+  DOCKER_REV: 064e90c26dffe5709bd5b87dbd211b9a8b21fc5b
 
   # Sequential version number of all cached things.
   # Bump to invalidate GitLab CI cache.


=====================================
.gitlab/generate-ci/gen_ci.hs
=====================================
@@ -107,6 +107,7 @@ data Opsys
 data LinuxDistro
   = Debian12
   | Debian11
+  | Debian11Js
   | Debian10
   | Debian9
   | Fedora33
@@ -285,12 +286,13 @@ tags arch opsys _bc = [runnerTag arch opsys] -- Tag for which runners we can use
 -- These names are used to find the docker image so they have to match what is
 -- in the docker registry.
 distroName :: LinuxDistro -> String
-distroName Debian12  = "deb12"
-distroName Debian11  = "deb11"
+distroName Debian12   = "deb12"
+distroName Debian11   = "deb11"
+distroName Debian11Js = "deb11-emsdk-closure"
 distroName Debian10   = "deb10"
-distroName Debian9   = "deb9"
-distroName Fedora33  = "fedora33"
-distroName Fedora38  = "fedora38"
+distroName Debian9    = "deb9"
+distroName Fedora33   = "fedora33"
+distroName Fedora38   = "fedora38"
 distroName Ubuntu1804 = "ubuntu18_04"
 distroName Ubuntu2004 = "ubuntu20_04"
 distroName Centos7    = "centos7"
@@ -1009,7 +1011,7 @@ job_groups =
      , fullyStaticBrokenTests (disableValidate (allowFailureGroup (standardBuildsWithConfig Amd64 (Linux Alpine312) staticNativeInt)))
      , validateBuilds Amd64 (Linux Debian11) (crossConfig "aarch64-linux-gnu" (Emulator "qemu-aarch64 -L /usr/aarch64-linux-gnu") Nothing)
 
-     , addValidateRule JSBackend (validateBuilds Amd64 (Linux Debian11) javascriptConfig)
+     , addValidateRule JSBackend (validateBuilds Amd64 (Linux Debian11Js) javascriptConfig)
 
      , make_wasm_jobs wasm_build_config
      , modifyValidateJobs manual $


=====================================
.gitlab/jobs.yaml
=====================================
@@ -1706,7 +1706,7 @@
       "XZ_OPT": "-9"
     }
   },
-  "nightly-x86_64-linux-deb11-int_native-cross_javascript-unknown-ghcjs-validate": {
+  "nightly-x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -1717,7 +1717,7 @@
     "artifacts": {
       "expire_in": "8 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb11-int_native-cross_javascript-unknown-ghcjs-validate.tar.xz",
+        "ghc-x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -1727,14 +1727,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb11-$CACHE_REV",
+      "key": "x86_64-linux-deb11-emsdk-closure-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11-emsdk-closure:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -1760,14 +1760,14 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "native",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-int_native-cross_javascript-unknown-ghcjs-validate",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate",
       "BUILD_FLAVOUR": "validate",
       "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
       "CONFIGURE_WRAPPER": "emconfigure",
       "CROSS_EMULATOR": "js-emulator",
       "CROSS_TARGET": "javascript-unknown-ghcjs",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb11-int_native-cross_javascript-unknown-ghcjs-validate",
+      "TEST_ENV": "x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate",
       "XZ_OPT": "-9"
     }
   },
@@ -5087,7 +5087,7 @@
       "TEST_ENV": "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate"
     }
   },
-  "x86_64-linux-deb11-int_native-cross_javascript-unknown-ghcjs-validate": {
+  "x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh save_test_output",
@@ -5098,7 +5098,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-linux-deb11-int_native-cross_javascript-unknown-ghcjs-validate.tar.xz",
+        "ghc-x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -5108,14 +5108,14 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-linux-deb11-$CACHE_REV",
+      "key": "x86_64-linux-deb11-emsdk-closure-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
       ]
     },
     "dependencies": [],
-    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11:$DOCKER_REV",
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb11-emsdk-closure:$DOCKER_REV",
     "needs": [
       {
         "artifacts": false,
@@ -5141,14 +5141,14 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "native",
-      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-int_native-cross_javascript-unknown-ghcjs-validate",
+      "BIN_DIST_NAME": "ghc-x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate",
       "BUILD_FLAVOUR": "validate",
       "CONFIGURE_ARGS": "--with-intree-gmp --enable-strict-ghc-toolchain-check",
       "CONFIGURE_WRAPPER": "emconfigure",
       "CROSS_EMULATOR": "js-emulator",
       "CROSS_TARGET": "javascript-unknown-ghcjs",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-linux-deb11-int_native-cross_javascript-unknown-ghcjs-validate"
+      "TEST_ENV": "x86_64-linux-deb11-emsdk-closure-int_native-cross_javascript-unknown-ghcjs-validate"
     }
   },
   "x86_64-linux-deb11-validate+boot_nonmoving_gc": {


=====================================
compiler/GHC/Hs/Binds.hs
=====================================
@@ -116,7 +116,7 @@ type instance XFunBind    (GhcPass pL) GhcTc = (HsWrapper, [CoreTickish])
 -- type         Int -> forall a'. a' -> a'
 -- Notice that the coercion captures the free a'.
 
-type instance XPatBind    GhcPs (GhcPass pR) = [AddEpAnn]
+type instance XPatBind    GhcPs (GhcPass pR) = NoExtField
 type instance XPatBind    GhcRn (GhcPass pR) = NameSet -- See Note [Bind free vars]
 type instance XPatBind    GhcTc (GhcPass pR) =
     ( Type                  -- Type of the GRHSs


=====================================
compiler/GHC/Parser.y
=====================================
@@ -2585,7 +2585,7 @@ decl_no_th :: { LHsDecl GhcPs }
                                           ; !cs <- getCommentsFor l
                                           ; return $! (sL (commentsA l cs) $ ValD noExtField r) } }
         | PREFIX_PERCENT atype infixexp     opt_sig rhs  {% runPV (unECP $3) >>= \ $3 ->
-                                       do { let { l = comb2 $3 $> }
+                                       do { let { l = comb2 $1 $> }
                                           ; r <- checkValDef l $3 (mkMultAnn (epTok $1) $2, $4) $5;
                                         -- parses bindings of the form %p x or
                                         -- %p x :: sig


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -1322,7 +1322,7 @@ checkValDef loc lhs (mult, Just (sigAnn, sig)) grhss
         -- x :: ty = rhs  parses as a *pattern* binding
   = do lhs' <- runPV $ mkHsTySigPV (combineLocsA lhs sig) lhs sig [sigAnn]
                         >>= checkLPat
-       checkPatBind loc [] lhs' grhss mult
+       checkPatBind loc lhs' grhss mult
 
 checkValDef loc lhs (mult_ann, Nothing) grhss
   | HsNoMultAnn{} <- mult_ann
@@ -1333,12 +1333,12 @@ checkValDef loc lhs (mult_ann, Nothing) grhss
                            fun is_infix pats grhss
             Nothing -> do
               lhs' <- checkPattern lhs
-              checkPatBind loc [] lhs' grhss mult_ann }
+              checkPatBind loc lhs' grhss mult_ann }
 
 checkValDef loc lhs (mult_ann, Nothing) ghrss
         -- %p x = rhs  parses as a *pattern* binding
   = do lhs' <- checkPattern lhs
-       checkPatBind loc [] lhs' ghrss mult_ann
+       checkPatBind loc lhs' ghrss mult_ann
 
 checkFunBind :: SrcStrictness
              -> SrcSpan
@@ -1376,15 +1376,14 @@ makeFunBind fn ms
 
 -- See Note [FunBind vs PatBind]
 checkPatBind :: SrcSpan
-             -> [AddEpAnn]
              -> LPat GhcPs
              -> Located (GRHSs GhcPs (LHsExpr GhcPs))
              -> HsMultAnn GhcPs
              -> P (HsBind GhcPs)
-checkPatBind loc annsIn (L _ (BangPat ans (L _ (VarPat _ v))))
+checkPatBind loc (L _ (BangPat ans (L _ (VarPat _ v))))
                         (L _match_span grhss) (HsNoMultAnn _)
       = return (makeFunBind v (L (noAnnSrcSpan loc)
-                [L (noAnnSrcSpan loc) (m (ans++annsIn) v)]))
+                [L (noAnnSrcSpan loc) (m ans v)]))
   where
     m a v = Match { m_ext = a
                   , m_ctxt = FunRhs { mc_fun    = v
@@ -1393,8 +1392,8 @@ checkPatBind loc annsIn (L _ (BangPat ans (L _ (VarPat _ v))))
                   , m_pats = []
                  , m_grhss = grhss }
 
-checkPatBind _loc annsIn lhs (L _ grhss) mult = do
-  return (PatBind annsIn lhs mult grhss)
+checkPatBind _loc lhs (L _ grhss) mult = do
+  return (PatBind noExtField lhs mult grhss)
 
 
 checkValSigLhs :: LHsExpr GhcPs -> P (LocatedN RdrName)
@@ -3317,12 +3316,12 @@ withCombinedComments ::
   HasLoc l2 =>
   l1 ->
   l2 ->
-  (SrcSpan -> EpAnnComments -> P a) ->
+  (SrcSpan -> P a) ->
   P (LocatedA a)
 withCombinedComments start end use = do
   cs <- getCommentsFor fullSpan
-  a <- use fullSpan cs
-  pure (L (noAnnSrcSpan fullSpan) a)
+  a <- use fullSpan
+  pure (L (EpAnn (spanAsAnchor fullSpan) noAnn cs) a)
   where
     fullSpan = combineSrcSpans (getHasLoc start) (getHasLoc end)
 
@@ -3362,15 +3361,14 @@ mkTupleSyntaxTycon boxity n =
 mkListSyntaxTy0 :: EpaLocation
                 -> EpaLocation
                 -> SrcSpan
-                -> EpAnnComments
                 -> P (HsType GhcPs)
-mkListSyntaxTy0 brkOpen brkClose span comments =
+mkListSyntaxTy0 brkOpen brkClose span =
   punsIfElse enabled disabled
   where
     enabled = HsTyVar noAnn NotPromoted rn
 
     -- attach the comments only to the RdrName since it's the innermost AST node
-    rn = L (EpAnn fullLoc rdrNameAnn comments) listTyCon_RDR
+    rn = L (EpAnn fullLoc rdrNameAnn emptyComments) listTyCon_RDR
 
     disabled =
       HsExplicitListTy annsKeyword NotPromoted []


=====================================
compiler/GHC/ThToHs.hs
=====================================
@@ -218,7 +218,7 @@ cvtDec (TH.ValD pat body ds)
         ; returnJustLA $ Hs.ValD noExtField $
           PatBind { pat_lhs = pat'
                   , pat_rhs = GRHSs emptyComments body' ds'
-                  , pat_ext = noAnn
+                  , pat_ext = noExtField
                   , pat_mult = HsNoMultAnn noExtField
                   } }
 


=====================================
compiler/GHC/Utils/Logger.hs
=====================================
@@ -417,14 +417,13 @@ defaultLogAction logflags msg_class srcSpan msg
       message = mkLocMessageWarningGroups (log_show_warn_groups logflags) msg_class srcSpan msg
 
       printDiagnostics = do
-        hPutChar stderr '\n'
         caretDiagnostic <-
             if log_show_caret logflags
             then getCaretDiagnostic msg_class srcSpan
             else pure empty
         printErrs $ getPprStyle $ \style ->
           withPprStyle (setStyleColoured True style)
-            (message $+$ caretDiagnostic)
+            (message $+$ caretDiagnostic $+$ blankLine)
         -- careful (#2302): printErrs prints in UTF-8,
         -- whereas converting to string first and using
         -- hPutStr would just emit the low 8 bits of


=====================================
testsuite/driver/testglobals.py
=====================================
@@ -182,8 +182,6 @@ class TestConfig:
         self.threads = 1
 
         # An optional executable used to wrap target code execution
-        # When set tests which aren't marked with TestConfig.cross_okay
-        # are skipped.
         self.target_wrapper = None
 
         # tests which should be considered to be broken during this testsuite
@@ -460,12 +458,6 @@ class TestOptions:
        # Should we copy the files of symlink the files for the test?
        self.copy_files = False
 
-       # Should the test be run in a cross-compiled tree?
-       #   None:  infer from test function
-       #   True:  run when --target-wrapper is set
-       #   False: do not run in cross-compiled trees
-       self.cross_okay = None # type: Optional[bool]
-
        # The extra hadrian dependencies we need for this particular test
        self.hadrian_deps = set(["test:ghc"]) # type: Set[str]
 


=====================================
testsuite/driver/testlib.py
=====================================
@@ -91,8 +91,8 @@ def setLocalTestOpts(opts: TestOptions) -> None:
     global testopts_ctx_var
     testopts_ctx_var.set(opts)
 
-def isCross() -> bool:
-    """ Are we testing a cross-compiler? """
+def needsTargetWrapper() -> bool:
+    """ Do we need to use a target wrapper? """
     return config.target_wrapper is not None
 
 def isCompilerStatsTest() -> bool:
@@ -240,7 +240,7 @@ def req_dynamic_hs( name, opts ):
         opts.expect = 'fail'
 
 def req_interp( name, opts ):
-    if not config.have_interp or isCross():
+    if not config.have_interp or needsTargetWrapper():
         opts.expect = 'fail'
     # skip on wasm32, otherwise they show up as unexpected passes
     if arch('wasm32'):
@@ -346,11 +346,10 @@ def req_host_target_ghc( name, opts ):
     """
     When testing a cross GHC, some test cases require a host GHC as well (e.g.
     for compiling custom Setup.hs). This is not supported yet (#23236), so for
-    the time being we skip them when testing cross GHCs. However, this is not
-    the case for the JS backend. The JS backend is a cross-compiler that
-    produces code that the host can run.
+    the time being we skip them when testing cross GHCs. However, for cross targets
+    which don't need a target wrapper (e.g. javascript), we can still run these testcases.
     """
-    if isCross() and not js_arch():
+    if needsTargetWrapper():
         opts.skip = True
 
 has_ls_files = None
@@ -1290,21 +1289,18 @@ async def test_common_work(name: TestName, opts,
                 all_ways = [WayName('ghci'), WayName('ghci-opt')]
             else:
                 all_ways = []
-            if isCross():
-                opts.cross_okay = False
+            if needsTargetWrapper():
+                opts.skip = True
         elif func in [makefile_test, run_command]:
             # makefile tests aren't necessarily runtime or compile-time
             # specific. Assume we can run them in all ways. See #16042 for what
             # happened previously.
             all_ways = config.compile_ways + config.run_ways
-            if isCross():
-                opts.cross_okay = False
+            if needsTargetWrapper():
+                opts.skip = True
         else:
             all_ways = [WayName('normal')]
 
-        if isCross() and opts.cross_okay is False:
-            opts.skip = True
-
         # A test itself can request extra ways by setting opts.extra_ways
         all_ways = list(OrderedDict.fromkeys(all_ways + [way for way in opts.extra_ways if way not in all_ways]))
 


=====================================
testsuite/tests/ghci/prog018/prog018.stdout
=====================================
@@ -1,7 +1,6 @@
 [1 of 3] Compiling A                ( A.hs, interpreted )
 [2 of 3] Compiling B                ( B.hs, interpreted )
 [3 of 3] Compiling C                ( C.hs, interpreted )
-
 A.hs:5:1: warning: [GHC-62161] [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In an equation for ‘incompletePattern’:
@@ -17,9 +16,10 @@ B.hs:7:1: warning: [GHC-66111] [-Wunused-imports (in -Wextra)]
 
 C.hs:6:7: error: [GHC-88464]
     Variable not in scope: variableNotInScope :: ()
+
 Failed, two modules loaded.
 [3 of 3] Compiling C                ( C.hs, interpreted )
-
 C.hs:6:7: error: [GHC-88464]
     Variable not in scope: variableNotInScope :: ()
+
 Failed, two modules reloaded.


=====================================
testsuite/tests/ghci/scripts/T9140.stdout
=====================================
@@ -1,4 +1,3 @@
-
 <interactive>:2:5: error: [GHC-20036]
     You can't mix polymorphic and unlifted bindings: a = (# 1 #)
     Suggested fix: Add a type signature.
@@ -10,3 +9,4 @@
 <interactive>:1:1: error: [GHC-17999]
     GHCi can't bind a variable of unlifted type:
       a :: (# Integer, Integer #)
+


=====================================
testsuite/tests/layout/layout001.stdout
=====================================
@@ -1,9 +1,9 @@
 Running with -XNoAlternativeLayoutRule
 Running with -XAlternativeLayoutRule
-
 layout001.hs:6:3: error: [GHC-58481] parse error on input ‘where’
-Running with -XAlternativeLayoutRule -XAlternativeLayoutRuleTransitional
 
+Running with -XAlternativeLayoutRule -XAlternativeLayoutRuleTransitional
 layout001.hs:6:3: warning: [GHC-93617] [-Walternative-layout-rule-transitional (in -Wdefault)]
     transitional layout will not be accepted in the future:
     `where' clause at the same depth as implicit layout block
+


=====================================
testsuite/tests/layout/layout003.stdout
=====================================
@@ -1,9 +1,9 @@
 Running with -XNoAlternativeLayoutRule
 Running with -XAlternativeLayoutRule
-
 layout003.hs:11:4: error: [GHC-58481] parse error on input ‘|’
-Running with -XAlternativeLayoutRule -XAlternativeLayoutRuleTransitional
 
+Running with -XAlternativeLayoutRule -XAlternativeLayoutRuleTransitional
 layout003.hs:11:4: warning: [GHC-93617] [-Walternative-layout-rule-transitional (in -Wdefault)]
     transitional layout will not be accepted in the future:
     `|' at the same depth as implicit layout block
+


=====================================
testsuite/tests/layout/layout004.stdout
=====================================
@@ -1,7 +1,7 @@
 Running with -XNoAlternativeLayoutRule
 Running with -XAlternativeLayoutRule
-
 layout004.hs:7:14: error: [GHC-58481] parse error on input ‘,’
-Running with -XAlternativeLayoutRule -XAlternativeLayoutRuleTransitional
 
+Running with -XAlternativeLayoutRule -XAlternativeLayoutRuleTransitional
 layout004.hs:7:14: error: [GHC-58481] parse error on input ‘,’
+


=====================================
testsuite/tests/layout/layout006.stdout
=====================================
@@ -1,13 +1,12 @@
 Running with -XNoAlternativeLayoutRule
-
 layout006.hs:12:4: warning: [GHC-53633] [-Woverlapping-patterns (in -Wdefault)]
     Pattern match is redundant
     In an equation for ‘f’: f | True = ...
-Running with -XAlternativeLayoutRule
 
+Running with -XAlternativeLayoutRule
 layout006.hs:12:2: error: [GHC-58481] parse error on input ‘|’
-Running with -XAlternativeLayoutRule -XAlternativeLayoutRuleTransitional
 
+Running with -XAlternativeLayoutRule -XAlternativeLayoutRuleTransitional
 layout006.hs:12:2: warning: [GHC-93617] [-Walternative-layout-rule-transitional (in -Wdefault)]
     transitional layout will not be accepted in the future:
     `|' at the same depth as implicit layout block
@@ -15,3 +14,4 @@ layout006.hs:12:2: warning: [GHC-93617] [-Walternative-layout-rule-transitional
 layout006.hs:12:4: warning: [GHC-53633] [-Woverlapping-patterns (in -Wdefault)]
     Pattern match is redundant
     In an equation for ‘f’: f | True = ...
+


=====================================
testsuite/tests/linear/should_fail/LinearLet6.stderr
=====================================
@@ -13,7 +13,7 @@ LinearLet6.hs:10:3: error: [GHC-18872]
             where
                 (Just y) = x
 
-LinearLet6.hs:15:14: error: [GHC-18872]
+LinearLet6.hs:15:11: error: [GHC-18872]
     • Couldn't match type ‘Many’ with ‘One’
         arising from a non-linear pattern ‘Just y’
           (non-variable lazy pattern aren't linear)


=====================================
testsuite/tests/linear/should_fail/LinearLet7.stderr
=====================================
@@ -1,14 +1,14 @@
 
-LinearLet7.hs:6:14: error: [GHC-18872]
+LinearLet7.hs:6:11: error: [GHC-18872]
     • Couldn't match type ‘Many’ with ‘One’
-        arising from multiplicity of ‘g’
-    • In a pattern binding: g = \ y -> g y
-      In the expression: let %1 g = \ y -> ... in g x
+        arising from a non-linear pattern ‘_’
+          (non-variable pattern bindings that have been generalised aren't linear)
+    • In the expression: let %1 g = \ y -> ... in g x
       In an equation for ‘f’: f x = let %1 g = ... in g x
 
 LinearLet7.hs:6:14: error: [GHC-18872]
     • Couldn't match type ‘Many’ with ‘One’
-        arising from a non-linear pattern ‘_’
-          (non-variable pattern bindings that have been generalised aren't linear)
-    • In the expression: let %1 g = \ y -> ... in g x
+        arising from multiplicity of ‘g’
+    • In a pattern binding: g = \ y -> g y
+      In the expression: let %1 g = \ y -> ... in g x
       In an equation for ‘f’: f x = let %1 g = ... in g x


=====================================
testsuite/tests/overloadedrecflds/ghci/GHCiDRF.stdout
=====================================
@@ -1,10 +1,10 @@
 GHCiDRF.foo :: T -> Int
-
 <interactive>:1:1: error: [GHC-87543]
     Ambiguous occurrence ‘GHCiDRF.bar’.
     It could refer to
        either the field ‘bar’ of record ‘T’, defined at GHCiDRF.hs:3:28,
            or the field ‘bar’ of record ‘U’, defined at GHCiDRF.hs:4:16.
+
 type T :: *
 data T = MkT {foo :: Int, ...}
   	-- Defined at GHCiDRF.hs:3:16
@@ -16,7 +16,6 @@ type U :: *
 data U = MkU {bar :: Bool}
   	-- Defined at GHCiDRF.hs:4:16
 GHCiDRF.foo :: GHCiDRF.T -> Int
-
 <interactive>:1:1: error: [GHC-87543]
     Ambiguous occurrence ‘GHCiDRF.bar’.
     It could refer to
@@ -26,6 +25,7 @@ GHCiDRF.foo :: GHCiDRF.T -> Int
            or the field ‘bar’ belonging to data constructor ‘MkU’,
               imported qualified from ‘GHCiDRF’
               (and originally defined at GHCiDRF.hs:4:16-18).
+
 type GHCiDRF.T :: *
 data GHCiDRF.T = GHCiDRF.MkT {GHCiDRF.foo :: Int, ...}
   	-- Defined at GHCiDRF.hs:3:16
@@ -36,7 +36,6 @@ data GHCiDRF.T = GHCiDRF.MkT {..., GHCiDRF.bar :: Int}
 type GHCiDRF.U :: *
 data GHCiDRF.U = GHCiDRF.MkU {GHCiDRF.bar :: Bool}
   	-- Defined at GHCiDRF.hs:4:16
-
 <interactive>:11:1: error: [GHC-87543]
     Ambiguous occurrence ‘GHCiDRF.bar’.
     It could refer to
@@ -46,3 +45,4 @@ data GHCiDRF.U = GHCiDRF.MkU {GHCiDRF.bar :: Bool}
            or the field ‘bar’ belonging to data constructor ‘MkU’,
               imported qualified from ‘GHCiDRF’
               (and originally defined at GHCiDRF.hs:4:16-18).
+


=====================================
testsuite/tests/overloadedrecflds/ghci/T19314.stdout
=====================================
@@ -1,6 +1,5 @@
 w :: [a] -> a
 x :: [a] -> a
-
 <interactive>:1:1: error: [GHC-88464]
     Variable not in scope: y
     Suggested fix:
@@ -12,3 +11,4 @@ x :: [a] -> a
     Suggested fix:
       Notice that ‘z’ is a field selector
       that has been suppressed by NoFieldSelectors.
+


=====================================
testsuite/tests/overloadedrecflds/ghci/duplicaterecfldsghci01.stdout
=====================================
@@ -7,7 +7,6 @@ type T :: * -> *
 data T a = MkT {foo :: Bool, ...}
   	-- Defined at <interactive>:4:18
 True
-
 <interactive>:1:1: error: [GHC-87543]
     Ambiguous occurrence ‘foo’.
     It could refer to
@@ -15,6 +14,7 @@ True
               defined at <interactive>:3:16,
            or the field ‘foo’ of record ‘T’,
               defined at <interactive>:4:18.
+
 type U :: *
 data U = MkU {foo :: Int}
   	-- Defined at <interactive>:12:16


=====================================
testsuite/tests/printer/AnnotationNoListTuplePuns.hs
=====================================
@@ -1,17 +1,18 @@
 {-# language NoListTuplePuns #-}
+{-# OPTIONS -ddump-parsed-ast #-}
 module AnnotationNoListTuplePuns where
 
 type A =
-  -- comment pre
+  -- comment pre A
   [
-    -- comment inside
+    -- comment inside A
   ]
-  -- comment post
+  -- comment post A
 
 type B =
-  -- comment pre
+  -- comment pre B
   [
-    -- comment inside
+    -- comment inside B
     Bool
   ]
-  -- comment post
+  -- comment post B


=====================================
testsuite/tests/printer/AnnotationNoListTuplePuns.stdout
=====================================
@@ -0,0 +1,323 @@
+
+==================== Parser AST ====================
+
+(L
+ { AnnotationNoListTuplePuns.hs:1:1 }
+ (HsModule
+  (XModulePs
+   (EpAnn
+    (EpaSpan { AnnotationNoListTuplePuns.hs:1:1 })
+    (AnnsModule
+     [(AddEpAnn AnnModule (EpaSpan { AnnotationNoListTuplePuns.hs:3:1-6 }))
+     ,(AddEpAnn AnnWhere (EpaSpan { AnnotationNoListTuplePuns.hs:3:34-38 }))]
+     []
+     []
+     (Just
+      ((,)
+       { AnnotationNoListTuplePuns.hs:19:1 }
+       { AnnotationNoListTuplePuns.hs:18:3-19 })))
+    (EpaCommentsBalanced
+     [(L
+       (EpaSpan
+        { AnnotationNoListTuplePuns.hs:1:1-32 })
+       (EpaComment
+        (EpaBlockComment
+         "{-# language NoListTuplePuns #-}")
+        { AnnotationNoListTuplePuns.hs:1:1 }))
+     ,(L
+       (EpaSpan
+        { AnnotationNoListTuplePuns.hs:2:1-33 })
+       (EpaComment
+        (EpaBlockComment
+         "{-# OPTIONS -ddump-parsed-ast #-}")
+        { AnnotationNoListTuplePuns.hs:1:1-32 }))]
+     [(L
+       (EpaSpan
+        { AnnotationNoListTuplePuns.hs:18:3-19 })
+       (EpaComment
+        (EpaLineComment
+         "-- comment post B")
+        { AnnotationNoListTuplePuns.hs:17:3 }))]))
+   (EpVirtualBraces
+    (1))
+   (Nothing)
+   (Nothing))
+  (Just
+   (L
+    (EpAnn
+     (EpaSpan { AnnotationNoListTuplePuns.hs:3:8-32 })
+     (AnnListItem
+      [])
+     (EpaComments
+      []))
+    {ModuleName: AnnotationNoListTuplePuns}))
+  (Nothing)
+  []
+  [(L
+    (EpAnn
+     (EpaSpan { AnnotationNoListTuplePuns.hs:(5,1)-(9,3) })
+     (AnnListItem
+      [])
+     (EpaComments
+      [(L
+        (EpaSpan
+         { AnnotationNoListTuplePuns.hs:6:3-18 })
+        (EpaComment
+         (EpaLineComment
+          "-- comment pre A")
+         { AnnotationNoListTuplePuns.hs:5:8 }))]))
+    (TyClD
+     (NoExtField)
+     (SynDecl
+      [(AddEpAnn AnnType (EpaSpan { AnnotationNoListTuplePuns.hs:5:1-4 }))
+      ,(AddEpAnn AnnEqual (EpaSpan { AnnotationNoListTuplePuns.hs:5:8 }))]
+      (L
+       (EpAnn
+        (EpaSpan { AnnotationNoListTuplePuns.hs:5:6 })
+        (NameAnnTrailing
+         [])
+        (EpaComments
+         []))
+       (Unqual
+        {OccName: A}))
+      (HsQTvs
+       (NoExtField)
+       [])
+      (Prefix)
+      (L
+       (EpAnn
+        (EpaSpan { AnnotationNoListTuplePuns.hs:(7,3)-(9,3) })
+        (AnnListItem
+         [])
+        (EpaComments
+         [(L
+           (EpaSpan
+            { AnnotationNoListTuplePuns.hs:8:5-23 })
+           (EpaComment
+            (EpaLineComment
+             "-- comment inside A")
+            { AnnotationNoListTuplePuns.hs:7:3 }))]))
+       (HsExplicitListTy
+        [(AddEpAnn AnnOpenS (EpaSpan { AnnotationNoListTuplePuns.hs:7:3 }))
+        ,(AddEpAnn AnnCloseS (EpaSpan { AnnotationNoListTuplePuns.hs:9:3 }))]
+        (NotPromoted)
+        [])))))
+  ,(L
+    (EpAnn
+     (EpaSpan { AnnotationNoListTuplePuns.hs:(12,1)-(17,3) })
+     (AnnListItem
+      [])
+     (EpaComments
+      [(L
+        (EpaSpan
+         { AnnotationNoListTuplePuns.hs:10:3-19 })
+        (EpaComment
+         (EpaLineComment
+          "-- comment post A")
+         { AnnotationNoListTuplePuns.hs:9:3 }))
+      ,(L
+        (EpaSpan
+         { AnnotationNoListTuplePuns.hs:13:3-18 })
+        (EpaComment
+         (EpaLineComment
+          "-- comment pre B")
+         { AnnotationNoListTuplePuns.hs:12:8 }))]))
+    (TyClD
+     (NoExtField)
+     (SynDecl
+      [(AddEpAnn AnnType (EpaSpan { AnnotationNoListTuplePuns.hs:12:1-4 }))
+      ,(AddEpAnn AnnEqual (EpaSpan { AnnotationNoListTuplePuns.hs:12:8 }))]
+      (L
+       (EpAnn
+        (EpaSpan { AnnotationNoListTuplePuns.hs:12:6 })
+        (NameAnnTrailing
+         [])
+        (EpaComments
+         []))
+       (Unqual
+        {OccName: B}))
+      (HsQTvs
+       (NoExtField)
+       [])
+      (Prefix)
+      (L
+       (EpAnn
+        (EpaSpan { AnnotationNoListTuplePuns.hs:(14,3)-(17,3) })
+        (AnnListItem
+         [])
+        (EpaComments
+         [(L
+           (EpaSpan
+            { AnnotationNoListTuplePuns.hs:15:5-23 })
+           (EpaComment
+            (EpaLineComment
+             "-- comment inside B")
+            { AnnotationNoListTuplePuns.hs:14:3 }))]))
+       (HsExplicitListTy
+        [(AddEpAnn AnnOpenS (EpaSpan { AnnotationNoListTuplePuns.hs:14:3 }))
+        ,(AddEpAnn AnnCloseS (EpaSpan { AnnotationNoListTuplePuns.hs:17:3 }))]
+        (NotPromoted)
+        [(L
+          (EpAnn
+           (EpaSpan { AnnotationNoListTuplePuns.hs:16:5-8 })
+           (AnnListItem
+            [])
+           (EpaComments
+            []))
+          (HsTyVar
+           []
+           (NotPromoted)
+           (L
+            (EpAnn
+             (EpaSpan { AnnotationNoListTuplePuns.hs:16:5-8 })
+             (NameAnnTrailing
+              [])
+             (EpaComments
+              []))
+            (Unqual
+             {OccName: Bool}))))])))))]))
+
+
+
+==================== Parser AST ====================
+
+(L
+ { AnnotationNoListTuplePuns.ppr.hs:1:1 }
+ (HsModule
+  (XModulePs
+   (EpAnn
+    (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:1:1 })
+    (AnnsModule
+     [(AddEpAnn AnnModule (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:3:1-6 }))
+     ,(AddEpAnn AnnWhere (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:3:34-38 }))]
+     []
+     []
+     (Just
+      ((,)
+       { AnnotationNoListTuplePuns.ppr.hs:5:16 }
+       { AnnotationNoListTuplePuns.ppr.hs:5:15 })))
+    (EpaCommentsBalanced
+     [(L
+       (EpaSpan
+        { AnnotationNoListTuplePuns.ppr.hs:1:1-32 })
+       (EpaComment
+        (EpaBlockComment
+         "{-# language NoListTuplePuns #-}")
+        { AnnotationNoListTuplePuns.ppr.hs:1:1 }))
+     ,(L
+       (EpaSpan
+        { AnnotationNoListTuplePuns.ppr.hs:2:1-33 })
+       (EpaComment
+        (EpaBlockComment
+         "{-# OPTIONS -ddump-parsed-ast #-}")
+        { AnnotationNoListTuplePuns.ppr.hs:1:1-32 }))]
+     []))
+   (EpVirtualBraces
+    (1))
+   (Nothing)
+   (Nothing))
+  (Just
+   (L
+    (EpAnn
+     (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:3:8-32 })
+     (AnnListItem
+      [])
+     (EpaComments
+      []))
+    {ModuleName: AnnotationNoListTuplePuns}))
+  (Nothing)
+  []
+  [(L
+    (EpAnn
+     (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:1-11 })
+     (AnnListItem
+      [])
+     (EpaComments
+      []))
+    (TyClD
+     (NoExtField)
+     (SynDecl
+      [(AddEpAnn AnnType (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:1-4 }))
+      ,(AddEpAnn AnnEqual (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:8 }))]
+      (L
+       (EpAnn
+        (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:6 })
+        (NameAnnTrailing
+         [])
+        (EpaComments
+         []))
+       (Unqual
+        {OccName: A}))
+      (HsQTvs
+       (NoExtField)
+       [])
+      (Prefix)
+      (L
+       (EpAnn
+        (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:10-11 })
+        (AnnListItem
+         [])
+        (EpaComments
+         []))
+       (HsExplicitListTy
+        [(AddEpAnn AnnOpenS (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:10 }))
+        ,(AddEpAnn AnnCloseS (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:4:11 }))]
+        (NotPromoted)
+        [])))))
+  ,(L
+    (EpAnn
+     (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:1-15 })
+     (AnnListItem
+      [])
+     (EpaComments
+      []))
+    (TyClD
+     (NoExtField)
+     (SynDecl
+      [(AddEpAnn AnnType (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:1-4 }))
+      ,(AddEpAnn AnnEqual (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:8 }))]
+      (L
+       (EpAnn
+        (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:6 })
+        (NameAnnTrailing
+         [])
+        (EpaComments
+         []))
+       (Unqual
+        {OccName: B}))
+      (HsQTvs
+       (NoExtField)
+       [])
+      (Prefix)
+      (L
+       (EpAnn
+        (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:10-15 })
+        (AnnListItem
+         [])
+        (EpaComments
+         []))
+       (HsExplicitListTy
+        [(AddEpAnn AnnOpenS (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:10 }))
+        ,(AddEpAnn AnnCloseS (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:15 }))]
+        (NotPromoted)
+        [(L
+          (EpAnn
+           (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:11-14 })
+           (AnnListItem
+            [])
+           (EpaComments
+            []))
+          (HsTyVar
+           []
+           (NotPromoted)
+           (L
+            (EpAnn
+             (EpaSpan { AnnotationNoListTuplePuns.ppr.hs:5:11-14 })
+             (NameAnnTrailing
+              [])
+             (EpaComments
+              []))
+            (Unqual
+             {OccName: Bool}))))])))))]))
+
+


=====================================
testsuite/tests/rename/should_compile/T13839.stdout
=====================================
@@ -1,5 +1,5 @@
-
 T13839a.hs:10:1: warning: [GHC-40910] [-Wunused-top-binds (in -Wextra, -Wunused-binds)]
     Defined but not used: ‘nonUsed’
+
 nonUsed :: ()
 nonUsed :: ()


=====================================
testsuite/tests/th/T7276a.stdout
=====================================
@@ -1,4 +1,3 @@
-
 <interactive>:3:9: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)]
     • Couldn't match type ‘[Dec]’ with ‘Exp’
       Expected: Q Exp
@@ -17,3 +16,4 @@
 (deferred type error)
       Code: x
     • In the untyped splice: $x
+


=====================================
testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr
=====================================
@@ -1,4 +1,3 @@
-
 CaretDiagnostics1.hs:7:8-15: error: [GHC-83865]
     • Couldn't match expected type ‘IO a0’ with actual type ‘Int’
     • In the second argument of ‘(+)’, namely ‘(3 :: Int)’
@@ -68,3 +67,4 @@ CaretDiagnostics1.hs:23:25-26: error: [GHC-83865]
    |
 23 | tabby2 =                ()
    |                         ^^
+



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d858d29de674dc3fedd505be23ffb6e42f646b77...768d72be838231114737a91f9aaa7c8481f2b895

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d858d29de674dc3fedd505be23ffb6e42f646b77...768d72be838231114737a91f9aaa7c8481f2b895
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20240418/13ca872a/attachment-0001.html>


More information about the ghc-commits mailing list