[Git][ghc/ghc][wip/backports-8.8] 8 commits: Bump bytestring submodule

Ben Gamari gitlab at gitlab.haskell.org
Wed Jul 8 15:38:14 UTC 2020



Ben Gamari pushed to branch wip/backports-8.8 at Glasgow Haskell Compiler / GHC


Commits:
a0c5ab3f by GHC GitLab CI at 2020-07-04T14:19:15+00:00
Bump bytestring submodule

- - - - -
3475384d by GHC GitLab CI at 2020-07-04T14:19:33+00:00
Bump Cabal submodule

- - - - -
b12faad0 by GHC GitLab CI at 2020-07-04T15:19:25+00:00
Bump to 8.8.4, RELEASE=YES

- - - - -
ac697a44 by Ben Gamari at 2020-07-06T12:15:24-04:00
gitlab-ci: Reintroduce workflow stanza

- - - - -
fc1bd787 by Moritz Angermann at 2020-07-08T11:22:36-04:00
Range is actually +/-2^32, not +/-2^31

See also: https://static.docs.arm.com/ihi0056/g/aaelf64.pdf

(cherry picked from commit 4a158ffc4e0ac250897aefaf6caf03eb5f688182)

- - - - -
1f2a440a by Moritz Angermann at 2020-07-08T11:26:40-04:00
Load .lo as well.

Some archives contain so called linker objects, with the affectionate
.lo suffic.  For example the musl libc.a will come in that form.  We
still want to load those objects, hence we should not discard them and
look for .lo as well.  Ultimately we might want to fix this proerly by
looking at the file magic.

(cherry picked from commit 3fd12af1eaafe304e5916bc1fcfdf31709d360b8)

- - - - -
ade1b738 by Travis Whitaker at 2020-07-08T11:34:57-04:00
Build a threaded stage 1 if the bootstrapping GHC supports it.

(cherry picked from commit 67738db10010fd28a8e997b5c8f83ea591b88a0e)

- - - - -
2900ab4f by Moritz Angermann at 2020-07-08T11:37:55-04:00
ghc-prim needs to depend on libc and libm

libm is just an empty shell on musl, and all the math functions are contained in
libc.

(cherry picked from commit b455074875d3c8fd3a5787e01dc6f922f3a97bc2)

- - - - -


12 changed files:

- .gitlab-ci.yml
- compiler/ghc.mk
- configure.ac
- ghc/ghc.mk
- hadrian/cfg/system.config.in
- hadrian/src/Expression.hs
- hadrian/src/Oracles/Flag.hs
- hadrian/src/Settings/Packages.hs
- libraries/ghc-prim/ghc-prim.cabal
- mk/config.mk.in
- rts/linker/LoadArchive.c
- rts/linker/elf_reloc_aarch64.c


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -32,6 +32,15 @@ stages:
     - if: '$CI_COMMIT_BRANCH =~ /ghc-[0.9]+\.[0-9]+/'
     - if: '$CI_PIPELINE_SOURCE == "web"'
 
+workflow:
+  # N.B. Don't run on wip/ branches, instead on run on merge requests.
+  rules:
+    - if: $CI_MERGE_REQUEST_ID
+    - if: $CI_COMMIT_TAG
+    - if: '$CI_COMMIT_BRANCH == "wip/marge_bot_batch_merge_job"'
+    - if: '$CI_COMMIT_BRANCH =~ /ghc-[0.9]+\.[0-9]+/'
+    - if: '$CI_PIPELINE_SOURCE == "web"'
+
 ############################################################
 # Runner Tags
 ############################################################


=====================================
compiler/ghc.mk
=====================================
@@ -326,6 +326,12 @@ ifeq "$(GhcThreaded)" "YES"
 compiler_stage2_CONFIGURE_OPTS += --ghc-option=-optc-DTHREADED_RTS
 endif
 
+# If the bootstrapping GHC supplies the threaded RTS, then we can have a
+# threaded stage 1 too.
+ifeq "$(GhcThreadedRts)" "YES"
+compiler_stage1_CONFIGURE_OPTS += --ghc-option=-optc-DTHREADED_RTS
+endif
+
 ifeq "$(GhcWithNativeCodeGen)" "YES"
 compiler_stage1_CONFIGURE_OPTS += --flags=ncg
 compiler_stage2_CONFIGURE_OPTS += --flags=ncg


=====================================
configure.ac
=====================================
@@ -13,10 +13,10 @@ dnl
 # see what flags are available. (Better yet, read the documentation!)
 #
 
-AC_INIT([The Glorious Glasgow Haskell Compilation System], [8.8.3], [glasgow-haskell-bugs at haskell.org], [ghc-AC_PACKAGE_VERSION])
+AC_INIT([The Glorious Glasgow Haskell Compilation System], [8.8.4], [glasgow-haskell-bugs at haskell.org], [ghc-AC_PACKAGE_VERSION])
 
 # Set this to YES for a released version, otherwise NO
-: ${RELEASE=NO}
+: ${RELEASE=YES}
 
 # The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line
 # above.  If this is not a released version, then we will append the
@@ -127,6 +127,9 @@ dnl CC_STAGE0 is like the "previous" variable CC (inherited by CC_STAGE[123])
 dnl but instead used by stage0 for bootstrapping stage1
 AC_ARG_VAR(CC_STAGE0, [C compiler command (bootstrap)])
 
+dnl RTS ways supplied by the bootstrapping compiler.
+AC_ARG_VAR(RTS_WAYS_STAGE0, [RTS ways])
+
 if test "$WithGhc" != ""; then
   FPTOOLS_GHC_VERSION([GhcVersion], [GhcMajVersion], [GhcMinVersion], [GhcPatchLevel])dnl
 
@@ -150,6 +153,17 @@ if test "$WithGhc" != ""; then
   BOOTSTRAPPING_GHC_INFO_FIELD([AR_STAGE0],[ar command])
   BOOTSTRAPPING_GHC_INFO_FIELD([AR_OPTS_STAGE0],[ar flags])
   BOOTSTRAPPING_GHC_INFO_FIELD([ArSupportsAtFile_STAGE0],[ar supports at file])
+  BOOTSTRAPPING_GHC_INFO_FIELD([RTS_WAYS_STAGE0],[RTS ways])
+
+  dnl Check whether or not the bootstrapping GHC has a threaded RTS. This
+  dnl determines whether or not we can have a threaded stage 1.
+  dnl See Note [Linking ghc-bin against threaded stage0 RTS] in
+  dnl hadrian/src/Settings/Packages.hs for details.
+  if echo ${RTS_WAYS_STAGE0} | grep '.*thr.*' 2>&1 >/dev/null; then
+      AC_SUBST(GhcThreadedRts, YES)
+  else
+      AC_SUBST(GhcThreadedRts, NO)
+  fi
 fi
 
 dnl ** Must have GHC to build GHC
@@ -1372,6 +1386,7 @@ Configure completed successfully.
 echo "\
    Bootstrapping using   : $WithGhc
       which is version   : $GhcVersion
+      with threaded RTS? : $GhcThreadedRts
 "
 
 if test "x$CC_LLVM_BACKEND" = "x1"; then


=====================================
ghc/ghc.mk
=====================================
@@ -63,6 +63,13 @@ ghc_stage2_MORE_HC_OPTS += -threaded
 ghc_stage3_MORE_HC_OPTS += -threaded
 endif
 
+# If stage 0 supplies a threaded RTS, we can use it for stage 1.
+# See Note [Linking ghc-bin against threaded stage0 RTS] in
+# hadrian/src/Settings/Packages.hs for details.
+ifeq "$(GhcThreadedRts)" "YES"
+ghc_stage1_MORE_HC_OPTS += -threaded
+endif
+
 ifeq "$(GhcProfiled)" "YES"
 ghc_stage2_PROGRAM_WAY = p
 endif
@@ -120,16 +127,11 @@ ghc/stage2/build/tmp/$(ghc_stage2_PROG) : $(compiler_stage2_p_LIB)
 ghc/stage2/build/tmp/$(ghc_stage2_PROG) : $(foreach lib,$(PACKAGES_STAGE1),$(libraries/$(lib)_dist-install_p_LIB))
 endif
 
-# Modules here import HsVersions.h, so we need ghc_boot_platform.h
-$(ghc_stage1_depfile_haskell) : compiler/stage1/$(PLATFORM_H)
-$(ghc_stage2_depfile_haskell) : compiler/stage2/$(PLATFORM_H)
-$(ghc_stage3_depfile_haskell) : compiler/stage3/$(PLATFORM_H)
-
 all_ghc_stage1 : $(GHC_STAGE1)
 all_ghc_stage2 : $(GHC_STAGE2)
 all_ghc_stage3 : $(GHC_STAGE3)
 
-$(INPLACE_LIB)/settings : settings
+$(INPLACE_LIB)/settings : $(includes_SETTINGS)
 	"$(CP)" $< $@
 
 $(INPLACE_LIB)/llvm-targets : llvm-targets
@@ -154,12 +156,6 @@ $(GHC_STAGE1) : | $(GHC_DEPENDENCIES)
 $(GHC_STAGE2) : | $(GHC_DEPENDENCIES)
 $(GHC_STAGE3) : | $(GHC_DEPENDENCIES)
 
-ifeq "$(GhcUnregisterised)" "NO"
-$(GHC_STAGE1) : | $$(ghc-split_INPLACE)
-$(GHC_STAGE2) : | $$(ghc-split_INPLACE)
-$(GHC_STAGE3) : | $$(ghc-split_INPLACE)
-endif
-
 ifeq "$(Windows_Host)" "YES"
 $(GHC_STAGE1) : | $$(touchy_INPLACE)
 $(GHC_STAGE2) : | $$(touchy_INPLACE)
@@ -174,7 +170,7 @@ $(GHC_STAGE2) : $(foreach w,$(GhcLibWays),libraries/base/dist-install/build/GHC/
 
 endif
 
-INSTALL_LIBS += settings
+INSTALL_LIBS += $(includes_SETTINGS)
 INSTALL_LIBS += llvm-targets
 INSTALL_LIBS += llvm-passes
 


=====================================
hadrian/cfg/system.config.in
=====================================
@@ -77,6 +77,8 @@ ghc-major-version     = @GhcMajVersion@
 ghc-minor-version     = @GhcMinVersion@
 ghc-patch-level       = @GhcPatchLevel@
 
+bootstrap-threaded-rts      = @GhcThreadedRts@
+
 supports-this-unit-id = @SUPPORTS_THIS_UNIT_ID@
 
 project-name          = @ProjectName@


=====================================
hadrian/src/Expression.hs
=====================================
@@ -26,6 +26,7 @@ import Base
 import Builder
 import Context hiding (stage, package, way)
 import Expression.Type
+import Oracles.Flag
 import Hadrian.Expression hiding (Expr, Predicate, Args)
 import Hadrian.Haskell.Cabal.Type
 import Hadrian.Oracles.Cabal
@@ -99,6 +100,13 @@ stage2 = stage Stage2
 notStage0 :: Predicate
 notStage0 = notM stage0
 
+-- | Whether or not the bootstrapping compiler provides a threaded RTS. We need
+--   to know this when building stage 1, since stage 1 links against the
+--   compiler's RTS ways. See Note [Linking ghc-bin against threaded stage0 RTS]
+--   in Settings.Packages for details.
+threadedBootstrapper :: Predicate
+threadedBootstrapper = expr (flag BootstrapThreadedRts)
+
 -- | Is a certain package /not/ built right now?
 notPackage :: Package -> Predicate
 notPackage = notM . package


=====================================
hadrian/src/Oracles/Flag.hs
=====================================
@@ -21,6 +21,7 @@ data Flag = ArSupportsAtFile
           | WithLibdw
           | HaveLibMingwEx
           | UseSystemFfi
+          | BootstrapThreadedRts
 
 -- Note, if a flag is set to empty string we treat it as set to NO. This seems
 -- fragile, but some flags do behave like this, e.g. GccIsClang.
@@ -39,6 +40,7 @@ flag f = do
             WithLibdw          -> "with-libdw"
             HaveLibMingwEx     -> "have-lib-mingw-ex"
             UseSystemFfi       -> "use-system-ffi"
+            BootstrapThreadedRts -> "bootstrap-threaded-rts"
     value <- lookupValueOrError configFile key
     when (value `notElem` ["YES", "NO", ""]) . error $ "Configuration flag "
         ++ quote (key ++ " = " ++ value) ++ " cannot be parsed."


=====================================
hadrian/src/Settings/Packages.hs
=====================================
@@ -53,10 +53,15 @@ packageArgs = do
             , arg "--disable-library-for-ghci"
             , anyTargetOs ["openbsd"] ? arg "--ld-options=-E"
             , flag GhcUnregisterised ? arg "--ghc-option=-DNO_REGS"
-            , notM ghcWithSMP ? arg "--ghc-option=-DNOSMP"
-            , notM ghcWithSMP ? arg "--ghc-option=-optc-DNOSMP"
+            , notM targetSupportsSMP ? arg "--ghc-option=-DNOSMP"
+            , notM targetSupportsSMP ? arg "--ghc-option=-optc-DNOSMP"
+            -- When building stage 1 or later, use thread-safe RTS functions if
+            -- the configuration calls for a threaded GHC.
             , (any (wayUnit Threaded) rtsWays) ?
               notStage0 ? arg "--ghc-option=-optc-DTHREADED_RTS"
+            -- When building stage 1, use thread-safe RTS functions if the
+            -- bootstrapping (stage 0) compiler provides a threaded RTS way.
+            , stage0 ? threadedBootstrapper ? arg "--ghc-option=-optc-DTHREADED_RTS"
             , ghcWithInterpreter ?
               ghcEnableTablesNextToCode ?
               notM (flag GhcUnregisterised) ?
@@ -85,10 +90,27 @@ packageArgs = do
           , builder (Cabal Flags) ? mconcat
             [ ghcWithInterpreter ? notStage0 ? arg "ghci"
             , flag CrossCompiling ? arg "-terminfo"
-            -- the 'threaded' flag is True by default, but
-            -- let's record explicitly that we link all ghc
-            -- executables with the threaded runtime.
-            , arg "threaded" ] ]
+            -- Note [Linking ghc-bin against threaded stage0 RTS]
+            -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+            -- We must maintain the invariant that GHCs linked with '-threaded'
+            -- are built with '-optc=-DTHREADED_RTS', otherwise we'll end up
+            -- with a GHC that can use the threaded runtime, but contains some
+            -- non-thread-safe functions. See
+            -- https://gitlab.haskell.org/ghc/ghc/issues/18024 for an example of
+            -- the sort of issues this can cause.
+            , ifM stage0
+                  -- We build a threaded stage 1 if the bootstrapping compiler
+                  -- supports it.
+                  (ifM threadedBootstrapper
+                       (arg "threaded")
+                       (arg "-threaded"))
+                  -- We build a threaded stage N, N>1 if the configuration calls
+                  -- for it.
+                  (ifM (ghcThreaded <$> expr flavour)
+                       (arg "threaded")
+                       (arg "-threaded"))
+            ]
+          ]
 
         -------------------------------- ghcPkg --------------------------------
         , package ghcPkg ?


=====================================
libraries/ghc-prim/ghc-prim.cabal
=====================================
@@ -66,6 +66,11 @@ Library
         --         on Windows. Required because of mingw32.
         extra-libraries: user32, mingw32, mingwex
 
+    if os(linux)
+        -- we need libm, but for musl and other's we might need libc, as libm
+        -- is just an empty shell.
+        extra-libraries: c, m
+
     c-sources:
         cbits/atomic.c
         cbits/bswap.c


=====================================
mk/config.mk.in
=====================================
@@ -199,6 +199,9 @@ endif
 # `GhcUnregisterised` mode doesn't allow that.
 GhcWithSMP := $(strip $(if $(filter YESNO, $(ArchSupportsSMP)$(GhcUnregisterised)),YES,NO))
 
+# Whether or not the bootstrapping GHC supplies a threaded RTS.
+GhcThreadedRts = @GhcThreadedRts@
+
 # Whether to include GHCi in the compiler.  Depends on whether the RTS linker
 # has support for this OS/ARCH combination.
 


=====================================
rts/linker/LoadArchive.c
=====================================
@@ -461,6 +461,7 @@ static HsInt loadArchive_ (pathchar *path)
         /* TODO: Stop relying on file extensions to determine input formats.
                  Instead try to match file headers. See Trac #13103.  */
         isObject = (thisFileNameSize >= 2 && strncmp(fileName + thisFileNameSize - 2, ".o"  , 2) == 0)
+                || (thisFileNameSize >= 3 && strncmp(fileName + thisFileNameSize - 3, ".lo" , 3) == 0)
                 || (thisFileNameSize >= 4 && strncmp(fileName + thisFileNameSize - 4, ".p_o", 4) == 0)
                 || (thisFileNameSize >= 4 && strncmp(fileName + thisFileNameSize - 4, ".obj", 4) == 0);
 


=====================================
rts/linker/elf_reloc_aarch64.c
=====================================
@@ -90,12 +90,14 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) {
             // ...              hi            ] [     Rd     ]
             //
             // imm64 = SignExtend(hi:lo:0x000,64)
-            assert(isInt64(32, addend));
+            // Range is 21 bits + the 12 page relative bits
+            // known to be 0. -2^32 <= X < 2^32
+            assert(isInt64(21+12, addend));
             assert((addend & 0xfff) == 0); /* page relative */
 
             *(inst_t *)P = (*(inst_t *)P & 0x9f00001f)
-                           | (inst_t) (((uint64_t) addend << 17) & 0x60000000)
-                           | (inst_t) (((uint64_t) addend >> 9) & 0x00ffffe0);
+                        | (inst_t) (((uint64_t) addend << 17) & 0x60000000)
+                        | (inst_t) (((uint64_t) addend >> 9) & 0x00ffffe0);
             break;
         }
         /* - control flow relocations */
@@ -108,8 +110,8 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) {
             break;
         }
         case COMPAT_R_AARCH64_ADR_GOT_PAGE: {
-
-            assert(isInt64(32, addend)); /* X in range */
+            /* range is -2^32 <= X < 2^32 */
+            assert(isInt64(21+12, addend)); /* X in range */
             assert((addend & 0xfff) == 0); /* page relative */
 
             *(inst_t *)P = (*(inst_t *)P & 0x9f00001f)



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/88262e192e69fc71916d47cbdbd8bb7c9a8f1782...2900ab4fd9118d542a3ccac830fdce046288d71f

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/88262e192e69fc71916d47cbdbd8bb7c9a8f1782...2900ab4fd9118d542a3ccac830fdce046288d71f
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/20200708/4a3c02bd/attachment-0001.html>


More information about the ghc-commits mailing list