[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 14 commits: gitlab-ci: Bump ci-images

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Mon Nov 25 01:26:01 UTC 2024



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


Commits:
970ada5a by Ben Gamari at 2024-11-22T23:32:06-05:00
gitlab-ci: Bump ci-images

For introduction of Alpine/i386 image.

Thanks to Julian for the base image.

Co-Authored-By: Julian Ospald <hasufell at hasufell.de>

- - - - -
8115abc2 by Ben Gamari at 2024-11-22T23:32:06-05:00
gitlab-ci: Add release job for i386/Alpine

As requested by Mikolaj and started by Julian.

Co-Authored-By: Julian Ospald <hasufell at hasufell.de>

- - - - -
639f0149 by Ben Gamari at 2024-11-22T23:32:06-05:00
rts/linker/Elf: Resolve _GLOBAL_OFFSET_TABLE_

- - - - -
490d4d0a by Ben Gamari at 2024-11-22T23:32:06-05:00
gitlab-ci: Mark i386 Alpine test breakages

Marks the following tests as broken on i386/Alpine:

 * T22033 due to #25497
 * simd009, T25062_V16, T25169, T22187_run due to #25498

- - - - -
536cdf09 by Cheng Shao at 2024-11-22T23:32:42-05:00
compiler: remove unused GHC.Linker.Loader.loadExpr

This patch removes the unused `GHC.Linker.Loader.loadExpr` function.
It was moved from `GHC.Runtime.Linker.linkExpr` in `ghc-9.0` to
`GHC.Linker.Loader.loadExpr` in `ghc-9.2`, and remain completely
unused and untested ever since. There's also no third party user of
this function to my best knowledge, so let's remove this. Anyone who
wants to write their own GHC API function to load bytecode can consult
the source code in older release branches.

- - - - -
6ee35024 by Drew Fenwick at 2024-11-22T23:33:26-05:00
Fix a non-compiling example in the type abstractions docs

This patch adds a missing Show constraint to a code example in the User Guide's type abstractions docs to fix issue #25422.
- - - - -
d1172e20 by Rodrigo Mesquita at 2024-11-22T23:34:02-05:00
Re-introduce ErrorCallWithLocation with a deprecation pragma

With the removal of the duplicate backtrace, part of CLC proposal #285,
the constructor `ErrorCallWithLocation` was removed from base.

This commit re-introduces it with a deprecation.

- - - - -
1187a60a by Ben Gamari at 2024-11-22T23:34:39-05:00
testsuite: Skip tests requiring Hadrian deps in out-of-tree testsuite runs

Some testsuite tests require specific tools (e.g. `check-ppr` and
`check-exact`) beyond those shipped in the binary distribution. Skip
these tests.

Fixes #13897.

- - - - -
c37d7a2e by Ben Gamari at 2024-11-22T23:34:39-05:00
testsuite: Declare exactprint tests' dependency on check-exact

- - - - -
454ce957 by Ben Gamari at 2024-11-22T23:35:15-05:00
ghc-internal: Fix a few cases of missing Haddock markup

- - - - -
a249649b by Ben Gamari at 2024-11-22T23:35:51-05:00
testsuite/GHCiPrimCall : Add missing Makefile includes

- - - - -
a021a493 by Ben Gamari at 2024-11-22T23:35:51-05:00
testsuite/IpeStats: Use Make rather than shell interpolation

- - - - -
340aed44 by Ben Gamari at 2024-11-24T20:25:25-05:00
hadrian-ghci-multi: Pass -this-package-name in unit response files

As noted in #25509, the `-this-package-name` must be passed for each
package to ensure that GHC can response references to the packages'
exposed modules via package-qualified imports. Fix this.

Closes #25509.

- - - - -
5002fa3d by Simon Hengel at 2024-11-24T20:25:33-05:00
Refactoring: Use `OnOff` more consistently for `Extension`

- - - - -


21 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Types/Hint/Ppr.hs
- docs/users_guide/exts/type_abstractions.rst
- hadrian/src/Rules/ToolArgs.hs
- libraries/ghc-internal/src/GHC/Internal/Exception.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Handle/FD.hs
- rts/Linker.c
- testsuite/driver/testlib.py
- testsuite/tests/ghc-api/exactprint/all.T
- testsuite/tests/ghci/should_run/GHCiPrimCall/Makefile
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/rts/ipe/IpeStats/Makefile


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: efc1ab81236eb37e20cb287ec77aebb6c6341098
+  DOCKER_REV: eb4d3389fd62e4f7321a0c8799014ec1f4da0708
 
   # Sequential version number of all cached things.
   # Bump to invalidate GitLab CI cache.


=====================================
.gitlab/generate-ci/gen_ci.hs
=====================================
@@ -415,6 +415,13 @@ type Variables = MonoidalMap String [String]
 (=:) :: String -> String -> Variables
 a =: b = MonoidalMap (Map.singleton a [b])
 
+type TestName = String
+
+brokenTest :: TestName -- ^ test name
+           -> String -- ^ explanation of breakage
+           -> Variables
+brokenTest test _why = "BROKEN_TESTS" =: test
+
 opsysVariables :: Arch -> Opsys -> Variables
 opsysVariables _ FreeBSD13 = mconcat
   [ -- N.B. we use iconv from ports as I see linker errors when we attempt
@@ -463,13 +470,16 @@ alpineVariables arch = mconcat $
   [ -- Due to #20266
     "CONFIGURE_ARGS" =: "--disable-ld-override"
   , "INSTALL_CONFIGURE_ARGS" =: "--disable-ld-override"
-    -- encoding004: due to lack of locale support
-    -- T10458, ghcilink002: due to #17869
-  , "BROKEN_TESTS" =: "encoding004 T10458"
+  , brokenTest "encoding004" "due to lack of locale support"
+  , brokenTest "T10458" "#17869"
+  ] ++
+  [ mconcat [ brokenTest test "#25498" | test <- ["simd009", "T25062_V16", "T25169", "T22187_run"] ]
+  | I386 <- [arch]
   ] ++
+  [ brokenTest "T22033" "#25497" | I386 <- [arch] ] ++
   [-- Bootstrap compiler has incorrectly configured target triple #25200
     "CONFIGURE_ARGS" =: "--enable-ignore-build-platform-mismatch --build=aarch64-unknown-linux --host=aarch64-unknown-linux --target=aarch64-unknown-linux"
-    |  AArch64 <- [arch]
+  | AArch64 <- [arch]
   ]
 
 
@@ -479,7 +489,7 @@ distroVariables arch Alpine318 = alpineVariables arch
 distroVariables arch Alpine320 = alpineVariables arch
 distroVariables _ Centos7 = mconcat [
     "HADRIAN_ARGS" =: "--docs=no-sphinx"
-  , "BROKEN_TESTS" =: "T22012" -- due to #23979
+  , brokenTest "T22012" "#23979"
   ]
 distroVariables _ Fedora33 = mconcat
   -- LLC/OPT do not work for some reason in our fedora images
@@ -1138,6 +1148,7 @@ alpine_x86 =
   -- Dynamically linked build, suitable for building your own static executables on alpine
   , disableValidate (standardBuildsWithConfig Amd64 (Linux Alpine312) (splitSectionsBroken vanilla))
   , disableValidate (standardBuildsWithConfig Amd64 (Linux Alpine320) (splitSectionsBroken vanilla))
+  , allowFailureGroup (standardBuildsWithConfig I386 (Linux Alpine320) (splitSectionsBroken vanilla))
   ]
   where
     -- ghcilink002 broken due to #17869


=====================================
.gitlab/jobs.yaml
=====================================
@@ -315,6 +315,69 @@
       "TEST_ENV": "aarch64-linux-deb12-validate+llvm"
     }
   },
+  "i386-linux-alpine3_20-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": true,
+    "artifacts": {
+      "expire_in": "2 weeks",
+      "paths": [
+        "ghc-i386-linux-alpine3_20-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "i386-linux-alpine3_20-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/i386-linux-alpine3_20:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "((($ONLY_JOBS) && ($ONLY_JOBS =~ /.*\\bi386-linux-alpine3_20-validate(\\s|$).*/)) || (($ONLY_JOBS == null) && ((($CI_MERGE_REQUEST_LABELS =~ /.*full-ci.*/) || ($CI_MERGE_REQUEST_LABELS =~ /.*marge_bot_batch_merge_job.*/) || ($CI_COMMIT_BRANCH == \"master\") || ($CI_COMMIT_BRANCH =~ /ghc-[0-9]+\\.[0-9]+/))))) && ($RELEASE_JOB != \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-i386-linux-alpine3_20-validate",
+      "BROKEN_TESTS": "encoding004 T10458 simd009 T25062_V16 T25169 T22187_run T22033",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "i386-linux-alpine3_20-validate"
+    }
+  },
   "i386-linux-deb10-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
@@ -759,6 +822,70 @@
       "XZ_OPT": "-9"
     }
   },
+  "nightly-i386-linux-alpine3_20-validate": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": true,
+    "artifacts": {
+      "expire_in": "8 weeks",
+      "paths": [
+        "ghc-i386-linux-alpine3_20-validate.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "i386-linux-alpine3_20-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/i386-linux-alpine3_20:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "(\"true\" == \"true\") && ($RELEASE_JOB != \"yes\") && ($NIGHTLY)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-i386-linux-alpine3_20-validate",
+      "BROKEN_TESTS": "encoding004 T10458 simd009 T25062_V16 T25169 T22187_run T22033",
+      "BUILD_FLAVOUR": "validate",
+      "CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "i386-linux-alpine3_20-validate",
+      "XZ_OPT": "-9"
+    }
+  },
   "nightly-i386-linux-deb10-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
@@ -3450,6 +3577,72 @@
       "XZ_OPT": "-9"
     }
   },
+  "release-i386-linux-alpine3_20-release+no_split_sections": {
+    "after_script": [
+      ".gitlab/ci.sh save_cache",
+      ".gitlab/ci.sh save_test_output",
+      ".gitlab/ci.sh clean",
+      "cat ci_timings"
+    ],
+    "allow_failure": true,
+    "artifacts": {
+      "expire_in": "1 year",
+      "paths": [
+        "ghc-i386-linux-alpine3_20-release+no_split_sections.tar.xz",
+        "junit.xml",
+        "unexpected-test-output.tar.gz"
+      ],
+      "reports": {
+        "junit": "junit.xml"
+      },
+      "when": "always"
+    },
+    "cache": {
+      "key": "i386-linux-alpine3_20-$CACHE_REV",
+      "paths": [
+        "cabal-cache",
+        "toolchain"
+      ]
+    },
+    "dependencies": [],
+    "image": "registry.gitlab.haskell.org/ghc/ci-images/i386-linux-alpine3_20:$DOCKER_REV",
+    "needs": [
+      {
+        "artifacts": false,
+        "job": "hadrian-ghc-in-ghci"
+      }
+    ],
+    "rules": [
+      {
+        "if": "(\"true\" == \"true\") && ($RELEASE_JOB == \"yes\") && ($NIGHTLY == null)",
+        "when": "on_success"
+      }
+    ],
+    "script": [
+      "sudo chown ghc:ghc -R .",
+      ".gitlab/ci.sh setup",
+      ".gitlab/ci.sh configure",
+      ".gitlab/ci.sh build_hadrian",
+      ".gitlab/ci.sh test_hadrian"
+    ],
+    "stage": "full-build",
+    "tags": [
+      "x86_64-linux"
+    ],
+    "variables": {
+      "BIGNUM_BACKEND": "gmp",
+      "BIN_DIST_NAME": "ghc-i386-linux-alpine3_20-release+no_split_sections",
+      "BROKEN_TESTS": "encoding004 T10458 simd009 T25062_V16 T25169 T22187_run T22033",
+      "BUILD_FLAVOUR": "release+no_split_sections",
+      "CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "HADRIAN_ARGS": "--hash-unit-ids",
+      "IGNORE_PERF_FAILURES": "all",
+      "INSTALL_CONFIGURE_ARGS": "--disable-ld-override --enable-strict-ghc-toolchain-check",
+      "RUNTEST_ARGS": "",
+      "TEST_ENV": "i386-linux-alpine3_20-release+no_split_sections",
+      "XZ_OPT": "-9"
+    }
+  },
   "release-i386-linux-deb10-release+no_split_sections": {
     "after_script": [
       ".gitlab/ci.sh save_cache",


=====================================
compiler/GHC/Driver/DynFlags.hs
=====================================
@@ -729,16 +729,6 @@ newtype FlushOut = FlushOut (IO ())
 defaultFlushOut :: FlushOut
 defaultFlushOut = FlushOut $ hFlush stdout
 
-
-
-data OnOff a = On a
-             | Off a
-  deriving (Eq, Show)
-
-instance Outputable a => Outputable (OnOff a) where
-  ppr (On x)  = text "On" <+> ppr x
-  ppr (Off x) = text "Off" <+> ppr x
-
 -- OnOffs accumulate in reverse order, so we use foldr in order to
 -- process them in the right order
 flattenExtensionFlags :: Maybe Language -> [OnOff LangExt.Extension] -> EnumSet LangExt.Extension


=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -29,6 +29,7 @@ module GHC.Driver.Flags
    , minusWcompatOpts
    , unusedBindsFlags
 
+   , OnOff(..)
    , TurnOnFlag
    , turnOn
    , turnOff
@@ -77,6 +78,14 @@ instance Binary Language where
 instance NFData Language where
   rnf x = x `seq` ()
 
+data OnOff a = On a
+             | Off a
+  deriving (Eq, Show)
+
+instance Outputable a => Outputable (OnOff a) where
+  ppr (On x)  = text "On" <+> ppr x
+  ppr (Off x) = text "Off" <+> ppr x
+
 type TurnOnFlag = Bool   -- True  <=> we are turning the flag on
                          -- False <=> we are turning the flag off
 turnOn  :: TurnOnFlag; turnOn  = True
@@ -269,78 +278,77 @@ extensionNames ext = mk (extensionDeprecation ext)     (extensionName ext : exte
                   ++ mk (ExtensionDeprecatedFor [ext]) (extensionDeprecatedNames ext)
   where mk depr = map (\name -> (depr, name))
 
-
-impliedXFlags :: [(LangExt.Extension, TurnOnFlag, LangExt.Extension)]
+impliedXFlags :: [(LangExt.Extension, OnOff LangExt.Extension)]
 impliedXFlags
 -- See Note [Updating flag description in the User's Guide]
-  = [ (LangExt.RankNTypes,                turnOn, LangExt.ExplicitForAll)
-    , (LangExt.QuantifiedConstraints,     turnOn, LangExt.ExplicitForAll)
-    , (LangExt.ScopedTypeVariables,       turnOn, LangExt.ExplicitForAll)
-    , (LangExt.LiberalTypeSynonyms,       turnOn, LangExt.ExplicitForAll)
-    , (LangExt.ExistentialQuantification, turnOn, LangExt.ExplicitForAll)
-    , (LangExt.FlexibleInstances,         turnOn, LangExt.TypeSynonymInstances)
-    , (LangExt.FunctionalDependencies,    turnOn, LangExt.MultiParamTypeClasses)
-    , (LangExt.MultiParamTypeClasses,     turnOn, LangExt.ConstrainedClassMethods)  -- c.f. #7854
-    , (LangExt.TypeFamilyDependencies,    turnOn, LangExt.TypeFamilies)
+  = [ (LangExt.RankNTypes,                On LangExt.ExplicitForAll)
+    , (LangExt.QuantifiedConstraints,     On LangExt.ExplicitForAll)
+    , (LangExt.ScopedTypeVariables,       On LangExt.ExplicitForAll)
+    , (LangExt.LiberalTypeSynonyms,       On LangExt.ExplicitForAll)
+    , (LangExt.ExistentialQuantification, On LangExt.ExplicitForAll)
+    , (LangExt.FlexibleInstances,         On LangExt.TypeSynonymInstances)
+    , (LangExt.FunctionalDependencies,    On LangExt.MultiParamTypeClasses)
+    , (LangExt.MultiParamTypeClasses,     On LangExt.ConstrainedClassMethods)  -- c.f. #7854
+    , (LangExt.TypeFamilyDependencies,    On LangExt.TypeFamilies)
 
-    , (LangExt.RebindableSyntax, turnOff, LangExt.ImplicitPrelude)      -- NB: turn off!
+    , (LangExt.RebindableSyntax, Off LangExt.ImplicitPrelude)      -- NB: turn off!
 
-    , (LangExt.DerivingVia, turnOn, LangExt.DerivingStrategies)
+    , (LangExt.DerivingVia, On LangExt.DerivingStrategies)
 
-    , (LangExt.GADTs,            turnOn, LangExt.GADTSyntax)
-    , (LangExt.GADTs,            turnOn, LangExt.MonoLocalBinds)
-    , (LangExt.TypeFamilies,     turnOn, LangExt.MonoLocalBinds)
+    , (LangExt.GADTs,            On LangExt.GADTSyntax)
+    , (LangExt.GADTs,            On LangExt.MonoLocalBinds)
+    , (LangExt.TypeFamilies,     On LangExt.MonoLocalBinds)
 
-    , (LangExt.TypeFamilies,     turnOn, LangExt.KindSignatures)  -- Type families use kind signatures
-    , (LangExt.PolyKinds,        turnOn, LangExt.KindSignatures)  -- Ditto polymorphic kinds
+    , (LangExt.TypeFamilies,     On LangExt.KindSignatures)  -- Type families use kind signatures
+    , (LangExt.PolyKinds,        On LangExt.KindSignatures)  -- Ditto polymorphic kinds
 
     -- TypeInType is now just a synonym for a couple of other extensions.
-    , (LangExt.TypeInType,       turnOn, LangExt.DataKinds)
-    , (LangExt.TypeInType,       turnOn, LangExt.PolyKinds)
-    , (LangExt.TypeInType,       turnOn, LangExt.KindSignatures)
+    , (LangExt.TypeInType,       On LangExt.DataKinds)
+    , (LangExt.TypeInType,       On LangExt.PolyKinds)
+    , (LangExt.TypeInType,       On LangExt.KindSignatures)
 
     -- Standalone kind signatures are a replacement for CUSKs.
-    , (LangExt.StandaloneKindSignatures, turnOff, LangExt.CUSKs)
+    , (LangExt.StandaloneKindSignatures, Off LangExt.CUSKs)
 
     -- AutoDeriveTypeable is not very useful without DeriveDataTypeable
-    , (LangExt.AutoDeriveTypeable, turnOn, LangExt.DeriveDataTypeable)
+    , (LangExt.AutoDeriveTypeable, On LangExt.DeriveDataTypeable)
 
     -- We turn this on so that we can export associated type
     -- type synonyms in subordinates (e.g. MyClass(type AssocType))
-    , (LangExt.TypeFamilies,     turnOn, LangExt.ExplicitNamespaces)
-    , (LangExt.TypeOperators, turnOn, LangExt.ExplicitNamespaces)
+    , (LangExt.TypeFamilies,     On LangExt.ExplicitNamespaces)
+    , (LangExt.TypeOperators, On LangExt.ExplicitNamespaces)
 
-    , (LangExt.ImpredicativeTypes,  turnOn, LangExt.RankNTypes)
+    , (LangExt.ImpredicativeTypes,  On LangExt.RankNTypes)
 
         -- Record wild-cards implies field disambiguation
         -- Otherwise if you write (C {..}) you may well get
         -- stuff like " 'a' not in scope ", which is a bit silly
         -- if the compiler has just filled in field 'a' of constructor 'C'
-    , (LangExt.RecordWildCards,     turnOn, LangExt.DisambiguateRecordFields)
+    , (LangExt.RecordWildCards,     On LangExt.DisambiguateRecordFields)
 
-    , (LangExt.ParallelArrays, turnOn, LangExt.ParallelListComp)
+    , (LangExt.ParallelArrays, On LangExt.ParallelListComp)
 
-    , (LangExt.JavaScriptFFI, turnOn, LangExt.InterruptibleFFI)
+    , (LangExt.JavaScriptFFI, On LangExt.InterruptibleFFI)
 
-    , (LangExt.DeriveTraversable, turnOn, LangExt.DeriveFunctor)
-    , (LangExt.DeriveTraversable, turnOn, LangExt.DeriveFoldable)
+    , (LangExt.DeriveTraversable, On LangExt.DeriveFunctor)
+    , (LangExt.DeriveTraversable, On LangExt.DeriveFoldable)
 
     -- Duplicate record fields require field disambiguation
-    , (LangExt.DuplicateRecordFields, turnOn, LangExt.DisambiguateRecordFields)
+    , (LangExt.DuplicateRecordFields, On LangExt.DisambiguateRecordFields)
 
-    , (LangExt.TemplateHaskell, turnOn, LangExt.TemplateHaskellQuotes)
-    , (LangExt.Strict, turnOn, LangExt.StrictData)
+    , (LangExt.TemplateHaskell, On LangExt.TemplateHaskellQuotes)
+    , (LangExt.Strict, On LangExt.StrictData)
 
     -- Historically only UnboxedTuples was required for unboxed sums to work.
     -- To avoid breaking code, we make UnboxedTuples imply UnboxedSums.
-    , (LangExt.UnboxedTuples, turnOn, LangExt.UnboxedSums)
+    , (LangExt.UnboxedTuples, On LangExt.UnboxedSums)
 
     -- The extensions needed to declare an H98 unlifted data type
-    , (LangExt.UnliftedDatatypes, turnOn, LangExt.DataKinds)
-    , (LangExt.UnliftedDatatypes, turnOn, LangExt.StandaloneKindSignatures)
+    , (LangExt.UnliftedDatatypes, On LangExt.DataKinds)
+    , (LangExt.UnliftedDatatypes, On LangExt.StandaloneKindSignatures)
 
     -- See Note [Non-variable pattern bindings aren't linear] in GHC.Tc.Gen.Bind
-    , (LangExt.LinearTypes, turnOn, LangExt.MonoLocalBinds)
+    , (LangExt.LinearTypes, On LangExt.MonoLocalBinds)
   ]
 
 


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -2925,13 +2925,18 @@ unSetExtensionFlag f = upd (unSetExtensionFlag' f)
 setExtensionFlag', unSetExtensionFlag' :: LangExt.Extension -> DynFlags -> DynFlags
 setExtensionFlag' f dflags = foldr ($) (xopt_set dflags f) deps
   where
-    deps = [ if turn_on then setExtensionFlag'   d
-                        else unSetExtensionFlag' d
-           | (f', turn_on, d) <- impliedXFlags, f' == f ]
+    deps :: [DynFlags -> DynFlags]
+    deps = [ setExtension d
+           | (f', d) <- impliedXFlags, f' == f ]
         -- When you set f, set the ones it implies
         -- NB: use setExtensionFlag recursively, in case the implied flags
         --     implies further flags
 
+    setExtension :: OnOff LangExt.Extension -> DynFlags -> DynFlags
+    setExtension = \ case
+      On extension -> setExtensionFlag' extension
+      Off extension -> unSetExtensionFlag' extension
+
 unSetExtensionFlag' f dflags = xopt_unset dflags f
    -- When you un-set f, however, we don't un-set the things it implies
    --      (except for -fno-glasgow-exts, which is treated specially)


=====================================
compiler/GHC/Linker/Loader.hs
=====================================
@@ -17,7 +17,6 @@ module GHC.Linker.Loader
    , showLoaderState
    , getLoaderState
    -- * Load & Unload
-   , loadExpr
    , loadDecls
    , loadPackages
    , loadModule
@@ -589,52 +588,6 @@ preloadLib interp hsc_env lib_paths framework_paths pls lib_spec = do
           , "Try using a dynamic library instead."
           ]
 
-
-{- **********************************************************************
-
-                        Link a byte-code expression
-
-  ********************************************************************* -}
-
--- | Load a single expression, /including/ first loading packages and
--- modules that this expression depends on.
---
--- Raises an IO exception ('ProgramError') if it can't find a compiled
--- version of the dependents to load.
---
-loadExpr :: Interp -> HscEnv -> SrcSpan -> UnlinkedBCO -> IO ForeignHValue
-loadExpr interp hsc_env span root_ul_bco = do
-  -- Initialise the linker (if it's not been done already)
-  initLoaderState interp hsc_env
-
-  -- Take lock for the actual work.
-  modifyLoaderState interp $ \pls0 -> do
-    -- Load the packages and modules required
-    (pls, ok, _, _) <- loadDependencies interp hsc_env pls0 span needed_mods
-    if failed ok
-      then throwGhcExceptionIO (ProgramError "")
-      else do
-        -- Load the expression itself
-        -- Load the necessary packages and linkables
-        let le = linker_env pls
-            bco_ix = mkNameEnv [(unlinkedBCOName root_ul_bco, 0)]
-        resolved <- linkBCO interp (pkgs_loaded pls) le bco_ix root_ul_bco
-        [root_hvref] <- createBCOs interp [resolved]
-        fhv <- mkFinalizedHValue interp root_hvref
-        return (pls, fhv)
-  where
-     free_names = uniqDSetToList (bcoFreeNames root_ul_bco)
-
-     needed_mods :: [Module]
-     needed_mods = [ nameModule n | n <- free_names,
-                     isExternalName n,      -- Names from other modules
-                     not (isWiredInName n)  -- Exclude wired-in names
-                   ]                        -- (see note below)
-        -- Exclude wired-in names because we may not have read
-        -- their interface files, so getLinkDeps will fail
-        -- All wired-in names are in the base package, which we link
-        -- by default, so we can safely ignore them here.
-
 initLinkDepsOpts :: HscEnv -> LinkDepsOpts
 initLinkDepsOpts hsc_env = opts
   where


=====================================
compiler/GHC/Types/Hint/Ppr.hs
=====================================
@@ -403,9 +403,7 @@ pprImpliedExtensions extension = case implied of
     xs -> parens $ "implied by" <+> unquotedListWith "and" xs
   where implied = map (quotes . ppr)
                 . filter (\ext -> extensionDeprecation ext == ExtensionNotDeprecated)
-                . map (\(impl, _, _) -> impl)
-                . filter (\(_, t, orig) -> orig == extension && t == turnOn)
-                $ impliedXFlags
+                $ [impl | (impl, On orig) <- impliedXFlags, orig == extension]
 
 pprPrefixUnqual :: Name -> SDoc
 pprPrefixUnqual name =


=====================================
docs/users_guide/exts/type_abstractions.rst
=====================================
@@ -54,7 +54,7 @@ part of the type argument using type constructors.
 
 For a somewhat-contrived example::
 
-    foo :: (Num a) => Maybe [a] -> String
+    foo :: (Show a, Num a) => Maybe [a] -> String
     foo (Nothing @[t]) = show (0 :: t)
     foo (Just @[t] xs) = show (sum xs :: t)
 


=====================================
hadrian/src/Rules/ToolArgs.hs
=====================================
@@ -99,7 +99,8 @@ multiSetup pkg_s = do
       writeFile' (resp_file root p) (intercalate "\n" (normalise_ghc arg_list
                                                       ++  modules cd
                                                       ++ concatMap rexp (reexportModules cd)
-                                                      ++ ["-outputdir", hidir]))
+                                                      ++ ["-outputdir", hidir,
+                                                          "-this-package-name", pkgName p]))
       return (resp_file root p)
 
 


=====================================
libraries/ghc-internal/src/GHC/Internal/Exception.hs
=====================================
@@ -8,6 +8,7 @@
 {-# LANGUAGE BangPatterns #-}
 {-# LANGUAGE DataKinds #-}
 {-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE ViewPatterns #-}
 {-# OPTIONS_HADDOCK not-home #-}
 
 -----------------------------------------------------------------------------
@@ -52,7 +53,7 @@ module GHC.Internal.Exception
     , ratioZeroDenomException
     , underflowException
       -- ** 'ErrorCall'
-    , ErrorCall(..)
+    , ErrorCall(.., ErrorCallWithLocation)
     , errorCallException
     , errorCallWithCallStackException
     , toExceptionWithBacktrace
@@ -178,7 +179,11 @@ data ErrorCall = ErrorCall String
              , Ord -- ^ @since base-4.7.0.0
              )
 
-{-# COMPLETE ErrorCall #-}
+{-# DEPRECATED ErrorCallWithLocation "ErrorCallWithLocation has been deprecated in favour of ErrorCall (which does not have a location). Backtraces are now handled by the backtrace exception mechanisms exclusively." #-}
+pattern ErrorCallWithLocation :: String -> String -> ErrorCall
+pattern ErrorCallWithLocation err loc <- ErrorCall ((\err -> (err, error "ErrorCallWithLocation has been deprecated in favour of ErrorCall (which does not have a location). Backtraces are now handled by the backtrace exception mechanisms exclusively.")) -> (err, loc))
+  where ErrorCallWithLocation err _ = ErrorCall err
+{-# COMPLETE ErrorCallWithLocation #-}
 
 -- | @since base-4.0.0.0
 instance Exception ErrorCall


=====================================
libraries/ghc-internal/src/GHC/Internal/IO/Handle/FD.hs
=====================================
@@ -368,11 +368,11 @@ fdToHandle' fdint mb_type is_socket filepath iomode binary = do
   mkHandleFromFD fd fd_type filepath iomode is_socket enc
 
 
--- | Turn an existing file descriptor into a Handle.  This is used by
+-- | Turn an existing file descriptor into a 'Handle'.  This is used by
 -- various external libraries to make Handles.
 --
--- Makes a binary Handle.  This is for historical reasons; it should
--- probably be a text Handle with the default encoding and newline
+-- Makes a binary 'Handle'.  This is for historical reasons; it should
+-- probably be a text 'Handle' with the default encoding and newline
 -- translation instead.
 fdToHandle :: Posix.FD -> IO Handle
 fdToHandle fdint = do
@@ -389,8 +389,8 @@ fdToHandle fdint = do
    mkHandleFromFD fd fd_type fd_str iomode False{-non-block-}
                   Nothing -- bin mode
 
--- | Turn an existing Handle into a file descriptor. This function throws an
--- IOError if the Handle does not reference a file descriptor.
+-- | Turn an existing 'Handle' into a file descriptor. This function throws an
+-- 'IOError' if the 'Handle' does not reference a file descriptor.
 --
 -- @since base-4.10.0.0
 handleToFd :: Handle -> IO FD.FD


=====================================
rts/Linker.c
=====================================
@@ -821,6 +821,13 @@ SymbolAddr* lookupDependentSymbol (SymbolName* lbl, ObjectCode *dependent, SymTy
                 NULL);
     }
 
+#if defined(OBJFORMAT_ELF)
+    // Resolve references to the GOT if we know the origin object
+    if (dependent && strncmp(lbl, "_GLOBAL_OFFSET_TABLE_", 21) == 0) {
+        return dependent->info->got_start;
+    }
+#endif
+
     if (!ghciLookupSymbolInfo(symhash, lbl, &pinfo)) {
         IF_DEBUG(linker_verbose, debugBelch("lookupSymbol: symbol '%s' not found, trying dlsym\n", lbl));
 


=====================================
testsuite/driver/testlib.py
=====================================
@@ -1627,6 +1627,11 @@ async def test_common_work(name: TestName, opts,
             do_ways = []
             config.hadrian_deps |= getTestOpts().hadrian_deps
 
+        # Skip tests which require hadrian dependencies if we are testing
+        # an out-of-tree compiler as Hadrian is unavailable. See #13897.
+        if not config.in_tree_compiler and getTestOpts().hadrian_deps - {'test:ghc'}:
+            do_ways = []
+
         # Run the required tests...
         for way in do_ways:
             if stopping():


=====================================
testsuite/tests/ghc-api/exactprint/all.T
=====================================
@@ -1,3 +1,5 @@
+setTestOpts(req_hadrian_deps(['test:check-exact']))
+
 test('RenameCase1',   ignore_stderr, makefile_test, ['RenameCase1'])
 test('LayoutLet2',    ignore_stderr, makefile_test, ['LayoutLet2'])
 test('LayoutLet3',    ignore_stderr, makefile_test, ['LayoutLet3'])


=====================================
testsuite/tests/ghci/should_run/GHCiPrimCall/Makefile
=====================================
@@ -1,3 +1,7 @@
+TOP=../../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
+
 .PHONY: GHCiPrimCall
 GHCiPrimCall:
 	'$(TEST_HC)' $(TEST_HC_OPTS) -fPIC -v0 -c GHCiPrimCall_cmm.cmm


=====================================
testsuite/tests/interface-stability/base-exports.stdout
=====================================
@@ -232,6 +232,7 @@ module Control.Exception where
   data Deadlock = Deadlock
   type ErrorCall :: *
   data ErrorCall = ErrorCall GHC.Internal.Base.String
+  pattern ErrorCallWithLocation :: GHC.Internal.Base.String -> GHC.Internal.Base.String -> ErrorCall
   type Exception :: * -> Constraint
   class (ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
     toException :: e -> SomeException
@@ -349,6 +350,7 @@ module Control.Exception.Base where
   data Deadlock = Deadlock
   type ErrorCall :: *
   data ErrorCall = ErrorCall GHC.Internal.Base.String
+  pattern ErrorCallWithLocation :: GHC.Internal.Base.String -> GHC.Internal.Base.String -> ErrorCall
   type Exception :: * -> Constraint
   class (ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
     toException :: e -> SomeException
@@ -5305,6 +5307,7 @@ module GHC.Exception where
   data CallStack = ...
   type ErrorCall :: *
   data ErrorCall = ErrorCall GHC.Internal.Base.String
+  pattern ErrorCallWithLocation :: GHC.Internal.Base.String -> GHC.Internal.Base.String -> ErrorCall
   type Exception :: * -> Constraint
   class (ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
     toException :: e -> SomeException


=====================================
testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
=====================================
@@ -232,6 +232,7 @@ module Control.Exception where
   data Deadlock = Deadlock
   type ErrorCall :: *
   data ErrorCall = ErrorCall GHC.Internal.Base.String
+  pattern ErrorCallWithLocation :: GHC.Internal.Base.String -> GHC.Internal.Base.String -> ErrorCall
   type Exception :: * -> Constraint
   class (ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
     toException :: e -> SomeException
@@ -349,6 +350,7 @@ module Control.Exception.Base where
   data Deadlock = Deadlock
   type ErrorCall :: *
   data ErrorCall = ErrorCall GHC.Internal.Base.String
+  pattern ErrorCallWithLocation :: GHC.Internal.Base.String -> GHC.Internal.Base.String -> ErrorCall
   type Exception :: * -> Constraint
   class (ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
     toException :: e -> SomeException
@@ -5274,6 +5276,7 @@ module GHC.Exception where
   data CallStack = ...
   type ErrorCall :: *
   data ErrorCall = ErrorCall GHC.Internal.Base.String
+  pattern ErrorCallWithLocation :: GHC.Internal.Base.String -> GHC.Internal.Base.String -> ErrorCall
   type Exception :: * -> Constraint
   class (ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
     toException :: e -> SomeException


=====================================
testsuite/tests/interface-stability/base-exports.stdout-mingw32
=====================================
@@ -232,6 +232,7 @@ module Control.Exception where
   data Deadlock = Deadlock
   type ErrorCall :: *
   data ErrorCall = ErrorCall GHC.Internal.Base.String
+  pattern ErrorCallWithLocation :: GHC.Internal.Base.String -> GHC.Internal.Base.String -> ErrorCall
   type Exception :: * -> Constraint
   class (ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
     toException :: e -> SomeException
@@ -349,6 +350,7 @@ module Control.Exception.Base where
   data Deadlock = Deadlock
   type ErrorCall :: *
   data ErrorCall = ErrorCall GHC.Internal.Base.String
+  pattern ErrorCallWithLocation :: GHC.Internal.Base.String -> GHC.Internal.Base.String -> ErrorCall
   type Exception :: * -> Constraint
   class (ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
     toException :: e -> SomeException
@@ -5451,6 +5453,7 @@ module GHC.Exception where
   data CallStack = ...
   type ErrorCall :: *
   data ErrorCall = ErrorCall GHC.Internal.Base.String
+  pattern ErrorCallWithLocation :: GHC.Internal.Base.String -> GHC.Internal.Base.String -> ErrorCall
   type Exception :: * -> Constraint
   class (ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
     toException :: e -> SomeException


=====================================
testsuite/tests/interface-stability/base-exports.stdout-ws-32
=====================================
@@ -232,6 +232,7 @@ module Control.Exception where
   data Deadlock = Deadlock
   type ErrorCall :: *
   data ErrorCall = ErrorCall GHC.Internal.Base.String
+  pattern ErrorCallWithLocation :: GHC.Internal.Base.String -> GHC.Internal.Base.String -> ErrorCall
   type Exception :: * -> Constraint
   class (ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
     toException :: e -> SomeException
@@ -349,6 +350,7 @@ module Control.Exception.Base where
   data Deadlock = Deadlock
   type ErrorCall :: *
   data ErrorCall = ErrorCall GHC.Internal.Base.String
+  pattern ErrorCallWithLocation :: GHC.Internal.Base.String -> GHC.Internal.Base.String -> ErrorCall
   type Exception :: * -> Constraint
   class (ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
     toException :: e -> SomeException
@@ -5305,6 +5307,7 @@ module GHC.Exception where
   data CallStack = ...
   type ErrorCall :: *
   data ErrorCall = ErrorCall GHC.Internal.Base.String
+  pattern ErrorCallWithLocation :: GHC.Internal.Base.String -> GHC.Internal.Base.String -> ErrorCall
   type Exception :: * -> Constraint
   class (ghc-internal-9.1100.0:GHC.Internal.Data.Typeable.Internal.Typeable e, GHC.Internal.Show.Show e) => Exception e where
     toException :: e -> SomeException


=====================================
testsuite/tests/rts/ipe/IpeStats/Makefile
=====================================
@@ -22,16 +22,16 @@ SKIPPED_SELECTOR := 'Tables skipped: [0-9]+'
 # statistics.
 
 ipe_stats:
-	@NoOmit="$$($$TEST_HC $$TEST_HC_OPTS -fforce-recomp -finfo-table-map -dipe-stats Fold.hs)" ; \
+	@NoOmit="$$('$(TEST_HC)' $(TEST_HC_OPTS) -fforce-recomp -finfo-table-map -dipe-stats Fold.hs)" ; \
 	Stack=$$(echo $$NoOmit | grep -Eo $(STACK_SELECTOR) | grep -Eo '[0-9]+$$') ; \
 	Fallback=$$(echo $$NoOmit | grep -Eo $(FALLBACK_SELECTOR) | grep -Eo '[0-9]+$$') ; \
 	Skipped=$$(echo $$NoOmit | grep -Eo $(SKIPPED_SELECTOR) | grep -Eo '[0-9]+$$') ; \
 	Both=$$(expr $$Stack + $$Fallback) ; \
-	OmitStack="$$($$TEST_HC $$TEST_HC_OPTS -fforce-recomp -finfo-table-map -fno-info-table-map-with-stack -dipe-stats Fold.hs)" ; \
+	OmitStack="$$('$(TEST_HC)' $(TEST_HC_OPTS) -fforce-recomp -finfo-table-map -fno-info-table-map-with-stack -dipe-stats Fold.hs)" ; \
 	SkippedStack=$$(echo $$OmitStack | grep -Eo $(SKIPPED_SELECTOR) | grep -Eo '[0-9]+$$') ; \
-	OmitFallback="$$($$TEST_HC $$TEST_HC_OPTS -fforce-recomp -finfo-table-map -fno-info-table-map-with-fallback -dipe-stats Fold.hs)" ; \
+	OmitFallback="$$('$(TEST_HC)' $(TEST_HC_OPTS) -fforce-recomp -finfo-table-map -fno-info-table-map-with-fallback -dipe-stats Fold.hs)" ; \
 	SkippedFallback=$$(echo $$OmitFallback| grep -Eo $(SKIPPED_SELECTOR) | grep -Eo '[0-9]+$$') ; \
-	OmitBoth="$$($$TEST_HC $$TEST_HC_OPTS -fforce-recomp -finfo-table-map -fno-info-table-map-with-stack -fno-info-table-map-with-fallback -dipe-stats Fold.hs)" ; \
+	OmitBoth="$$('$(TEST_HC)' $(TEST_HC_OPTS) -fforce-recomp -finfo-table-map -fno-info-table-map-with-stack -fno-info-table-map-with-fallback -dipe-stats Fold.hs)" ; \
 	SkippedBoth=$$(echo $$OmitBoth| grep -Eo $(SKIPPED_SELECTOR) | grep -Eo '[0-9]+$$') ; \
 	echo "Baseline number of skipped tables: $$Skipped\n" ; \
 	echo "Baseline number of stack tables:                                  $$Stack" ; \



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3a4d58e25cb1fd0c33f6c7dab7235b7a715a9492...5002fa3d7de76eef72a34414a21949d93e9cfe63

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3a4d58e25cb1fd0c33f6c7dab7235b7a715a9492...5002fa3d7de76eef72a34414a21949d93e9cfe63
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/20241124/7e6f38c1/attachment-0001.html>


More information about the ghc-commits mailing list