[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 8 commits: gitlab-ci: Don't use coreutils on Darwin

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Tue Aug 9 14:37:04 UTC 2022



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


Commits:
c1c08bd8 by Ben Gamari at 2022-08-09T02:31:14-04:00
gitlab-ci: Don't use coreutils on Darwin

In general we want to ensure that the tested environment is as similar
as possible to the environment the user will use. In the case of Darwin,
this means we want to use the system's BSD command-line utilities, not
coreutils.

This would have caught #21974.

- - - - -
1c582f44 by Ben Gamari at 2022-08-09T02:31:14-04:00
hadrian: Fix bindist installation on Darwin

It turns out that `cp -P` on Darwin does not always copy a symlink as
a symlink. In order to get these semantics one must pass `-RP`. It's not
entirely clear whether this is valid under POSIX, but it is nevertheless
what Apple does.

- - - - -
681aa076 by Ben Gamari at 2022-08-09T02:31:49-04:00
hadrian: Fix access mode of installed package registration files

Previously hadrian's bindist Makefile would modify package
registrations placed by `install` via a shell pipeline and `mv`.
However, the use of `mv` means that if umask is set then the user may
otherwise end up with package registrations which are inaccessible.
Fix this by ensuring that the mode is 0644.

- - - - -
e9dfd26a by Krzysztof Gogolewski at 2022-08-09T02:32:24-04:00
Cleanups around pretty-printing

* Remove hack when printing OccNames. No longer needed since e3dcc0d5
* Remove unused `pprCmms` and `instance Outputable Instr`
* Simplify `pprCLabel` (no need to pass platform)
* Remove evil `Show`/`Eq` instances for `SDoc`. They were needed by
  ImmLit, but that can take just a String instead.
* Remove instance `Outputable CLabel` - proper output of labels
  needs a platform, and is done by the `OutputableP` instance

- - - - -
5f651d52 by Ben Gamari at 2022-08-09T10:36:33-04:00
rts/linker: Resolve iconv_* on FreeBSD

FreeBSD's libiconv includes an implementation of the
iconv_* functions in libc. Unfortunately these can
only be resolved using dlvsym, which is how the RTS linker
usually resolves such functions. To fix this we include an ad-hoc
special case for iconv_*.

Fixes #20354.

- - - - -
f97a2861 by Ben Gamari at 2022-08-09T10:36:33-04:00
system-cxx-std-lib: Add support for FreeBSD libcxxrt

- - - - -
b1b4638f by Ben Gamari at 2022-08-09T10:36:33-04:00
gitlab-ci: Bump to use freebsd13 runners

- - - - -
6156ec32 by sheaf at 2022-08-09T10:36:41-04:00
Fix size_up_alloc to account for UnliftedDatatypes

The size_up_alloc function mistakenly considered any type that isn't
lifted to not allocate anything, which is wrong. What we want instead
is to check the type isn't boxed. This accounts for (BoxedRep Unlifted).

Fixes #21939

- - - - -


24 changed files:

- .gitlab/ci.sh
- .gitlab/darwin/toolchain.nix
- .gitlab/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/Cmm.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/CmmToAsm/AArch64/Regs.hs
- compiler/GHC/CmmToAsm/PPC/CodeGen.hs
- compiler/GHC/CmmToAsm/PPC/Ppr.hs
- compiler/GHC/CmmToAsm/PPC/Regs.hs
- compiler/GHC/CmmToAsm/X86/Ppr.hs
- compiler/GHC/CmmToAsm/X86/Regs.hs
- compiler/GHC/Core/Unfold.hs
- compiler/GHC/StgToCmm/Ticky.hs
- compiler/GHC/Types/Name/Occurrence.hs
- compiler/GHC/Unit/Types.hs
- hadrian/bindist/Makefile
- hadrian/bindist/config.mk.in
- hadrian/src/Rules/BinaryDist.hs
- m4/fp_find_cxx_std_lib.m4
- + mk/install_script.sh
- rts/Linker.c
- testsuite/tests/linters/notes.stdout


Changes:

=====================================
.gitlab/ci.sh
=====================================
@@ -207,6 +207,9 @@ function set_toolchain_paths() {
       CABAL="$toolchain/bin/cabal$exe"
       HAPPY="$toolchain/bin/happy$exe"
       ALEX="$toolchain/bin/alex$exe"
+      if [ "$(uname)" = "FreeBSD" ]; then
+        GHC=/usr/local/bin/ghc
+      fi
       ;;
     nix)
       if [[ ! -f toolchain.sh ]]; then
@@ -288,7 +291,7 @@ function fetch_ghc() {
           cp -r ghc-${GHC_VERSION}*/* "$toolchain"
           ;;
         *)
-          pushd "ghc-${GHC_VERSION}*"
+          pushd ghc-${GHC_VERSION}*
           ./configure --prefix="$toolchain"
           "$MAKE" install
           popd
@@ -326,9 +329,7 @@ function fetch_cabal() {
           local base_url="https://downloads.haskell.org/~cabal/cabal-install-$v/"
           case "$(uname)" in
             Darwin) cabal_url="$base_url/cabal-install-$v-x86_64-apple-darwin17.7.0.tar.xz" ;;
-            FreeBSD)
-              #cabal_url="$base_url/cabal-install-$v-x86_64-portbld-freebsd.tar.xz" ;;
-              cabal_url="http://home.smart-cactus.org/~ben/ghc/cabal-install-3.0.0.0-x86_64-portbld-freebsd.tar.xz" ;;
+            FreeBSD) cabal_url="$base_url/cabal-install-$v-x86_64-freebsd13.tar.xz" ;;
             *) fail "don't know where to fetch cabal-install for $(uname)"
           esac
           echo "Fetching cabal-install from $cabal_url"


=====================================
.gitlab/darwin/toolchain.nix
=====================================
@@ -85,7 +85,6 @@ pkgs.writeTextFile {
     export PATH
     PATH="${pkgs.autoconf}/bin:$PATH"
     PATH="${pkgs.automake}/bin:$PATH"
-    PATH="${pkgs.coreutils}/bin:$PATH"
     export FONTCONFIG_FILE=${fonts}
     export XELATEX="${ourtexlive}/bin/xelatex"
     export MAKEINDEX="${ourtexlive}/bin/makeindex"


=====================================
.gitlab/gen_ci.hs
=====================================
@@ -92,7 +92,7 @@ names of jobs to update these other places.
 data Opsys
   = Linux LinuxDistro
   | Darwin
-  | FreeBSD
+  | FreeBSD13
   | Windows deriving (Eq)
 
 data LinuxDistro
@@ -223,7 +223,7 @@ runnerTag arch (Linux distro) =
 runnerTag AArch64 Darwin = "aarch64-darwin"
 runnerTag Amd64 Darwin = "x86_64-darwin-m1"
 runnerTag Amd64 Windows = "new-x86_64-windows"
-runnerTag Amd64 FreeBSD = "x86_64-freebsd"
+runnerTag Amd64 FreeBSD13 = "x86_64-freebsd13"
 
 tags :: Arch -> Opsys -> BuildConfig -> [String]
 tags arch opsys _bc = [runnerTag arch opsys] -- Tag for which runners we can use
@@ -242,7 +242,7 @@ distroName Alpine     = "alpine3_12"
 opsysName :: Opsys -> String
 opsysName (Linux distro) = "linux-" ++ distroName distro
 opsysName Darwin = "darwin"
-opsysName FreeBSD = "freebsd"
+opsysName FreeBSD13 = "freebsd13"
 opsysName Windows = "windows"
 
 archName :: Arch -> String
@@ -313,7 +313,7 @@ type Variables = M.MonoidalMap String [String]
 a =: b = M.singleton a [b]
 
 opsysVariables :: Arch -> Opsys -> Variables
-opsysVariables _ FreeBSD = mconcat
+opsysVariables _ FreeBSD13 = mconcat
   [ -- N.B. we use iconv from ports as I see linker errors when we attempt
     -- to use the "native" iconv embedded in libc as suggested by the
     -- porting guide [1].
@@ -321,7 +321,7 @@ opsysVariables _ FreeBSD = mconcat
     "CONFIGURE_ARGS" =:  "--with-gmp-includes=/usr/local/include --with-gmp-libraries=/usr/local/lib --with-iconv-includes=/usr/local/include --with-iconv-libraries=/usr/local/lib"
   , "HADRIAN_ARGS" =: "--docs=no-sphinx"
   , "GHC_VERSION" =: "9.2.2"
-  , "CABAL_INSTALL_VERSION" =: "3.2.0.0"
+  , "CABAL_INSTALL_VERSION" =: "3.6.2.0"
   ]
 opsysVariables ARMv7 (Linux distro) =
   distroVariables distro <>
@@ -489,12 +489,12 @@ instance ToJSON OnOffRules where
 
 -- | A Rule corresponds to some condition which must be satisifed in order to
 -- run the job.
-data Rule = FastCI -- ^ Run this job when the fast-ci label is set
-          | ReleaseOnly -- ^ Only run this job in a release pipeline
-          | Nightly     -- ^ Only run this job in the nightly pipeline
-          | LLVMBackend -- ^ Only run this job when the "LLVM backend" label is present
-          | FreeBSDTag  -- ^ Only run this job when the "FreeBSD" label is set.
-          | Disable     -- ^ Don't run this job.
+data Rule = FastCI       -- ^ Run this job when the fast-ci label is set
+          | ReleaseOnly  -- ^ Only run this job in a release pipeline
+          | Nightly      -- ^ Only run this job in the nightly pipeline
+          | LLVMBackend  -- ^ Only run this job when the "LLVM backend" label is present
+          | FreeBSDLabel -- ^ Only run this job when the "FreeBSD" label is set.
+          | Disable      -- ^ Don't run this job.
           deriving (Bounded, Enum, Ord, Eq)
 
 -- A constant evaluating to True because gitlab doesn't support "true" in the
@@ -512,8 +512,8 @@ ruleString On FastCI = true
 ruleString Off FastCI = "$CI_MERGE_REQUEST_LABELS !~ /.*fast-ci.*/"
 ruleString On LLVMBackend = "$CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/"
 ruleString Off LLVMBackend = true
-ruleString On FreeBSDTag = "$CI_MERGE_REQUEST_LABELS =~ /.*FreeBSD.*/"
-ruleString Off FreeBSDTag = true
+ruleString On FreeBSDLabel = "$CI_MERGE_REQUEST_LABELS =~ /.*FreeBSD.*/"
+ruleString Off FreeBSDLabel = true
 ruleString On ReleaseOnly = "$RELEASE_JOB == \"yes\""
 ruleString Off ReleaseOnly = "$RELEASE_JOB != \"yes\""
 ruleString On Nightly = "$NIGHTLY"
@@ -781,7 +781,7 @@ jobs = M.fromList $ concatMap flattenJobGroup $
      , fastCI (standardBuilds Amd64 Windows)
      , disableValidate (standardBuildsWithConfig Amd64 Windows nativeInt)
      , standardBuilds Amd64 Darwin
-     , allowFailureGroup (addValidateRule FreeBSDTag (standardBuilds Amd64 FreeBSD))
+     , allowFailureGroup (addValidateRule FreeBSDLabel (standardBuilds Amd64 FreeBSD13))
      , standardBuilds AArch64 Darwin
      , standardBuilds AArch64 (Linux Debian10)
      , disableValidate (standardBuilds AArch64 (Linux Debian11))


=====================================
.gitlab/jobs.yaml
=====================================
@@ -658,7 +658,7 @@
       "ac_cv_func_utimensat": "no"
     }
   },
-  "nightly-x86_64-freebsd-validate": {
+  "nightly-x86_64-freebsd13-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh clean",
@@ -668,7 +668,7 @@
     "artifacts": {
       "expire_in": "8 weeks",
       "paths": [
-        "ghc-x86_64-freebsd-validate.tar.xz",
+        "ghc-x86_64-freebsd13-validate.tar.xz",
         "junit.xml"
       ],
       "reports": {
@@ -677,7 +677,7 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-freebsd-$CACHE_REV",
+      "key": "x86_64-freebsd13-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
@@ -705,17 +705,17 @@
     ],
     "stage": "full-build",
     "tags": [
-      "x86_64-freebsd"
+      "x86_64-freebsd13"
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-freebsd-validate",
+      "BIN_DIST_NAME": "ghc-x86_64-freebsd13-validate",
       "BUILD_FLAVOUR": "validate",
-      "CABAL_INSTALL_VERSION": "3.2.0.0",
+      "CABAL_INSTALL_VERSION": "3.6.2.0",
       "CONFIGURE_ARGS": "--with-gmp-includes=/usr/local/include --with-gmp-libraries=/usr/local/lib --with-iconv-includes=/usr/local/include --with-iconv-libraries=/usr/local/lib ",
       "GHC_VERSION": "9.2.2",
       "HADRIAN_ARGS": "--docs=no-sphinx",
-      "TEST_ENV": "x86_64-freebsd-validate",
+      "TEST_ENV": "x86_64-freebsd13-validate",
       "XZ_OPT": "-9"
     }
   },
@@ -2288,7 +2288,7 @@
       "ac_cv_func_utimensat": "no"
     }
   },
-  "release-x86_64-freebsd-release": {
+  "release-x86_64-freebsd13-release": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh clean",
@@ -2298,7 +2298,7 @@
     "artifacts": {
       "expire_in": "1 year",
       "paths": [
-        "ghc-x86_64-freebsd-release.tar.xz",
+        "ghc-x86_64-freebsd13-release.tar.xz",
         "junit.xml"
       ],
       "reports": {
@@ -2307,7 +2307,7 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-freebsd-$CACHE_REV",
+      "key": "x86_64-freebsd13-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
@@ -2335,18 +2335,18 @@
     ],
     "stage": "full-build",
     "tags": [
-      "x86_64-freebsd"
+      "x86_64-freebsd13"
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-freebsd-release",
+      "BIN_DIST_NAME": "ghc-x86_64-freebsd13-release",
       "BUILD_FLAVOUR": "release",
-      "CABAL_INSTALL_VERSION": "3.2.0.0",
+      "CABAL_INSTALL_VERSION": "3.6.2.0",
       "CONFIGURE_ARGS": "--with-gmp-includes=/usr/local/include --with-gmp-libraries=/usr/local/lib --with-iconv-includes=/usr/local/include --with-iconv-libraries=/usr/local/lib ",
       "GHC_VERSION": "9.2.2",
       "HADRIAN_ARGS": "--docs=no-sphinx",
       "IGNORE_PERF_FAILURES": "all",
-      "TEST_ENV": "x86_64-freebsd-release",
+      "TEST_ENV": "x86_64-freebsd13-release",
       "XZ_OPT": "-9"
     }
   },
@@ -3208,7 +3208,7 @@
       "ac_cv_func_utimensat": "no"
     }
   },
-  "x86_64-freebsd-validate": {
+  "x86_64-freebsd13-validate": {
     "after_script": [
       ".gitlab/ci.sh save_cache",
       ".gitlab/ci.sh clean",
@@ -3218,7 +3218,7 @@
     "artifacts": {
       "expire_in": "2 weeks",
       "paths": [
-        "ghc-x86_64-freebsd-validate.tar.xz",
+        "ghc-x86_64-freebsd13-validate.tar.xz",
         "junit.xml"
       ],
       "reports": {
@@ -3227,7 +3227,7 @@
       "when": "always"
     },
     "cache": {
-      "key": "x86_64-freebsd-$CACHE_REV",
+      "key": "x86_64-freebsd13-$CACHE_REV",
       "paths": [
         "cabal-cache",
         "toolchain"
@@ -3255,17 +3255,17 @@
     ],
     "stage": "full-build",
     "tags": [
-      "x86_64-freebsd"
+      "x86_64-freebsd13"
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-freebsd-validate",
+      "BIN_DIST_NAME": "ghc-x86_64-freebsd13-validate",
       "BUILD_FLAVOUR": "validate",
-      "CABAL_INSTALL_VERSION": "3.2.0.0",
+      "CABAL_INSTALL_VERSION": "3.6.2.0",
       "CONFIGURE_ARGS": "--with-gmp-includes=/usr/local/include --with-gmp-libraries=/usr/local/lib --with-iconv-includes=/usr/local/include --with-iconv-libraries=/usr/local/lib ",
       "GHC_VERSION": "9.2.2",
       "HADRIAN_ARGS": "--docs=no-sphinx",
-      "TEST_ENV": "x86_64-freebsd-validate"
+      "TEST_ENV": "x86_64-freebsd13-validate"
     }
   },
   "x86_64-linux-alpine3_12-int_native-validate+fully_static": {


=====================================
compiler/GHC/Cmm.hs
=====================================
@@ -33,7 +33,7 @@ module GHC.Cmm (
      module GHC.Cmm.Expr,
 
      -- * Pretty-printing
-     pprCmms, pprCmmGroup, pprSection, pprStatic
+     pprCmmGroup, pprSection, pprStatic
   ) where
 
 import GHC.Prelude
@@ -379,12 +379,6 @@ pprBBlock (BasicBlock ident stmts) =
 --
 -- These conventions produce much more readable Cmm output.
 
-pprCmms :: (OutputableP Platform info, OutputableP Platform g)
-        => Platform -> [GenCmmGroup RawCmmStatics info g] -> SDoc
-pprCmms platform cmms = pprCode CStyle (vcat (intersperse separator $ map (pdoc platform) cmms))
-        where
-          separator = space $$ text "-------------------" $$ space
-
 pprCmmGroup :: (OutputableP Platform d, OutputableP Platform info, OutputableP Platform g)
             => Platform -> GenCmmGroup d info g -> SDoc
 pprCmmGroup platform tops


=====================================
compiler/GHC/Cmm/CLabel.hs
=====================================
@@ -294,9 +294,6 @@ data CLabel
 instance Show CLabel where
   show = showPprUnsafe . pprDebugCLabel genericPlatform
 
-instance Outputable CLabel where
-  ppr = text . show
-
 data ModuleLabelKind
     = MLK_Initializer String
     | MLK_InitializerArray
@@ -1412,19 +1409,19 @@ pprCLabel !platform !sty lbl = -- see Note [Bangs in CLabel]
       AsmStyle | use_leading_underscores -> pp_cSEP <> doc
       _                                  -> doc
 
-    tempLabelPrefixOrUnderscore :: Platform -> SDoc
-    tempLabelPrefixOrUnderscore platform = case sty of
+    tempLabelPrefixOrUnderscore :: SDoc
+    tempLabelPrefixOrUnderscore = case sty of
       AsmStyle -> asmTempLabelPrefix platform
       CStyle   -> char '_'
 
 
   in case lbl of
    LocalBlockLabel u -> case sty of
-      AsmStyle -> tempLabelPrefixOrUnderscore platform <> pprUniqueAlways u
-      CStyle   -> tempLabelPrefixOrUnderscore platform <> text "blk_" <> pprUniqueAlways u
+      AsmStyle -> tempLabelPrefixOrUnderscore <> pprUniqueAlways u
+      CStyle   -> tempLabelPrefixOrUnderscore <> text "blk_" <> pprUniqueAlways u
 
    AsmTempLabel u
-      -> tempLabelPrefixOrUnderscore platform <> pprUniqueAlways u
+      -> tempLabelPrefixOrUnderscore <> pprUniqueAlways u
 
    AsmTempDerivedLabel l suf
       -> asmTempLabelPrefix platform
@@ -1474,7 +1471,7 @@ pprCLabel !platform !sty lbl = -- see Note [Bangs in CLabel]
       CStyle   -> ppr name <> ppIdFlavor flavor
 
    SRTLabel u
-      -> maybe_underscore $ tempLabelPrefixOrUnderscore platform <> pprUniqueAlways u <> pp_cSEP <> text "srt"
+      -> maybe_underscore $ tempLabelPrefixOrUnderscore <> pprUniqueAlways u <> pp_cSEP <> text "srt"
 
    RtsLabel (RtsApFast (NonDetFastString str))
       -> maybe_underscore $ ftext str <> text "_fast"
@@ -1514,7 +1511,7 @@ pprCLabel !platform !sty lbl = -- see Note [Bangs in CLabel]
       -> maybe_underscore $ text "SLOW_CALL_fast_" <> text pat <> text "_ctr"
 
    LargeBitmapLabel u
-      -> maybe_underscore $ tempLabelPrefixOrUnderscore platform
+      -> maybe_underscore $ tempLabelPrefixOrUnderscore
                             <> char 'b' <> pprUniqueAlways u <> pp_cSEP <> text "btm"
                             -- Some bitmaps for tuple constructors have a numeric tag (e.g. '7')
                             -- until that gets resolved we'll just force them to start


=====================================
compiler/GHC/CmmToAsm/AArch64/Ppr.hs
=====================================
@@ -50,14 +50,14 @@ pprNatCmmDecl config proc@(CmmProc top_info lbl _ (ListGraph blocks)) =
         pprLabel platform lbl $$ -- blocks guaranteed not null, so label needed
         vcat (map (pprBasicBlock config top_info) blocks) $$
         (if ncgDwarfEnabled config
-         then ppr (mkAsmTempEndLabel lbl) <> char ':' else empty) $$
+         then pdoc platform (mkAsmTempEndLabel lbl) <> char ':' else empty) $$
         pprSizeDecl platform lbl
 
     Just (CmmStaticsRaw info_lbl _) ->
       pprSectionAlign config (Section Text info_lbl) $$
       -- pprProcAlignment config $$
       (if platformHasSubsectionsViaSymbols platform
-          then ppr (mkDeadStripPreventer info_lbl) <> char ':'
+          then pdoc platform (mkDeadStripPreventer info_lbl) <> char ':'
           else empty) $$
       vcat (map (pprBasicBlock config top_info) blocks) $$
       -- above: Even the first block gets a label, because with branch-chain
@@ -65,9 +65,9 @@ pprNatCmmDecl config proc@(CmmProc top_info lbl _ (ListGraph blocks)) =
       (if platformHasSubsectionsViaSymbols platform
        then -- See Note [Subsections Via Symbols]
                 text "\t.long "
-            <+> ppr info_lbl
+            <+> pdoc platform info_lbl
             <+> char '-'
-            <+> ppr (mkDeadStripPreventer info_lbl)
+            <+> pdoc platform (mkDeadStripPreventer info_lbl)
        else empty) $$
       pprSizeDecl platform info_lbl
 
@@ -87,9 +87,6 @@ pprAlignForSection _platform _seg
     -- .balign is stable, whereas .align is platform dependent.
     = text "\t.balign 8" --  always 8
 
-instance Outputable Instr where
-    ppr = pprInstr genericPlatform
-
 -- | Print section header and appropriate alignment for that section.
 --
 -- This one will emit the header:
@@ -118,7 +115,7 @@ pprBasicBlock config info_env (BasicBlock blockid instrs)
     pprLabel platform asmLbl $$
     vcat (map (pprInstr platform) (id {-detectTrivialDeadlock-} optInstrs)) $$
     (if  ncgDwarfEnabled config
-      then ppr (mkAsmTempEndLabel asmLbl) <> char ':'
+      then pdoc platform (mkAsmTempEndLabel asmLbl) <> char ':'
       else empty
     )
   where
@@ -138,7 +135,7 @@ pprBasicBlock config info_env (BasicBlock blockid instrs)
            pprLabel platform info_lbl $$
            c $$
            (if ncgDwarfEnabled config
-             then ppr (mkAsmTempEndLabel info_lbl) <> char ':'
+             then pdoc platform (mkAsmTempEndLabel info_lbl) <> char ':'
              else empty)
     -- Make sure the info table has the right .loc for the block
     -- coming right after it. See Note [Info Offset]
@@ -235,7 +232,7 @@ pprImm _ (ImmInt i)     = int i
 pprImm _ (ImmInteger i) = integer i
 pprImm p (ImmCLbl l)    = pdoc p l
 pprImm p (ImmIndex l i) = pdoc p l <> char '+' <> int i
-pprImm _ (ImmLit s)     = s
+pprImm _ (ImmLit s)     = text s
 
 -- TODO: See pprIm below for why this is a bad idea!
 pprImm _ (ImmFloat f)


=====================================
compiler/GHC/CmmToAsm/AArch64/Regs.hs
=====================================
@@ -59,7 +59,7 @@ data Imm
   = ImmInt      Int
   | ImmInteger  Integer     -- Sigh.
   | ImmCLbl     CLabel      -- AbstractC Label (with baggage)
-  | ImmLit      SDoc        -- Simple string
+  | ImmLit      String
   | ImmIndex    CLabel Int
   | ImmFloat    Rational
   | ImmDouble   Rational
@@ -67,14 +67,8 @@ data Imm
   | ImmConstantDiff Imm Imm
   deriving (Eq, Show)
 
-instance Show SDoc where
-  show = showPprUnsafe . ppr
-
-instance Eq SDoc where
-  lhs == rhs = show lhs == show rhs
-
 strImmLit :: String -> Imm
-strImmLit s = ImmLit (text s)
+strImmLit s = ImmLit s
 
 
 litToImm :: CmmLit -> Imm


=====================================
compiler/GHC/CmmToAsm/PPC/CodeGen.hs
=====================================
@@ -407,7 +407,7 @@ getRegister' :: NCGConfig -> Platform -> CmmExpr -> NatM Register
 getRegister' _ platform (CmmReg (CmmGlobal PicBaseReg))
   | OSAIX <- platformOS platform = do
         let code dst = toOL [ LD II32 dst tocAddr ]
-            tocAddr = AddrRegImm toc (ImmLit (text "ghc_toc_table[TC]"))
+            tocAddr = AddrRegImm toc (ImmLit "ghc_toc_table[TC]")
         return (Any II32 code)
   | target32Bit platform = do
       reg <- getPicBaseNat $ archWordFormat (target32Bit platform)


=====================================
compiler/GHC/CmmToAsm/PPC/Ppr.hs
=====================================
@@ -240,7 +240,7 @@ pprImm platform = \case
    ImmInteger i   -> integer i
    ImmCLbl l      -> pdoc platform l
    ImmIndex l i   -> pdoc platform l <> char '+' <> int i
-   ImmLit s       -> s
+   ImmLit s       -> text s
    ImmFloat f     -> float $ fromRational f
    ImmDouble d    -> double $ fromRational d
    ImmConstantSum a b   -> pprImm platform a <> char '+' <> pprImm platform b


=====================================
compiler/GHC/CmmToAsm/PPC/Regs.hs
=====================================
@@ -133,7 +133,7 @@ data Imm
         = ImmInt        Int
         | ImmInteger    Integer     -- Sigh.
         | ImmCLbl       CLabel      -- AbstractC Label (with baggage)
-        | ImmLit        SDoc        -- Simple string
+        | ImmLit        String
         | ImmIndex    CLabel Int
         | ImmFloat      Rational
         | ImmDouble     Rational
@@ -147,7 +147,7 @@ data Imm
 
 
 strImmLit :: String -> Imm
-strImmLit s = ImmLit (text s)
+strImmLit s = ImmLit s
 
 
 litToImm :: CmmLit -> Imm


=====================================
compiler/GHC/CmmToAsm/X86/Ppr.hs
=====================================
@@ -432,7 +432,7 @@ pprImm platform = \case
    ImmInteger i        -> integer i
    ImmCLbl l           -> pdoc platform l
    ImmIndex l i        -> pdoc platform l <> char '+' <> int i
-   ImmLit s            -> s
+   ImmLit s            -> text s
    ImmFloat f          -> float $ fromRational f
    ImmDouble d         -> double $ fromRational d
    ImmConstantSum a b  -> pprImm platform a <> char '+' <> pprImm platform b


=====================================
compiler/GHC/CmmToAsm/X86/Regs.hs
=====================================
@@ -55,7 +55,6 @@ import GHC.Platform.Reg.Class
 
 import GHC.Cmm
 import GHC.Cmm.CLabel           ( CLabel )
-import GHC.Utils.Outputable
 import GHC.Utils.Panic
 import GHC.Platform
 
@@ -111,7 +110,7 @@ data Imm
   = ImmInt      Int
   | ImmInteger  Integer     -- Sigh.
   | ImmCLbl     CLabel      -- AbstractC Label (with baggage)
-  | ImmLit      SDoc        -- Simple string
+  | ImmLit      String
   | ImmIndex    CLabel Int
   | ImmFloat    Rational
   | ImmDouble   Rational
@@ -119,7 +118,7 @@ data Imm
   | ImmConstantDiff Imm Imm
 
 strImmLit :: String -> Imm
-strImmLit s = ImmLit (text s)
+strImmLit s = ImmLit s
 
 
 litToImm :: CmmLit -> Imm


=====================================
compiler/GHC/Core/Unfold.hs
=====================================
@@ -580,10 +580,9 @@ sizeExpr opts !bOMB_OUT_SIZE top_args expr
     ------------
     -- Cost to allocate binding with given binder
     size_up_alloc bndr
-      |  isTyVar bndr                 -- Doesn't exist at runtime
-      || isJoinId bndr                -- Not allocated at all
-      || isUnliftedType (idType bndr) -- Doesn't live in heap
-           -- OK to call isUnliftedType: binders have a fixed RuntimeRep (search for FRRBinder)
+      |  isTyVar bndr                    -- Doesn't exist at runtime
+      || isJoinId bndr                   -- Not allocated at all
+      || not (isBoxedType (idType bndr)) -- Doesn't live in heap
       = 0
       | otherwise
       = 10


=====================================
compiler/GHC/StgToCmm/Ticky.hs
=====================================
@@ -363,7 +363,7 @@ emitTickyCounter cloType tickee
                                       Just (CgIdInfo { cg_lf = cg_lf })
                                           | isLFThunk cg_lf
                                           -> return $! CmmLabel $ mkClosureInfoTableLabel (profilePlatform profile) tickee cg_lf
-                                      _   -> pprTraceDebug "tickyThunkUnknown" (text t <> colon <> ppr name <+> ppr (mkInfoTableLabel name NoCafRefs))
+                                      _   -> pprTraceDebug "tickyThunkUnknown" (text t <> colon <> ppr name <+> pdoc (profilePlatform profile) (mkInfoTableLabel name NoCafRefs))
                                             return $! zeroCLit platform
 
                             TickyLNE {} -> return $! zeroCLit platform


=====================================
compiler/GHC/Types/Name/Occurrence.hs
=====================================
@@ -6,7 +6,6 @@
 {-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE BangPatterns #-}
 {-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE LambdaCase #-}
 
 -- |
 -- #name_types#
@@ -282,24 +281,9 @@ pprOccName (OccName sp occ)
   = getPprStyle $ \ sty ->
     if codeStyle sty
     then ztext (zEncodeFS occ)
-    else pp_occ <> whenPprDebug (braces (pprNameSpaceBrief sp))
-  where
-    pp_occ = sdocOption sdocSuppressUniques $ \case
-               True  -> text (strip_th_unique (unpackFS occ))
-               False -> ftext occ
-
-        -- See Note [Suppressing uniques in OccNames]
-    strip_th_unique ('[' : c : _) | isAlphaNum c = []
-    strip_th_unique (c : cs) = c : strip_th_unique cs
-    strip_th_unique []       = []
+    else ftext occ <> whenPprDebug (braces (pprNameSpaceBrief sp))
 
 {-
-Note [Suppressing uniques in OccNames]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-This is a hack to de-wobblify the OccNames that contain uniques from
-Template Haskell that have been turned into a string in the OccName.
-See Note [Unique OccNames from Template Haskell] in "GHC.ThToHs"
-
 ************************************************************************
 *                                                                      *
 \subsection{Construction}


=====================================
compiler/GHC/Unit/Types.hs
=====================================
@@ -207,7 +207,7 @@ pprModule mod@(Module p n)  = getPprStyle doc
     | qualModule sty mod =
         case p of
           HoleUnit -> angleBrackets (pprModuleName n)
-          _        -> ppr (moduleUnit mod) <> char ':' <> pprModuleName n
+          _        -> ppr p <> char ':' <> pprModuleName n
     | otherwise =
         pprModuleName n
 


=====================================
hadrian/bindist/Makefile
=====================================
@@ -23,43 +23,6 @@ ifeq "$(Darwin_Host)" "YES"
 XATTR ?= /usr/bin/xattr
 endif
 
-# installscript
-#
-# $1 = package name
-# $2 = wrapper path
-# $3 = bindir
-# $4 = ghcbindir
-# $5 = Executable binary path
-# $6 = Library Directory
-# $7 = Docs Directory
-# $8 = Includes Directory
-# We are installing wrappers to programs by searching corresponding
-# wrappers. If wrapper is not found, we are attaching the common wrapper
-# to it. This implementation is a bit hacky and depends on consistency
-# of program names. For hadrian build this will work as programs have a
-# consistent naming procedure.
-define installscript
-	echo "installscript $1 -> $2"
-	@if [ -L 'wrappers/$1' ]; then                \
-		$(CP) -P 'wrappers/$1' '$2' ;             \
-	else								          \
-		rm -f '$2' && 		                      \
-		$(CREATE_SCRIPT) '$2' &&                  \
-		echo "#!$(SHELL)" >>  '$2'  &&            \
-		echo "exedir=\"$4\"" >> '$2'  &&          \
-		echo "exeprog=\"$1\"" >> '$2'  &&         \
-		echo "executablename=\"$5\"" >> '$2'  &&  \
-		echo "bindir=\"$3\"" >> '$2'  &&          \
-		echo "libdir=\"$6\"" >> '$2'  &&          \
-		echo "docdir=\"$7\"" >> '$2'  &&          \
-		echo "includedir=\"$8\"" >> '$2'  &&      \
-		echo "" >> '$2'  &&                       \
-		cat 'wrappers/$1' >> '$2'  &&             \
-		$(EXECUTABLE_FILE) '$2' ;                 \
-	fi
-	@echo "$1 installed to $2"
-endef
-
 # patchpackageconf
 #
 # Hacky function to patch up the 'haddock-interfaces' and 'haddock-html'
@@ -83,6 +46,8 @@ define patchpackageconf \
 	((echo "$1" | grep rts) && (cat '$2.copy' | sed 's|haddock-.*||' > '$2.copy.copy')) || (cat '$2.copy' > '$2.copy.copy')
 	# We finally replace the original file.
 	mv '$2.copy.copy' '$2'
+	# Fix the mode, in case umask is set
+	chmod 644 '$2'
 endef
 
 # QUESTION : should we use shell commands?
@@ -230,12 +195,13 @@ install_docs:
 		$(INSTALL_SCRIPT) docs-utils/gen_contents_index "$(DESTDIR)$(docdir)/html/libraries/"; \
 	fi
 
-BINARY_NAMES=$(shell ls ./wrappers/)
+export SHELL
 install_wrappers: install_bin_libdir
 	@echo "Installing wrapper scripts"
 	$(INSTALL_DIR) "$(DESTDIR)$(WrapperBinsDir)"
-	$(foreach p, $(BINARY_NAMES),\
-		$(call installscript,$p,$(DESTDIR)$(WrapperBinsDir)/$p,$(WrapperBinsDir),$(ActualBinsDir),$(ActualBinsDir)/$p,$(ActualLibsDir),$(docdir),$(includedir)))
+	for p in `cd wrappers; $(FIND) . ! -type d`; do \
+	    mk/install_script.sh "$$p" "$(DESTDIR)/$(WrapperBinsDir)/$$p" "$(WrapperBinsDir)" "$(ActualBinsDir)" "$(ActualBinsDir)/$$p" "$(ActualLibsDir)" "$(docdir)" "$(includedir)"; \
+	done
 
 PKG_CONFS = $(shell find "$(DESTDIR)$(ActualLibsDir)/package.conf.d" -name '*.conf' | sed "s:   :\0xxx\0:g")
 update_package_db: install_bin install_lib


=====================================
hadrian/bindist/config.mk.in
=====================================
@@ -93,9 +93,6 @@ ghcheaderdir  = $(ghclibdir)/rts/include
 #-----------------------------------------------------------------------------
 # Utilities needed by the installation Makefile
 
-GENERATED_FILE  = chmod a-w
-EXECUTABLE_FILE = chmod +x
-CP              = cp
 FIND            = @FindCmd@
 INSTALL         = @INSTALL@
 INSTALL        := $(subst .././install-sh,$(TOP)/install-sh,$(INSTALL))
@@ -103,6 +100,8 @@ LN_S            = @LN_S@
 MV              = mv
 SED             = @SedCmd@
 SHELL           = @SHELL@
+RANLIB_CMD      = @RanlibCmd@
+STRIP_CMD       = @StripCmd@
 
 #
 # Invocations of `install' for different classes
@@ -117,9 +116,6 @@ INSTALL_MAN     = $(INSTALL) -m 644
 INSTALL_DOC     = $(INSTALL) -m 644
 INSTALL_DIR     = $(INSTALL) -m 755 -d
 
-CREATE_SCRIPT   = create () { touch "$$1" && chmod 755 "$$1" ; } && create
-CREATE_DATA     = create () { touch "$$1" && chmod 644 "$$1" ; } && create
-
 #-----------------------------------------------------------------------------
 # Build configuration
 


=====================================
hadrian/src/Rules/BinaryDist.hs
=====================================
@@ -352,6 +352,7 @@ bindistInstallFiles =
     , "mk" -/- "project.mk"
     , "mk" -/- "relpath.sh"
     , "mk" -/- "system-cxx-std-lib-1.0.conf.in"
+    , "mk" -/- "install_script.sh"
     , "README", "INSTALL" ]
 
 -- | This auxiliary function gives us a top-level 'Filepath' that we can 'need'


=====================================
m4/fp_find_cxx_std_lib.m4
=====================================
@@ -18,10 +18,44 @@ unknown
 #endif
 EOF
         AC_MSG_CHECKING([C++ standard library flavour])
-        if "$CXX" -E actest.cpp -o actest.out; then
-            if grep "libc++" actest.out >/dev/null; then
-                CXX_STD_LIB_LIBS="c++ c++abi"
-                p="`"$CXX" --print-file-name libc++.so`"
+        if ! "$CXX" -E actest.cpp -o actest.out; then
+            rm -f actest.cpp actest.out
+            AC_MSG_ERROR([Failed to compile test program])
+        fi
+
+        dnl Identify standard library type
+        if grep "libc++" actest.out >/dev/null; then
+            CXX_STD_LIB_FLAVOUR="c++"
+            AC_MSG_RESULT([libc++])
+        elif grep "libstdc++" actest.out >/dev/null; then
+            CXX_STD_LIB_FLAVOUR="stdc++"
+            AC_MSG_RESULT([libstdc++])
+        else
+            rm -f actest.cpp actest.out
+            AC_MSG_ERROR([Unknown C++ standard library implementation.])
+        fi
+        rm -f actest.cpp actest.out
+
+        dnl -----------------------------------------
+        dnl Figure out how to link...
+        dnl -----------------------------------------
+        cat >actest.cpp <<-EOF
+#include <iostream>
+int main(int argc, char** argv) {
+    std::cout << "hello world\n";
+    return 0;
+}
+EOF
+        if ! "$CXX" -c actest.cpp; then
+            AC_MSG_ERROR([Failed to compile test object])
+        fi
+
+        try_libs() {
+            dnl Try to link a plain object with CC manually
+            AC_MSG_CHECKING([for linkage against '${3}'])
+            if "$CC" -o actest actest.o ${1} 2>/dev/null; then
+                CXX_STD_LIB_LIBS="${3}"
+                p="`"$CXX" --print-file-name ${2}`"
                 d="`dirname "$p"`"
                 dnl On some platforms (e.g. Windows) the C++ standard library
                 dnl can be found in the system search path. In this case $CXX
@@ -31,24 +65,25 @@ EOF
                 if test "$d" = "."; then d=""; fi
                 CXX_STD_LIB_LIB_DIRS="$d"
                 CXX_STD_LIB_DYN_LIB_DIRS="$d"
-                AC_MSG_RESULT([libc++])
-            elif grep "libstdc++" actest.out >/dev/null; then
-                CXX_STD_LIB_LIBS="stdc++"
-                p="`"$CXX" --print-file-name libstdc++.so`"
-                d="`dirname "$p"`"
-                if test "$d" = "."; then d=""; fi
-                CXX_STD_LIB_LIB_DIRS="$d"
-                CXX_STD_LIB_DYN_LIB_DIRS="$d"
-                AC_MSG_RESULT([libstdc++])
+                AC_MSG_RESULT([success])
+                true
             else
-                rm -f actest.cpp actest.out
-                AC_MSG_ERROR([Unknown C++ standard library implementation.])
+                AC_MSG_RESULT([failed])
+                false
             fi
-            rm -f actest.cpp actest.out
-        else
-            rm -f actest.cpp actest.out
-            AC_MSG_ERROR([Failed to compile test program])
-        fi
+        }
+        case $CXX_STD_LIB_FLAVOUR in
+        c++)
+            try_libs "-lc++ -lc++abi" "libc++.so" "c++ c++abi" || \
+            try_libs "-lc++ -lcxxrt" "libc++.so" "c++ cxxrt" ||
+            AC_MSG_ERROR([Failed to find C++ standard library]) ;;
+        stdc++)
+            try_libs "-lstdc++" "libstdc++.so" "stdc++" || \
+            try_libs "-lstdc++ -lsupc++" "libstdc++.so" "stdc++ supc++" || \
+            AC_MSG_ERROR([Failed to find C++ standard library]) ;;
+        esac
+
+        rm -f actest.cpp actest.o actest
     fi
 
     AC_SUBST([CXX_STD_LIB_LIBS])


=====================================
mk/install_script.sh
=====================================
@@ -0,0 +1,34 @@
+#!/bin/sh
+
+# $1 = executable name
+# $2 = wrapper path
+# $3 = bindir
+# $4 = ghcbindir
+# $5 = Executable binary path
+# $6 = Library Directory
+# $7 = Docs Directory
+# $8 = Includes Directory
+# We are installing wrappers to programs by searching corresponding
+# wrappers. If wrapper is not found, we are attaching the common wrapper
+# to it. This implementation is a bit hacky and depends on consistency
+# of program names. For hadrian build this will work as programs have a
+# consistent naming procedure.
+
+echo "Installing $1 -> $2"
+if [ -L "wrappers/$1" ]; then
+    cp -RP "wrappers/$1" "$2"
+else
+    rm -f "$2" &&
+    touch "$2" &&
+    echo "#!$SHELL" >> "$2"  &&
+    echo "exedir=\"$4\"" >> "$2"  &&
+    echo "exeprog=\"$1\"" >> "$2"  &&
+    echo "executablename=\"$5\"" >> "$2"  &&
+    echo "bindir=\"$3\"" >> "$2"  &&
+    echo "libdir=\"$6\"" >> "$2"  &&
+    echo "docdir=\"$7\"" >> "$2"  &&
+    echo "includedir=\"$8\"" >> "$2"  &&
+    echo "" >> "$2"  &&
+    cat "wrappers/$1" >> "$2"  &&
+    chmod 755 "$2"
+fi


=====================================
rts/Linker.c
=====================================
@@ -80,6 +80,33 @@
 #if defined(dragonfly_HOST_OS)
 #include <sys/tls.h>
 #endif
+
+/*
+ * Note [iconv and FreeBSD]
+ * ~~~~~~~~~~~~~~~~~~~~~~~~
+ *
+ * On FreeBSD libc.so provides an implementation of the iconv_* family of
+ * functions. However, due to their implementation, these symbols cannot be
+ * resolved via dlsym(); rather, they can only be resolved using the
+ * explicitly-versioned dlvsym().
+ *
+ * This is problematic for the RTS linker since we may be asked to load
+ * an object that depends upon iconv. To handle this we include a set of
+ * fallback cases for these functions, allowing us to resolve them to the
+ * symbols provided by the libc against which the RTS is linked.
+ *
+ * See #20354.
+ */
+
+#if defined(freebsd_HOST_OS)
+extern void iconvctl();
+extern void iconv_open_into();
+extern void iconv_open();
+extern void iconv_close();
+extern void iconv_canonicalize();
+extern void iconv();
+#endif
+
 /*
    Note [runtime-linker-support]
    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -637,6 +664,10 @@ internal_dlsym(const char *symbol) {
     }
     RELEASE_LOCK(&dl_mutex);
 
+    IF_DEBUG(linker, debugBelch("internal_dlsym: looking for symbol '%s' in special cases\n", symbol));
+#   define SPECIAL_SYMBOL(sym) \
+      if (strcmp(symbol, #sym) == 0) return (void*)&sym;
+
 #   if defined(HAVE_SYS_STAT_H) && defined(linux_HOST_OS) && defined(__GLIBC__)
     // HACK: GLIBC implements these functions with a great deal of trickery where
     //       they are either inlined at compile time to their corresponding
@@ -646,18 +677,28 @@ internal_dlsym(const char *symbol) {
     //       We borrow the approach that the LLVM JIT uses to resolve these
     //       symbols. See http://llvm.org/PR274 and #7072 for more info.
 
-    IF_DEBUG(linker, debugBelch("internal_dlsym: looking for symbol '%s' in GLIBC special cases\n", symbol));
+    SPECIAL_SYMBOL(stat);
+    SPECIAL_SYMBOL(fstat);
+    SPECIAL_SYMBOL(lstat);
+    SPECIAL_SYMBOL(stat64);
+    SPECIAL_SYMBOL(fstat64);
+    SPECIAL_SYMBOL(lstat64);
+    SPECIAL_SYMBOL(atexit);
+    SPECIAL_SYMBOL(mknod);
+#   endif
 
-    if (strcmp(symbol, "stat") == 0) return (void*)&stat;
-    if (strcmp(symbol, "fstat") == 0) return (void*)&fstat;
-    if (strcmp(symbol, "lstat") == 0) return (void*)&lstat;
-    if (strcmp(symbol, "stat64") == 0) return (void*)&stat64;
-    if (strcmp(symbol, "fstat64") == 0) return (void*)&fstat64;
-    if (strcmp(symbol, "lstat64") == 0) return (void*)&lstat64;
-    if (strcmp(symbol, "atexit") == 0) return (void*)&atexit;
-    if (strcmp(symbol, "mknod") == 0) return (void*)&mknod;
+    // See Note [iconv and FreeBSD]
+#   if defined(freebsd_HOST_OS)
+    SPECIAL_SYMBOL(iconvctl);
+    SPECIAL_SYMBOL(iconv_open_into);
+    SPECIAL_SYMBOL(iconv_open);
+    SPECIAL_SYMBOL(iconv_close);
+    SPECIAL_SYMBOL(iconv_canonicalize);
+    SPECIAL_SYMBOL(iconv);
 #   endif
 
+#undef SPECIAL_SYMBOL
+
     // we failed to find the symbol
     return NULL;
 }


=====================================
testsuite/tests/linters/notes.stdout
=====================================
@@ -44,7 +44,6 @@ ref    compiler/GHC/Tc/Types.hs:702:33:     Note [Extra dependencies from .hs-bo
 ref    compiler/GHC/Tc/Types.hs:1433:47:     Note [Care with plugin imports]
 ref    compiler/GHC/Tc/Types/Constraint.hs:253:34:     Note [NonCanonical Semantics]
 ref    compiler/GHC/Types/Demand.hs:308:25:     Note [Preserving Boxity of results is rarely a win]
-ref    compiler/GHC/Types/Name/Occurrence.hs:301:4:     Note [Unique OccNames from Template Haskell]
 ref    compiler/GHC/Unit/Module/Deps.hs:82:13:     Note [Structure of dep_boot_mods]
 ref    compiler/GHC/Utils/Monad.hs:391:34:     Note [multiShotIO]
 ref    compiler/Language/Haskell/Syntax/Binds.hs:204:31:     Note [fun_id in Match]



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ae347f59f5d3885cdba7f4542872c37ef7bc5c59...6156ec32e3ea9b55072d175cd8cf8856f867d268

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ae347f59f5d3885cdba7f4542872c37ef7bc5c59...6156ec32e3ea9b55072d175cd8cf8856f867d268
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/20220809/e6fe4bda/attachment-0001.html>


More information about the ghc-commits mailing list