[Git][ghc/ghc][wip/rts-configure-symbols] 8 commits: Add safe list indexing operator: !?

John Ericson (@Ericson2314) gitlab at gitlab.haskell.org
Tue Jan 10 18:41:50 UTC 2023



John Ericson pushed to branch wip/rts-configure-symbols at Glasgow Haskell Compiler / GHC


Commits:
d53f6f4d by Oleg Grenrus at 2023-01-09T21:11:02-05:00
Add safe list indexing operator: !?

With Joachim's amendments.

Implements https://github.com/haskell/core-libraries-committee/issues/110

- - - - -
cfaf1ad7 by Nicolas Trangez at 2023-01-09T21:11:03-05:00
rts, tests: limit thread name length to 15 bytes

On Linux, `pthread_setname_np` (or rather, the kernel) only allows for
thread names up to 16 bytes, including the terminating null byte.

This commit adds a note pointing this out in `createOSThread`, and fixes
up two instances where a thread name of more than 15 characters long was
used (in the RTS, and in a test-case).

Fixes: #22366
Fixes: https://gitlab.haskell.org/ghc/ghc/-/issues/22366
See: https://gitlab.haskell.org/ghc/ghc/-/issues/22366#note_460796

- - - - -
64286132 by Matthew Pickering at 2023-01-09T21:11:03-05:00
Store bootstrap_llvm_target and use it to set LlvmTarget in bindists

This mirrors some existing logic for the bootstrap_target which
influences how TargetPlatform is set.

As described on #21970 not storing this led to `LlvmTarget` being set incorrectly
and hence the wrong `--target` flag being passed to the C compiler.

Towards #21970

- - - - -
4724e8d1 by Matthew Pickering at 2023-01-09T21:11:04-05:00
Check for FP_LD_NO_FIXUP_CHAINS in installation configure script

Otherwise, when installing from a bindist the C flag isn't passed to the
C compiler.

This completes the fix for #22429

- - - - -
2e926b88 by Georgi Lyubenov at 2023-01-09T21:11:07-05:00
Fix outdated link to Happy section on sequences

- - - - -
146a1458 by Matthew Pickering at 2023-01-09T21:11:07-05:00
Revert "NCG(x86): Compile add+shift as lea if possible."

This reverts commit 20457d775885d6c3df020d204da9a7acfb3c2e5a.

See #22666 and #21777

- - - - -
5a763d8c by John Ericson at 2023-01-10T08:04:54+00:00
Give the RTS it's own configure script

Currently it doesn't do much anything, we are just trying to introduce
it without breaking the build. Later, we will move functionality from
the top-level configure script over to it.

We need to bump Cabal for https://github.com/haskell/cabal/pull/8649; to
facilitate and existing hack of skipping some configure checks for the
RTS we now need to skip just *part* not *all* of the "post configure"
hook, as running the configure script (which we definitely want to do)
is also implemented as part of the "post configure" hook. But doing this
requires exposing functionality that wasn't exposed before.

- - - - -
af547008 by John Ericson at 2023-01-10T09:53:37-05:00
rts: Move most external symbols logic to the configure script

This is much more terse because we are programmatically handling the
leading underscore.

`findPtr` however is still handled in the Cabal file because we need a
newer Cabal to pass flags to the configure script automatically.

- - - - -


28 changed files:

- boot
- compiler/GHC/CmmToAsm/X86/CodeGen.hs
- compiler/GHC/Parser.y
- configure.ac
- distrib/configure.ac.in
- hadrian/src/Base.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Rules/Lint.hs
- hadrian/src/Rules/Register.hs
- hadrian/src/Rules/SourceDist.hs
- libraries/base/.gitignore
- libraries/base/Data/List.hs
- libraries/base/Data/OldList.hs
- libraries/base/GHC/List.hs
- libraries/base/changelog.md
- m4/fp_find_libdw.m4
- m4/ghc_llvm_target.m4
- rts/.gitignore
- + rts/configure.ac
- + rts/external-symbols.list.in
- rts/posix/OSThreads.c
- + rts/rts.buildinfo.in
- rts/rts.cabal.in
- rts/sm/NonMoving.c
- − testsuite/tests/codeGen/should_gen_asm/AddMulX86.asm
- − testsuite/tests/codeGen/should_gen_asm/AddMulX86.hs
- testsuite/tests/codeGen/should_gen_asm/all.T
- testsuite/tests/rts/pause-resume/pause_resume.c


Changes:

=====================================
boot
=====================================
@@ -63,7 +63,7 @@ def autoreconf():
     else:
         reconf_cmd = 'autoreconf'
 
-    for dir_ in ['.'] + glob.glob('libraries/*/'):
+    for dir_ in ['.', 'rts'] + glob.glob('libraries/*/'):
         if os.path.isfile(os.path.join(dir_, 'configure.ac')):
             print("Booting %s" % dir_)
             # Update config.sub in submodules


=====================================
compiler/GHC/CmmToAsm/X86/CodeGen.hs
=====================================
@@ -1048,29 +1048,10 @@ getRegister' _ is32Bit (CmmMachOp mop [x, y]) = -- dyadic MachOps
 
     --------------------
     add_code :: Width -> CmmExpr -> CmmExpr -> NatM Register
-    -- x + imm
     add_code rep x (CmmLit (CmmInt y _))
         | is32BitInteger y
         , rep /= W8 -- LEA doesn't support byte size (#18614)
         = add_int rep x y
-    -- x + (y << imm)
-    add_code rep x y
-        -- Byte size is not supported and 16bit size is slow when computed via LEA
-        | rep /= W8 && rep /= W16
-        -- 2^3 = 8 is the highest multiplicator supported by LEA.
-        , Just (x,y,shift_bits) <- get_shift x y
-        = add_shiftL rep x y (fromIntegral shift_bits)
-        where
-          -- x + (y << imm)
-          get_shift x (CmmMachOp (MO_Shl _w) [y, CmmLit (CmmInt shift_bits _)])
-            | shift_bits <= 3
-            = Just (x, y, shift_bits)
-          -- (y << imm) + x
-          get_shift (CmmMachOp (MO_Shl _w) [y, CmmLit (CmmInt shift_bits _)]) x
-            | shift_bits <= 3
-            = Just (x, y, shift_bits)
-          get_shift _ _
-            = Nothing
     add_code rep x y = trivialCode rep (ADD format) (Just (ADD format)) x y
       where format = intFormat rep
     -- TODO: There are other interesting patterns we want to replace
@@ -1085,7 +1066,6 @@ getRegister' _ is32Bit (CmmMachOp mop [x, y]) = -- dyadic MachOps
     sub_code rep x y = trivialCode rep (SUB (intFormat rep)) Nothing x y
 
     -- our three-operand add instruction:
-    add_int :: (Width -> CmmExpr -> Integer -> NatM Register)
     add_int width x y = do
         (x_reg, x_code) <- getSomeReg x
         let
@@ -1099,22 +1079,6 @@ getRegister' _ is32Bit (CmmMachOp mop [x, y]) = -- dyadic MachOps
         --
         return (Any format code)
 
-    -- x + (y << shift_bits) using LEA
-    add_shiftL :: (Width -> CmmExpr -> CmmExpr -> Int -> NatM Register)
-    add_shiftL width x y shift_bits = do
-        (x_reg, x_code) <- getSomeReg x
-        (y_reg, y_code) <- getSomeReg y
-        let
-            format = intFormat width
-            imm = ImmInt 0
-            code dst
-               = (x_code `appOL` y_code) `snocOL`
-                 LEA format
-                        (OpAddr (AddrBaseIndex (EABaseReg x_reg) (EAIndex y_reg (2 ^ shift_bits)) imm))
-                        (OpReg dst)
-        --
-        return (Any format code)
-
     ----------------------
 
     -- See Note [DIV/IDIV for bytes]


=====================================
compiler/GHC/Parser.y
=====================================
@@ -540,8 +540,9 @@ importdecls
 This might seem like an awfully roundabout way to declare a list; plus, to add
 insult to injury you have to reverse the results at the end.  The answer is that
 left recursion prevents us from running out of stack space when parsing long
-sequences.  See: https://www.haskell.org/happy/doc/html/sec-sequences.html for
-more guidance.
+sequences. See:
+https://haskell-happy.readthedocs.io/en/latest/using.html#parsing-sequences
+for more guidance.
 
 By adding/removing branches, you can affect what lists are accepted.  Here
 are the most common patterns, rewritten as regular expressions for clarity:


=====================================
configure.ac
=====================================
@@ -667,6 +667,8 @@ GHC_LLVM_TARGET_SET_VAR
 # we intend to pass trough --targets to llvm as is.
 LLVMTarget_CPP=`    echo "$LlvmTarget"`
 AC_SUBST(LLVMTarget_CPP)
+# The target is substituted into the distrib/configure.ac file
+AC_SUBST(LlvmTarget)
 
 dnl ** See whether cc supports --target=<triple> and set
 dnl CONF_CC_OPTS_STAGE[012] accordingly.


=====================================
distrib/configure.ac.in
=====================================
@@ -18,6 +18,8 @@ dnl--------------------------------------------------------------------
 dnl Various things from the source distribution configure
 bootstrap_target=@TargetPlatform@
 
+bootstrap_llvm_target=@LlvmTarget@
+
 TargetHasRTSLinker=@TargetHasRTSLinker@
 AC_SUBST(TargetHasRTSLinker)
 
@@ -169,6 +171,11 @@ FPTOOLS_SET_C_LD_FLAGS([target],[CONF_CC_OPTS_STAGE1],[CONF_GCC_LINKER_OPTS_STAG
 # Stage 3 won't be supported by cross-compilation
 FPTOOLS_SET_C_LD_FLAGS([target],[CONF_CC_OPTS_STAGE2],[CONF_GCC_LINKER_OPTS_STAGE2],[CONF_LD_LINKER_OPTS_STAGE2],[CONF_CPP_OPTS_STAGE2])
 
+FP_LD_NO_FIXUP_CHAINS([target], [LDFLAGS])
+FP_LD_NO_FIXUP_CHAINS([build], [CONF_GCC_LINKER_OPTS_STAGE0])
+FP_LD_NO_FIXUP_CHAINS([target], [CONF_GCC_LINKER_OPTS_STAGE1])
+FP_LD_NO_FIXUP_CHAINS([target], [CONF_GCC_LINKER_OPTS_STAGE2])
+
 AC_SUBST(CONF_CC_OPTS_STAGE0)
 AC_SUBST(CONF_CC_OPTS_STAGE1)
 AC_SUBST(CONF_CC_OPTS_STAGE2)


=====================================
hadrian/src/Base.hs
=====================================
@@ -20,9 +20,6 @@ module Base (
     module Stage,
     module Way,
 
-    -- * Files
-    configH,
-
     -- * Paths
     hadrianPath, configPath, configFile, sourcePath, shakeFilesDir,
     stageBinPath, stageLibPath, templateHscPath,
@@ -72,11 +69,6 @@ configFile = configPath -/- "system.config"
 sourcePath :: FilePath
 sourcePath = hadrianPath -/- "src"
 
--- TODO: Change @mk/config.h@ to @shake-build/cfg/config.h at .
--- | Path to the generated @mk/config.h@ file.
-configH :: FilePath
-configH = "mk/config.h"
-
 -- | The directory in 'buildRoot' containing the Shake database and other
 -- auxiliary files generated by Hadrian.
 shakeFilesDir :: FilePath


=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -147,7 +147,8 @@ generatePackageCode context@(Context stage pkg _ _) = do
         root -/- "**" -/- dir -/- "cmm/AutoApply.cmm" %> \file ->
             build $ target context GenApply [] [file]
         let go gen file = generate file (semiEmptyTarget stage) gen
-        root -/- "**" -/- dir -/- "include/ghcautoconf.h" %> go generateGhcAutoconfH
+        root -/- "**" -/- dir -/- "include/ghcautoconf.h" %> \_ ->
+            need . pure =<< pkgSetupConfigFile context
         root -/- "**" -/- dir -/- "include/ghcplatform.h" %> go generateGhcPlatformH
         root -/- "**" -/- dir -/- "include/DerivedConstants.h" %> genPlatformConstantsHeader context
         root -/- "**" -/- dir -/- "include/rts/EventLogConstants.h" %> genEventTypes "--event-types-defines"
@@ -486,26 +487,6 @@ generateConfigHs = do
     stageString (Stage0 GlobalLibs) = error "stageString: StageBoot"
 
 
--- | Generate @ghcautoconf.h@ header.
-generateGhcAutoconfH :: Expr String
-generateGhcAutoconfH = do
-    trackGenerateHs
-    configHContents  <- expr $ mapMaybe undefinePackage <$> readFileLines configH
-    return . unlines $
-        [ "#if !defined(__GHCAUTOCONF_H__)"
-        , "#define __GHCAUTOCONF_H__" ]
-        ++ configHContents ++
-        [ "#endif /* __GHCAUTOCONF_H__ */" ]
-  where
-    undefinePackage s
-        | "#define PACKAGE_" `isPrefixOf` s
-            = Just $ "/* #undef " ++ takeWhile (/=' ') (drop 8 s) ++ " */"
-        | "#define __GLASGOW_HASKELL" `isPrefixOf` s
-            = Nothing
-        | "/* REMOVE ME */" == s
-            = Nothing
-        | otherwise = Just s
-
 -- | Generate @Version.hs@ files.
 generateVersionHs :: Expr String
 generateVersionHs = do


=====================================
hadrian/src/Rules/Lint.hs
=====================================
@@ -11,13 +11,15 @@ lintRules :: Rules ()
 lintRules = do
   "lint:base" ~> lint base
   "lint:compiler" ~> lint compiler
+
+  -- Ensure that autoconf scripts, which are usually run by Cabal, are run to
+  -- avoid depending upon Cabal from the stage0 compiler..
   "libraries" -/- "base" -/- "include" -/- "HsBaseConfig.h" %> \_ ->
       -- ./configure is called here manually because we need to generate
       -- HsBaseConfig.h, which is created from HsBaseConfig.h.in. ./configure
-      -- is usually run by Cabal which generates this file but if we do that
-      -- then hadrian thinks it needs to build the stage0 compiler before
-      -- attempting to configure. Therefore we just run it directly here.
       cmd_ (Cwd "libraries/base") "./configure"
+  "rts" -/- "include" -/- "ghcautoconf.h" %> \_ ->
+      cmd_ (Cwd "rts") "./configure"
 
 lint :: Action () -> Action ()
 lint lintAction = do


=====================================
hadrian/src/Rules/Register.hs
=====================================
@@ -48,11 +48,9 @@ configurePackageRules = do
         when (pkg == rts) $ do
           -- Rts.h is a header listed in the cabal file, and configuring
           -- therefore wants to ensure that the header "works" post-configure.
-          -- But it (transitively) includes these, so we must ensure they exist
+          -- But it (transitively) includes this, so we must ensure it exists
           -- for that check to work.
-          need [ buildP -/- "include/ghcautoconf.h"
-               , buildP -/- "include/ghcplatform.h"
-               ]
+          need [buildP -/- "include/ghcplatform.h"]
         Cabal.configurePackage ctx
 
     root -/- "**/autogen/cabal_macros.h" %> \out -> do


=====================================
hadrian/src/Rules/SourceDist.hs
=====================================
@@ -142,7 +142,9 @@ prepareTree dest = do
       moveFile (dest -/- "boot") (dest -/- "boot.source")
 
     bootFiles =
-      [ pkgPath process -/- "include" -/- "HsProcessConfig.h.in"
+      [ pkgPath rts -/- "configure"
+      , pkgPath rts -/- "ghcautoconf.h.autoconf.in"
+      , pkgPath process -/- "include" -/- "HsProcessConfig.h.in"
       , pkgPath process -/- "configure"
       , pkgPath ghcBignum -/- "configure"
       , pkgPath base -/- "configure"


=====================================
libraries/base/.gitignore
=====================================
@@ -19,4 +19,3 @@
 /include/EventConfig.h
 /include/HsBaseConfig.h
 /include/HsBaseConfig.h.in
-


=====================================
libraries/base/Data/List.hs
=====================================
@@ -127,6 +127,7 @@ module Data.List
    -- | These functions treat a list @xs@ as a indexed collection,
    -- with indices ranging from 0 to @'length' xs - 1 at .
 
+   , (!?)
    , (!!)
 
    , elemIndex


=====================================
libraries/base/Data/OldList.hs
=====================================
@@ -127,6 +127,7 @@ module Data.OldList
    -- | These functions treat a list @xs@ as a indexed collection,
    -- with indices ranging from 0 to @'length' xs - 1 at .
 
+   , (!?)
    , (!!)
 
    , elemIndex


=====================================
libraries/base/GHC/List.hs
=====================================
@@ -31,7 +31,7 @@ module GHC.List (
    -- Other functions
    foldl1', concat, concatMap,
    map, (++), filter, lookup,
-   head, last, tail, init, uncons, (!!),
+   head, last, tail, init, uncons, (!?), (!!),
    scanl, scanl1, scanl', scanr, scanr1,
    iterate, iterate', repeat, replicate, cycle,
    take, drop, splitAt, takeWhile, dropWhile, span, break, reverse,
@@ -49,7 +49,7 @@ import GHC.Num (Num(..))
 import GHC.Num.Integer (Integer)
 import GHC.Stack.Types (HasCallStack)
 
-infixl 9  !!
+infixl 9  !?, !!
 infix  4 `elem`, `notElem`
 
 -- $setup
@@ -1370,9 +1370,10 @@ concat = foldr (++) []
 -- >>> ['a', 'b', 'c'] !! (-1)
 -- *** Exception: Prelude.!!: negative index
 --
--- WARNING: This function is partial. You can use
--- <https://hackage.haskell.org/package/safe/docs/Safe.html#v:atMay atMay>
--- instead.
+-- WARNING: This function is partial, and should only be used if you are
+-- sure that the indexing will not fail. Otherwise, use 'Data.List.!?'.
+--
+-- WARNING: This function takes linear time in the index.
 #if defined(USE_REPORT_PRELUDE)
 (!!)                    :: [a] -> Int -> a
 xs     !! n | n < 0 =  errorWithoutStackTrace "Prelude.!!: negative index"
@@ -1401,6 +1402,30 @@ xs !! n
                                    _ -> r (k-1)) tooLarge xs n
 #endif
 
+-- | List index (subscript) operator, starting from 0. Returns 'Nothing'
+-- if the index is out of bounds
+--
+-- >>> ['a', 'b', 'c'] !? 0
+-- Just 'a'
+-- >>> ['a', 'b', 'c'] !? 2
+-- Just 'c'
+-- >>> ['a', 'b', 'c'] !? 3
+-- Nothing
+-- >>> ['a', 'b', 'c'] !? (-1)
+-- Nothing
+--
+-- This is the total variant of the partial '!!' operator.
+--
+-- WARNING: This function takes linear time in the index.
+(!?) :: [a] -> Int -> Maybe a
+
+{-# INLINABLE (!?) #-}
+xs !? n
+  | n < 0     = Nothing
+  | otherwise = foldr (\x r k -> case k of
+                                   0 -> Just x
+                                   _ -> r (k-1)) (const Nothing) xs n
+
 --------------------------------------------------------------
 -- The zip family
 --------------------------------------------------------------


=====================================
libraries/base/changelog.md
=====================================
@@ -58,6 +58,8 @@
     freeing a `Pool`. (#14762) (#18338)
   * `Type.Reflection.Unsafe` is now marked as unsafe.
   * Add `Data.Typeable.heqT`, a kind-heterogeneous version of `Data.Typeable.eqT`.
+  * Add `Data.List.!?` per
+    [CLC proposal #110](https://github.com/haskell/core-libraries-committee/issues/110).
 
 ## 4.17.0.0 *August 2022*
 


=====================================
m4/fp_find_libdw.m4
=====================================
@@ -48,9 +48,6 @@ AC_DEFUN([FP_FIND_LIBDW],
   AC_SUBST(UseLibdw)
   if test $UseLibdw = "YES" ; then
     USE_LIBDW=1
-    AC_SUBST([CabalHaveLibdw],[True])
-  else
-    AC_SUBST([CabalHaveLibdw],[False])
   fi
   AC_DEFINE_UNQUOTED([USE_LIBDW], [$USE_LIBDW], [Set to 1 to use libdw])
 ])


=====================================
m4/ghc_llvm_target.m4
=====================================
@@ -50,5 +50,10 @@ AC_DEFUN([GHC_LLVM_TARGET], [
 # require it.
 AC_DEFUN([GHC_LLVM_TARGET_SET_VAR], [
   AC_REQUIRE([FPTOOLS_SET_PLATFORMS_VARS])
-  GHC_LLVM_TARGET([$target],[$target_cpu],[$target_vendor],[$target_os],[LlvmTarget])
+  if test "$bootstrap_llvm_target" != ""
+  then
+    LlvmTarget=$bootstrap_llvm_target
+  else
+    GHC_LLVM_TARGET([$target],[$target_cpu],[$target_vendor],[$target_os],[LlvmTarget])
+  fi
 ])


=====================================
rts/.gitignore
=====================================
@@ -12,7 +12,13 @@
 /package.conf.install.raw
 /fs.*
 
+/aclocal.m4
 /autom4te.cache/
 /config.log
 /config.status
 /configure
+
+/external-symbols.list
+/ghcautoconf.h.autoconf.in
+/ghcautoconf.h.autoconf
+/include/ghcautoconf.h


=====================================
rts/configure.ac
=====================================
@@ -0,0 +1,88 @@
+# Configure script template for the Run-time System of GHC
+#
+# Process with 'autoreconf' to get a working configure script.
+#
+# For the generated configure script, do "./configure --help" to
+# see what flags are available. (Better yet, read the documentation!)
+#
+
+AC_INIT([GHC run-time system], [1.0.2], [libraries at haskell.org], [rts])
+
+AC_CONFIG_MACRO_DIRS([../m4])
+
+# Safety check: Ensure that we are in the correct source directory.
+AC_CONFIG_SRCDIR([include/rts/Constants.h])
+
+dnl * We require autoconf version 2.69 due to
+dnl   https://bugs.ruby-lang.org/issues/8179. Also see #14910.
+dnl * We need 2.50 due to the use of AC_SYS_LARGEFILE and AC_MSG_NOTICE.
+dnl * We need 2.52 due to the use of AS_TR_CPP and AS_TR_SH.
+dnl * Using autoconf 2.59 started to give nonsense like this
+dnl     #define SIZEOF_CHAR 0
+dnl   recently.
+AC_PREREQ([2.69])
+
+AC_CONFIG_HEADERS([ghcautoconf.h.autoconf])
+
+# We have to run these unconditionally, but we may discard their
+# results in the following code
+AC_CANONICAL_BUILD
+AC_CANONICAL_HOST
+
+GHC_CONVERT_PLATFORM_PARTS([host], [Host])
+FPTOOLS_SET_PLATFORM_VARS([host], [Host])
+FPTOOLS_SET_HASKELL_PLATFORM_VARS([Host])
+
+AC_OUTPUT
+
+dnl ######################################################################
+dnl Generate ghcautoconf.h
+dnl ######################################################################
+
+[
+mkdir -p include
+touch include/ghcautoconf.h
+> include/ghcautoconf.h
+
+echo "#if !defined(__GHCAUTOCONF_H__)" >> include/ghcautoconf.h
+echo "#define __GHCAUTOCONF_H__" >> include/ghcautoconf.h
+# Copy the contents of $srcdir/../mk/config.h, turning '#define PACKAGE_FOO
+# "blah"' into '/* #undef PACKAGE_FOO */' to avoid clashes.
+cat $srcdir/../mk/config.h ghcautoconf.h.autoconf | sed \
+   -e 's,^\([	 ]*\)#[	 ]*define[	 ][	 ]*\(PACKAGE_[A-Z]*\)[	 ][ 	]*".*".*$,\1/* #undef \2 */,' \
+   -e '/__GLASGOW_HASKELL/d' \
+   -e '/REMOVE ME/d' \
+   >> include/ghcautoconf.h
+echo "#endif /* __GHCAUTOCONF_H__ */" >> include/ghcautoconf.h
+]
+
+dnl ######################################################################
+dnl Generate external symbol flags (-Wl,-u...)
+dnl ######################################################################
+
+dnl See Note [Undefined symbols in the RTS]
+
+cat $srcdir/external-symbols.list.in \
+    | "$CC" -E -P -traditional -Iinclude - -o - \
+    | sed '/^$/d' \
+    > external-symbols.list \
+    || exit 1
+
+mv external-symbols.list external-symbols.tmp
+if [[ -n "$LeadingUnderscore" ]]; then
+    sed 's/^/  -Wl,-u_/' external-symbols.tmp > external-symbols.list
+else
+    sed 's/^/  -Wl,-u/' external-symbols.tmp > external-symbols.list
+fi
+rm -f external-symbols.tmp
+
+dnl ######################################################################
+dnl Generate build-info
+dnl ######################################################################
+
+cat $srcdir/rts.buildinfo.in | \
+    sed -e 's/^  *//' | \
+    "$CC" -E -P -traditional - -o - \
+    > rts.buildinfo
+echo "" >> rts.buildinfo
+rm -f external-symbols.list


=====================================
rts/external-symbols.list.in
=====================================
@@ -0,0 +1,96 @@
+#include "ghcautoconf.h"
+
+#if 0
+See Note [Undefined symbols in the RTS]
+#endif
+
+#if SIZEOF_VOID_P == 8
+hs_atomic_add64
+hs_atomic_sub64
+hs_atomic_and64
+hs_atomic_nand64
+hs_atomic_or64
+hs_atomic_xor64
+hs_atomicread64
+hs_atomicwrite64
+#endif
+
+#if mingw32_HOST_OS
+base_GHCziEventziWindows_processRemoteCompletion_closure
+#endif
+
+base_GHCziTopHandler_runIO_closure
+base_GHCziTopHandler_runNonIO_closure
+ghczmprim_GHCziTupleziPrim_Z0T_closure
+ghczmprim_GHCziTypes_True_closure
+ghczmprim_GHCziTypes_False_closure
+base_GHCziPack_unpackCString_closure
+base_GHCziWeakziFinalizze_runFinalizzerBatch_closure
+base_GHCziIOziException_stackOverflow_closure
+base_GHCziIOziException_heapOverflow_closure
+base_GHCziIOziException_allocationLimitExceeded_closure
+base_GHCziIOziException_blockedIndefinitelyOnMVar_closure
+base_GHCziIOziException_blockedIndefinitelyOnSTM_closure
+base_GHCziIOziException_cannotCompactFunction_closure
+base_GHCziIOziException_cannotCompactPinned_closure
+base_GHCziIOziException_cannotCompactMutable_closure
+base_GHCziIOPort_doubleReadException_closure
+base_ControlziExceptionziBase_nonTermination_closure
+base_ControlziExceptionziBase_nestedAtomically_closure
+base_GHCziEventziThread_blockedOnBadFD_closure
+base_GHCziConcziSync_runSparks_closure
+base_GHCziConcziIO_ensureIOManagerIsRunning_closure
+base_GHCziConcziIO_interruptIOManager_closure
+base_GHCziConcziIO_ioManagerCapabilitiesChanged_closure
+base_GHCziConcziSignal_runHandlersPtr_closure
+base_GHCziTopHandler_flushStdHandles_closure
+base_GHCziTopHandler_runMainIO_closure
+ghczmprim_GHCziTypes_Czh_con_info
+ghczmprim_GHCziTypes_Izh_con_info
+ghczmprim_GHCziTypes_Fzh_con_info
+ghczmprim_GHCziTypes_Dzh_con_info
+ghczmprim_GHCziTypes_Wzh_con_info
+base_GHCziPtr_Ptr_con_info
+base_GHCziPtr_FunPtr_con_info
+base_GHCziInt_I8zh_con_info
+base_GHCziInt_I16zh_con_info
+base_GHCziInt_I32zh_con_info
+base_GHCziInt_I64zh_con_info
+base_GHCziWord_W8zh_con_info
+base_GHCziWord_W16zh_con_info
+base_GHCziWord_W32zh_con_info
+base_GHCziWord_W64zh_con_info
+base_GHCziStable_StablePtr_con_info
+hs_atomic_add8
+hs_atomic_add16
+hs_atomic_add32
+hs_atomic_sub8
+hs_atomic_sub16
+hs_atomic_sub32
+hs_atomic_and8
+hs_atomic_and16
+hs_atomic_and32
+hs_atomic_nand8
+hs_atomic_nand16
+hs_atomic_nand32
+hs_atomic_or8
+hs_atomic_or16
+hs_atomic_or32
+hs_atomic_xor8
+hs_atomic_xor16
+hs_atomic_xor32
+hs_cmpxchg8
+hs_cmpxchg16
+hs_cmpxchg32
+hs_cmpxchg64
+hs_xchg8
+hs_xchg16
+hs_xchg32
+hs_xchg64
+hs_atomicread8
+hs_atomicread16
+hs_atomicread32
+hs_atomicwrite8
+hs_atomicwrite16
+hs_atomicwrite32
+base_GHCziStackziCloneStack_StackSnapshot_closure


=====================================
rts/posix/OSThreads.c
=====================================
@@ -218,6 +218,12 @@ start_thread (void *param)
     return startProc(startParam);
 }
 
+/* Note: at least on Linux/Glibc, `pthread_setname_np` restricts the name of
+ * a thread to 16 bytes, including the terminating null byte. Hence, make sure
+ * to only pass in names of up to 15 characters. Otherwise,
+ * `pthread_setname_np` when called in `start_thread` will fail with `ERANGE`,
+ * which is not checked for, and the thread won't be named at all.
+ */
 int
 createOSThread (OSThreadId* pId, const char *name,
                 OSThreadProc *startProc, void *param)


=====================================
rts/rts.buildinfo.in
=====================================
@@ -0,0 +1,3 @@
+-- External symbols referenced by the RTS
+ld-options:
+#include "external-symbols.list"


=====================================
rts/rts.cabal.in
=====================================
@@ -1,9 +1,27 @@
 cabal-version: 3.0
 name: rts
 version: 1.0.2
+synopsis: The GHC runtime system
+description:
+    The GHC runtime system.
+
+    Code produced by GHC links this library to provide missing functionality
+    that cannot be written in Haskell itself.
 license: BSD-3-Clause
 maintainer: glasgow-haskell-users at haskell.org
-build-type: Simple
+build-type: Configure
+
+extra-source-files:
+    configure
+    configure.ac
+    external-symbols.list.in
+    rts.buildinfo.in
+
+extra-tmp-files:
+    autom4te.cache
+    rts.buildinfo
+    config.log
+    config.status
 
 source-repository head
     type:     git
@@ -206,6 +224,7 @@ library
 
       include-dirs: include
       includes: Rts.h
+      autogen-includes: ghcautoconf.h
       install-includes: Cmm.h HsFFI.h MachDeps.h Rts.h RtsAPI.h Stg.h
                         ghcautoconf.h ghcconfig.h ghcplatform.h ghcversion.h
                         -- ^ from include
@@ -277,201 +296,22 @@ library
                         stg/Types.h
 
       -- See Note [Undefined symbols in the RTS]
-      if flag(64bit)
-        if flag(leading-underscore)
-          ld-options:
-            "-Wl,-u,_hs_atomic_add64"
-            "-Wl,-u,_hs_atomic_sub64"
-            "-Wl,-u,_hs_atomic_and64"
-            "-Wl,-u,_hs_atomic_nand64"
-            "-Wl,-u,_hs_atomic_or64"
-            "-Wl,-u,_hs_atomic_xor64"
-            "-Wl,-u,_hs_atomicread64"
-            "-Wl,-u,_hs_atomicwrite64"
-        else
-          ld-options:
-            "-Wl,-u,hs_atomic_add64"
-            "-Wl,-u,hs_atomic_sub64"
-            "-Wl,-u,hs_atomic_and64"
-            "-Wl,-u,hs_atomic_nand64"
-            "-Wl,-u,hs_atomic_or64"
-            "-Wl,-u,hs_atomic_xor64"
-            "-Wl,-u,hs_atomicread64"
-            "-Wl,-u,hs_atomicwrite64"
+      --
+      -- We should handle this symbol with the others in the configure script
+      -- once we are using Cabal containing
+      -- https://github.com/haskell/cabal/pull/8565 /
+      -- 30f8a46008d164b5c4c6ce0b4453eb93eb5ef46c.
       if flag(leading-underscore)
-        ld-options:
-           "-Wl,-u,_base_GHCziTopHandler_runIO_closure"
-           "-Wl,-u,_base_GHCziTopHandler_runNonIO_closure"
-           "-Wl,-u,_ghczmprim_GHCziTupleziPrim_Z0T_closure"
-           "-Wl,-u,_ghczmprim_GHCziTypes_True_closure"
-           "-Wl,-u,_ghczmprim_GHCziTypes_False_closure"
-           "-Wl,-u,_base_GHCziPack_unpackCString_closure"
-           "-Wl,-u,_base_GHCziWeakziFinalizze_runFinalizzerBatch_closure"
-           "-Wl,-u,_base_GHCziIOziException_stackOverflow_closure"
-           "-Wl,-u,_base_GHCziIOziException_heapOverflow_closure"
-           "-Wl,-u,_base_GHCziIOziException_allocationLimitExceeded_closure"
-           "-Wl,-u,_base_GHCziIOziException_blockedIndefinitelyOnMVar_closure"
-           "-Wl,-u,_base_GHCziIOziException_blockedIndefinitelyOnSTM_closure"
-           "-Wl,-u,_base_GHCziIOziException_cannotCompactFunction_closure"
-           "-Wl,-u,_base_GHCziIOziException_cannotCompactPinned_closure"
-           "-Wl,-u,_base_GHCziIOziException_cannotCompactMutable_closure"
-           "-Wl,-u,_base_GHCziIOPort_doubleReadException_closure"
-           "-Wl,-u,_base_ControlziExceptionziBase_nonTermination_closure"
-           "-Wl,-u,_base_ControlziExceptionziBase_nestedAtomically_closure"
-           "-Wl,-u,_base_GHCziEventziThread_blockedOnBadFD_closure"
-           "-Wl,-u,_base_GHCziConcziSync_runSparks_closure"
-           "-Wl,-u,_base_GHCziConcziIO_ensureIOManagerIsRunning_closure"
-           "-Wl,-u,_base_GHCziConcziIO_interruptIOManager_closure"
-           "-Wl,-u,_base_GHCziConcziIO_ioManagerCapabilitiesChanged_closure"
-           "-Wl,-u,_base_GHCziConcziSignal_runHandlersPtr_closure"
-           "-Wl,-u,_base_GHCziTopHandler_flushStdHandles_closure"
-           "-Wl,-u,_base_GHCziTopHandler_runMainIO_closure"
-           "-Wl,-u,_ghczmprim_GHCziTypes_Czh_con_info"
-           "-Wl,-u,_ghczmprim_GHCziTypes_Izh_con_info"
-           "-Wl,-u,_ghczmprim_GHCziTypes_Fzh_con_info"
-           "-Wl,-u,_ghczmprim_GHCziTypes_Dzh_con_info"
-           "-Wl,-u,_ghczmprim_GHCziTypes_Wzh_con_info"
-           "-Wl,-u,_base_GHCziPtr_Ptr_con_info"
-           "-Wl,-u,_base_GHCziPtr_FunPtr_con_info"
-           "-Wl,-u,_base_GHCziInt_I8zh_con_info"
-           "-Wl,-u,_base_GHCziInt_I16zh_con_info"
-           "-Wl,-u,_base_GHCziInt_I32zh_con_info"
-           "-Wl,-u,_base_GHCziInt_I64zh_con_info"
-           "-Wl,-u,_base_GHCziWord_W8zh_con_info"
-           "-Wl,-u,_base_GHCziWord_W16zh_con_info"
-           "-Wl,-u,_base_GHCziWord_W32zh_con_info"
-           "-Wl,-u,_base_GHCziWord_W64zh_con_info"
-           "-Wl,-u,_base_GHCziStable_StablePtr_con_info"
-           "-Wl,-u,_hs_atomic_add8"
-           "-Wl,-u,_hs_atomic_add16"
-           "-Wl,-u,_hs_atomic_add32"
-           "-Wl,-u,_hs_atomic_sub8"
-           "-Wl,-u,_hs_atomic_sub16"
-           "-Wl,-u,_hs_atomic_sub32"
-           "-Wl,-u,_hs_atomic_and8"
-           "-Wl,-u,_hs_atomic_and16"
-           "-Wl,-u,_hs_atomic_and32"
-           "-Wl,-u,_hs_atomic_nand8"
-           "-Wl,-u,_hs_atomic_nand16"
-           "-Wl,-u,_hs_atomic_nand32"
-           "-Wl,-u,_hs_atomic_or8"
-           "-Wl,-u,_hs_atomic_or16"
-           "-Wl,-u,_hs_atomic_or32"
-           "-Wl,-u,_hs_atomic_xor8"
-           "-Wl,-u,_hs_atomic_xor16"
-           "-Wl,-u,_hs_atomic_xor32"
-           "-Wl,-u,_hs_cmpxchg8"
-           "-Wl,-u,_hs_cmpxchg16"
-           "-Wl,-u,_hs_cmpxchg32"
-           "-Wl,-u,_hs_cmpxchg64"
-           "-Wl,-u,_hs_xchg8"
-           "-Wl,-u,_hs_xchg16"
-           "-Wl,-u,_hs_xchg32"
-           "-Wl,-u,_hs_xchg64"
-           "-Wl,-u,_hs_atomicread8"
-           "-Wl,-u,_hs_atomicread16"
-           "-Wl,-u,_hs_atomicread32"
-           "-Wl,-u,_hs_atomicwrite8"
-           "-Wl,-u,_hs_atomicwrite16"
-           "-Wl,-u,_hs_atomicwrite32"
-           "-Wl,-u,_base_GHCziStackziCloneStack_StackSnapshot_closure"
-
         if flag(find-ptr)
           -- This symbol is useful in gdb, but not referred to anywhere,
           -- so we need to force it to be included in the binary.
           ld-options: "-Wl,-u,_findPtr"
-
       else
-        ld-options:
-           "-Wl,-u,base_GHCziTopHandler_runIO_closure"
-           "-Wl,-u,base_GHCziTopHandler_runNonIO_closure"
-           "-Wl,-u,ghczmprim_GHCziTupleziPrim_Z0T_closure"
-           "-Wl,-u,ghczmprim_GHCziTypes_True_closure"
-           "-Wl,-u,ghczmprim_GHCziTypes_False_closure"
-           "-Wl,-u,base_GHCziPack_unpackCString_closure"
-           "-Wl,-u,base_GHCziWeakziFinalizze_runFinalizzerBatch_closure"
-           "-Wl,-u,base_GHCziIOziException_stackOverflow_closure"
-           "-Wl,-u,base_GHCziIOziException_heapOverflow_closure"
-           "-Wl,-u,base_GHCziIOziException_allocationLimitExceeded_closure"
-           "-Wl,-u,base_GHCziIOziException_blockedIndefinitelyOnMVar_closure"
-           "-Wl,-u,base_GHCziIOziException_blockedIndefinitelyOnSTM_closure"
-           "-Wl,-u,base_GHCziIOziException_cannotCompactFunction_closure"
-           "-Wl,-u,base_GHCziIOziException_cannotCompactPinned_closure"
-           "-Wl,-u,base_GHCziIOziException_cannotCompactMutable_closure"
-           "-Wl,-u,base_GHCziIOPort_doubleReadException_closure"
-           "-Wl,-u,base_ControlziExceptionziBase_nonTermination_closure"
-           "-Wl,-u,base_ControlziExceptionziBase_nestedAtomically_closure"
-           "-Wl,-u,base_GHCziEventziThread_blockedOnBadFD_closure"
-           "-Wl,-u,base_GHCziConcziSync_runSparks_closure"
-           "-Wl,-u,base_GHCziConcziIO_ensureIOManagerIsRunning_closure"
-           "-Wl,-u,base_GHCziConcziIO_interruptIOManager_closure"
-           "-Wl,-u,base_GHCziConcziIO_ioManagerCapabilitiesChanged_closure"
-           "-Wl,-u,base_GHCziConcziSignal_runHandlersPtr_closure"
-           "-Wl,-u,base_GHCziTopHandler_flushStdHandles_closure"
-           "-Wl,-u,base_GHCziTopHandler_runMainIO_closure"
-           "-Wl,-u,ghczmprim_GHCziTypes_Czh_con_info"
-           "-Wl,-u,ghczmprim_GHCziTypes_Izh_con_info"
-           "-Wl,-u,ghczmprim_GHCziTypes_Fzh_con_info"
-           "-Wl,-u,ghczmprim_GHCziTypes_Dzh_con_info"
-           "-Wl,-u,ghczmprim_GHCziTypes_Wzh_con_info"
-           "-Wl,-u,base_GHCziPtr_Ptr_con_info"
-           "-Wl,-u,base_GHCziPtr_FunPtr_con_info"
-           "-Wl,-u,base_GHCziInt_I8zh_con_info"
-           "-Wl,-u,base_GHCziInt_I16zh_con_info"
-           "-Wl,-u,base_GHCziInt_I32zh_con_info"
-           "-Wl,-u,base_GHCziInt_I64zh_con_info"
-           "-Wl,-u,base_GHCziWord_W8zh_con_info"
-           "-Wl,-u,base_GHCziWord_W16zh_con_info"
-           "-Wl,-u,base_GHCziWord_W32zh_con_info"
-           "-Wl,-u,base_GHCziWord_W64zh_con_info"
-           "-Wl,-u,base_GHCziStable_StablePtr_con_info"
-           "-Wl,-u,hs_atomic_add8"
-           "-Wl,-u,hs_atomic_add16"
-           "-Wl,-u,hs_atomic_add32"
-           "-Wl,-u,hs_atomic_sub8"
-           "-Wl,-u,hs_atomic_sub16"
-           "-Wl,-u,hs_atomic_sub32"
-           "-Wl,-u,hs_atomic_and8"
-           "-Wl,-u,hs_atomic_and16"
-           "-Wl,-u,hs_atomic_and32"
-           "-Wl,-u,hs_atomic_nand8"
-           "-Wl,-u,hs_atomic_nand16"
-           "-Wl,-u,hs_atomic_nand32"
-           "-Wl,-u,hs_atomic_or8"
-           "-Wl,-u,hs_atomic_or16"
-           "-Wl,-u,hs_atomic_or32"
-           "-Wl,-u,hs_atomic_xor8"
-           "-Wl,-u,hs_atomic_xor16"
-           "-Wl,-u,hs_atomic_xor32"
-           "-Wl,-u,hs_cmpxchg8"
-           "-Wl,-u,hs_cmpxchg16"
-           "-Wl,-u,hs_cmpxchg32"
-           "-Wl,-u,hs_cmpxchg64"
-           "-Wl,-u,hs_xchg8"
-           "-Wl,-u,hs_xchg16"
-           "-Wl,-u,hs_xchg32"
-           "-Wl,-u,hs_xchg64"
-           "-Wl,-u,hs_atomicread8"
-           "-Wl,-u,hs_atomicread16"
-           "-Wl,-u,hs_atomicread32"
-           "-Wl,-u,hs_atomicwrite8"
-           "-Wl,-u,hs_atomicwrite16"
-           "-Wl,-u,hs_atomicwrite32"
-           "-Wl,-u,base_GHCziStackziCloneStack_StackSnapshot_closure"
-
         if flag(find-ptr)
           -- This symbol is useful in gdb, but not referred to anywhere,
           -- so we need to force it to be included in the binary.
           ld-options: "-Wl,-u,findPtr"
 
-      if os(windows)
-        if flag(leading-underscore)
-          ld-options:
-             "-Wl,-u,_base_GHCziEventziWindows_processRemoteCompletion_closure"
-        else
-          ld-options:
-             "-Wl,-u,base_GHCziEventziWindows_processRemoteCompletion_closure"
-
       if os(osx)
         ld-options: "-Wl,-search_paths_first"
                     -- See Note [fd_set_overflow]


=====================================
rts/sm/NonMoving.c
=====================================
@@ -1015,7 +1015,7 @@ void nonmovingCollect(StgWeak **dead_weaks, StgTSO **resurrected_threads)
         nonmoving_write_barrier_enabled = true;
         debugTrace(DEBUG_nonmoving_gc, "Starting concurrent mark thread");
         OSThreadId thread;
-        if (createOSThread(&thread, "non-moving mark thread",
+        if (createOSThread(&thread, "nonmoving-mark",
                            nonmovingConcurrentMark, mark_queue) != 0) {
             barf("nonmovingCollect: failed to spawn mark thread: %s", strerror(errno));
         }


=====================================
testsuite/tests/codeGen/should_gen_asm/AddMulX86.asm deleted
=====================================
@@ -1,46 +0,0 @@
-.section .text
-.align 8
-.align 8
-	.quad	8589934604
-	.quad	0
-	.long	14
-	.long	0
-.globl AddMulX86_f_info
-.type AddMulX86_f_info, @function
-AddMulX86_f_info:
-.LcAx:
-	leaq (%r14,%rsi,8),%rbx
-	jmp *(%rbp)
-	.size AddMulX86_f_info, .-AddMulX86_f_info
-.section .data
-.align 8
-.align 1
-.globl AddMulX86_f_closure
-.type AddMulX86_f_closure, @object
-AddMulX86_f_closure:
-	.quad	AddMulX86_f_info
-.section .text
-.align 8
-.align 8
-	.quad	8589934604
-	.quad	0
-	.long	14
-	.long	0
-.globl AddMulX86_g_info
-.type AddMulX86_g_info, @function
-AddMulX86_g_info:
-.LcAL:
-	leaq (%r14,%rsi,8),%rbx
-	jmp *(%rbp)
-	.size AddMulX86_g_info, .-AddMulX86_g_info
-.section .data
-.align 8
-.align 1
-.globl AddMulX86_g_closure
-.type AddMulX86_g_closure, @object
-AddMulX86_g_closure:
-	.quad	AddMulX86_g_info
-.section .note.GNU-stack,"", at progbits
-.ident "GHC 9.3.20220228"
-
-


=====================================
testsuite/tests/codeGen/should_gen_asm/AddMulX86.hs deleted
=====================================
@@ -1,12 +0,0 @@
-{-# LANGUAGE MagicHash #-}
-
-module AddMulX86 where
-
-import GHC.Exts
-
-f :: Int# -> Int# -> Int#
-f x y =
-    x +# (y *# 8#) -- Should result in a lea instruction, which we grep the assembly output for.
-
-g x y =
-    (y *# 8#) +# x  -- Should result in a lea instruction, which we grep the assembly output for.


=====================================
testsuite/tests/codeGen/should_gen_asm/all.T
=====================================
@@ -10,4 +10,3 @@ test('memset-unroll', is_amd64_codegen, compile_cmp_asm, ['cmm', ''])
 test('bytearray-memset-unroll', is_amd64_codegen, compile_grep_asm, ['hs', True, ''])
 test('bytearray-memcpy-unroll', is_amd64_codegen, compile_grep_asm, ['hs', True, ''])
 test('T18137', [when(opsys('darwin'), skip), only_ways(llvm_ways)], compile_grep_asm, ['hs', False, '-fllvm -split-sections'])
-test('AddMulX86', is_amd64_codegen, compile_cmp_asm, ['hs', '-dno-typeable-binds'])


=====================================
testsuite/tests/rts/pause-resume/pause_resume.c
=====================================
@@ -187,7 +187,7 @@ void pauseAndResumeViaThread
     )
 {
     OSThreadId threadId;
-    createOSThread(&threadId, "Pause and resume thread", &pauseAndResumeViaThread_helper, (void *)count);
+    createOSThread(&threadId, "pause-resume", &pauseAndResumeViaThread_helper, (void *)count);
 }
 
 const int TIMEOUT = 1000000; // 1 second



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a5f611a4c4564bb1f9b5fd856279f7e3608b82d7...af547008235a83b95bf28cebb634bf4ace33d672

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a5f611a4c4564bb1f9b5fd856279f7e3608b82d7...af547008235a83b95bf28cebb634bf4ace33d672
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/20230110/dda61d81/attachment-0001.html>


More information about the ghc-commits mailing list