[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 7 commits: RTS configure: Move over mem management checks

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Wed Oct 11 17:32:52 UTC 2023



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


Commits:
96862350 by John Ericson at 2023-10-11T13:32:01-04:00
RTS configure: Move over mem management checks

These are for heap allocation, a strictly RTS concern.

All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it
belongs in the RTS configure and should be safe to move without
modification.

The RTS configure one has a new
```
AC_CHECK_SIZEOF([void *])
```
that the top-level configure version didn't have, so that
`ac_cv_sizeof_void_p` is defined. Once more code is moved over in latter
commits, that can go away.

Progress towards #17191

- - - - -
6f66c263 by John Ericson at 2023-10-11T13:32:01-04:00
RTS configure: Move over `__thread` check

This used by (@bgamari thinks) the `GCThread` abstraction in the RTS.

All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it
belongs in the RTS configure and should be safe to move without
modification.

Progress towards #17191

- - - - -
93abd966 by John Ericson at 2023-10-11T13:32:02-04:00
RTS configure: Move over misc function checks

These are for general use in the RTS.

All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it
belongs in the RTS configure and should be safe to move without
modification.

Progress towards #17191

- - - - -
876555ef by John Ericson at 2023-10-11T13:32:02-04:00
RTS configure: Move over `eventfd` check

This check is for the RTS part of the event manager and has a
corresponding part in `base`.

All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it
belongs in the RTS configure and should be safe to move without
modification.

Progress towards #17191

- - - - -
f8ddb0b4 by John Ericson at 2023-10-11T13:32:02-04:00
Split `FP_CHECK_PTHREADS` and move part to RTS configure

`NEED_PTHREAD_LIB` is unused since
3609340743c1b25fdfd0e18b1670dac54c8d8623 (part of the make build
system), and so is no longer defined.

Progress towards #17191

- - - - -
334f3275 by Moritz Angermann at 2023-10-11T13:32:03-04:00
nativeGen: section flags for .text$foo only

Commit 3ece9856d157c85511d59f9f862ab351bbd9b38b, was supposed to fix
#22834 in !9810.

It does however add "xr" indiscriminatly to .text sections
even if splitSections is disabled. This leads to the assembler saying:

ghc_1.s:7849:0: error:
     Warning: Ignoring changed section attributes for .text
     |
7849 | .section .text,"xr"
     | ^

- - - - -
bc874842 by Sylvain Henry at 2023-10-11T13:32:05-04:00
Modularity: pass TempDir instead of DynFlags (#17957)

- - - - -


6 changed files:

- compiler/GHC/CmmToAsm/Ppr.hs
- compiler/GHC/SysTools/Process.hs
- compiler/GHC/SysTools/Tasks.hs
- configure.ac
- m4/fp_check_pthreads.m4
- rts/configure.ac


Changes:

=====================================
compiler/GHC/CmmToAsm/Ppr.hs
=====================================
@@ -246,9 +246,10 @@ pprGNUSectionHeader config t suffix =
         panic "PprBase.pprGNUSectionHeader: unknown section type"
     flags = case t of
       Text
-        | OSMinGW32 <- platformOS platform
+        | OSMinGW32 <- platformOS platform, splitSections
                     -> text ",\"xr\""
-        | otherwise -> text ",\"ax\"," <> sectionType platform "progbits"
+        | splitSections
+                    -> text ",\"ax\"," <> sectionType platform "progbits"
       CString
         | OSMinGW32 <- platformOS platform
                     -> empty


=====================================
compiler/GHC/SysTools/Process.hs
=====================================
@@ -10,14 +10,14 @@ module GHC.SysTools.Process where
 
 import GHC.Prelude
 
-import GHC.Driver.DynFlags
-
 import GHC.Utils.Exception
 import GHC.Utils.Error
 import GHC.Utils.Outputable
 import GHC.Utils.Panic
 import GHC.Utils.Misc
 import GHC.Utils.Logger
+import GHC.Utils.TmpFs
+import GHC.Utils.CliOption
 
 import GHC.Types.SrcLoc ( SrcLoc, mkSrcLoc, mkSrcSpan )
 import GHC.Data.FastString
@@ -32,7 +32,6 @@ import System.IO
 import System.IO.Error as IO
 import System.Process
 
-import GHC.Utils.TmpFs
 
 -- | Enable process jobs support on Windows if it can be expected to work (e.g.
 -- @process >= 1.6.9.0@).
@@ -153,14 +152,14 @@ runSomething logger phase_name pgm args =
 runSomethingResponseFile
   :: Logger
   -> TmpFs
-  -> DynFlags
+  -> TempDir
   -> (String->String)
   -> String
   -> String
   -> [Option]
   -> Maybe [(String,String)]
   -> IO ()
-runSomethingResponseFile logger tmpfs dflags filter_fn phase_name pgm args mb_env =
+runSomethingResponseFile logger tmpfs tmp_dir filter_fn phase_name pgm args mb_env =
     runSomethingWith logger phase_name pgm args $ \real_args -> do
         fp <- getResponseFile real_args
         let args = ['@':fp]
@@ -168,7 +167,7 @@ runSomethingResponseFile logger tmpfs dflags filter_fn phase_name pgm args mb_en
         return (r,())
   where
     getResponseFile args = do
-      fp <- newTempName logger tmpfs (tmpDir dflags) TFL_CurrentModule "rsp"
+      fp <- newTempName logger tmpfs tmp_dir TFL_CurrentModule "rsp"
       withFile fp WriteMode $ \h -> do
           hSetEncoding h utf8
           hPutStr h $ unlines $ map escape args


=====================================
compiler/GHC/SysTools/Tasks.hs
=====================================
@@ -117,7 +117,7 @@ runCpp logger tmpfs dflags args = traceSystoolCommand logger "cpp" $ do
       userOpts_c = map Option $ getOpts dflags opt_c
       args2 = args0 ++ args ++ userOpts_c
   mb_env <- getGccEnv args2
-  runSomethingResponseFile logger tmpfs dflags cc_filter "C pre-processor" p
+  runSomethingResponseFile logger tmpfs (tmpDir dflags) cc_filter "C pre-processor" p
                            args2 mb_env
 
 -- | Run the Haskell C preprocessor.
@@ -148,7 +148,7 @@ runCc mLanguage logger tmpfs dflags args = traceSystoolCommand logger "cc" $ do
       -- We take care to pass -optc flags in args1 last to ensure that the
       -- user can override flags passed by GHC. See #14452.
   mb_env <- getGccEnv args2
-  runSomethingResponseFile logger tmpfs dflags cc_filter dbgstring prog args2
+  runSomethingResponseFile logger tmpfs (tmpDir dflags) cc_filter dbgstring prog args2
                            mb_env
  where
   -- force the C compiler to interpret this file as C when
@@ -275,7 +275,7 @@ runLink logger tmpfs dflags args = traceSystoolCommand logger "linker" $ do
       optl_args = map Option (getOpts dflags opt_l)
       args2     = args0 ++ args ++ optl_args
   mb_env <- getGccEnv args2
-  runSomethingResponseFile logger tmpfs dflags ld_filter "Linker" p args2 mb_env
+  runSomethingResponseFile logger tmpfs (tmpDir dflags) ld_filter "Linker" p args2 mb_env
   where
     ld_filter = case (platformOS (targetPlatform dflags)) of
                   OSSolaris2 -> sunos_ld_filter
@@ -339,7 +339,7 @@ runMergeObjects logger tmpfs dflags args =
     if toolSettings_mergeObjsSupportsResponseFiles (toolSettings dflags)
       then do
         mb_env <- getGccEnv args2
-        runSomethingResponseFile logger tmpfs dflags id "Merge objects" p args2 mb_env
+        runSomethingResponseFile logger tmpfs (tmpDir dflags) id "Merge objects" p args2 mb_env
       else do
         runSomething logger "Merge objects" p args2
 


=====================================
configure.ac
=====================================
@@ -1038,81 +1038,8 @@ AC_LINK_IFELSE([AC_LANG_CALL([], [printf\$LDBLStub])],
             [Define to 1 if we have printf$LDBLStub (Apple Mac OS >= 10.4, PPC).])
     ])
 
-FP_CHECK_PTHREADS
-
-dnl ** check for eventfd which is needed by the I/O manager
-AC_CHECK_HEADERS([sys/eventfd.h])
-AC_CHECK_FUNCS([eventfd])
-
-AC_CHECK_FUNCS([getpid getuid raise])
-
-dnl ** Check for __thread support in the compiler
-AC_MSG_CHECKING(for __thread support)
-AC_COMPILE_IFELSE(
-  [ AC_LANG_SOURCE([[__thread int tester = 0;]]) ],
-  [
-   AC_MSG_RESULT(yes)
-   AC_DEFINE([CC_SUPPORTS_TLS],[1],[Define to 1 if __thread is supported])
-  ],
-  [
-   AC_MSG_RESULT(no)
-   AC_DEFINE([CC_SUPPORTS_TLS],[0],[Define to 1 if __thread is supported])
-  ])
-
-dnl large address space support (see rts/include/rts/storage/MBlock.h)
-dnl
-dnl Darwin has vm_allocate/vm_protect
-dnl Linux has mmap(MAP_NORESERVE)/madv(MADV_DONTNEED)
-dnl FreeBSD, Solaris and maybe other have MAP_NORESERVE/MADV_FREE
-dnl (They also have MADV_DONTNEED, but it means something else!)
-dnl
-dnl Windows has VirtualAlloc MEM_RESERVE/MEM_COMMIT, however
-dnl it counts page-table space as committed memory, and so quickly
-dnl runs out of paging file when we have multiple processes reserving
-dnl 1TB of address space, we get the following error:
-dnl    VirtualAlloc MEM_RESERVE 1099512676352 bytes failed: The paging file is too small for this operation to complete.
-dnl
-
-AC_ARG_ENABLE(large-address-space,
-    [AS_HELP_STRING([--enable-large-address-space],
-        [Use a single large address space on 64 bit systems (enabled by default on 64 bit platforms)])],
-    EnableLargeAddressSpace=$enableval,
-    EnableLargeAddressSpace=yes
-)
-
-use_large_address_space=no
-if test "$ac_cv_sizeof_void_p" -eq 8 ; then
-    if test "x$EnableLargeAddressSpace" = "xyes" ; then
-        if test "$ghc_host_os" = "darwin" ; then
-            use_large_address_space=yes
-        elif test "$ghc_host_os" = "openbsd" ; then
-            # as of OpenBSD 5.8 (2015), OpenBSD does not support mmap with MAP_NORESERVE.
-            # The flag MAP_NORESERVE is supported for source compatibility reasons,
-            # but is completely ignored by OS mmap
-                  use_large_address_space=no
-        elif test "$ghc_host_os" = "mingw32" ; then
-            # as of Windows 8.1/Server 2012 windows does no longer allocate the page
-            # tabe for reserved memory eagerly. So we are now free to use LAS there too.
-                  use_large_address_space=yes
-        else
-            AC_CHECK_DECLS([MAP_NORESERVE, MADV_FREE, MADV_DONTNEED],[],[],
-                [
-                #include <unistd.h>
-                #include <sys/types.h>
-                #include <sys/mman.h>
-                #include <fcntl.h>
-            ])
-            if test "$ac_cv_have_decl_MAP_NORESERVE" = "yes" &&
-                test "$ac_cv_have_decl_MADV_FREE" = "yes" ||
-                test "$ac_cv_have_decl_MADV_DONTNEED" = "yes" ; then
-                    use_large_address_space=yes
-            fi
-        fi
-    fi
-fi
-if test "$use_large_address_space" = "yes" ; then
-   AC_DEFINE([USE_LARGE_ADDRESS_SPACE], [1], [Enable single heap address space support])
-fi
+FP_CHECK_PTHREAD_LIB
+AC_SUBST([UseLibpthread])
 
 GHC_ADJUSTORS_METHOD([Target])
 AC_SUBST([UseLibffiForAdjustors])


=====================================
m4/fp_check_pthreads.m4
=====================================
@@ -1,7 +1,10 @@
-dnl FP_CHECK_PTHREADS
-dnl ----------------------------------
-dnl Check various aspects of the platform's pthreads support
-AC_DEFUN([FP_CHECK_PTHREADS],
+# FP_CHECK_PTHREAD_LIB
+# ----------------------------------
+# Check whether -lpthread is needed for pthread.
+#
+# Sets variables:
+#   - UseLibpthread: [YES|NO]
+AC_DEFUN([FP_CHECK_PTHREAD_LIB],
 [
   dnl Some platforms (e.g. Android's Bionic) have pthreads support available
   dnl without linking against libpthread. Check whether -lpthread is necessary
@@ -12,25 +15,28 @@ AC_DEFUN([FP_CHECK_PTHREADS],
   AC_CHECK_FUNC(pthread_create,
       [
           AC_MSG_RESULT(no)
-          AC_SUBST([UseLibpthread],[NO])
-          need_lpthread=0
+          UseLibpthread=NO
       ],
       [
           AC_CHECK_LIB(pthread, pthread_create,
               [
                   AC_MSG_RESULT(yes)
-                  AC_SUBST([UseLibpthread],[YES])
-                  need_lpthread=1
+                  UseLibpthread=YES
               ],
               [
-                  AC_SUBST([UseLibpthread],[NO])
                   AC_MSG_RESULT([no pthreads support found.])
-                  need_lpthread=0
+                  UseLibpthread=NO
               ])
       ])
-  AC_DEFINE_UNQUOTED([NEED_PTHREAD_LIB], [$need_lpthread],
-      [Define 1 if we need to link code using pthreads with -lpthread])
+])
 
+# FP_CHECK_PTHREAD_FUNCS
+# ----------------------------------
+# Check various aspects of the platform's pthreads support
+#
+# `AC_DEFINE`s various C `HAVE_*` macros.
+AC_DEFUN([FP_CHECK_PTHREAD_FUNCS],
+[
   dnl Setting thread names
   dnl ~~~~~~~~~~~~~~~~~~~~
   dnl The portability situation here is complicated:


=====================================
rts/configure.ac
=====================================
@@ -33,6 +33,83 @@ GHC_CONVERT_PLATFORM_PARTS([host], [Host])
 FPTOOLS_SET_PLATFORM_VARS([host], [Host])
 FPTOOLS_SET_HASKELL_PLATFORM_VARS([Host])
 
+FP_CHECK_PTHREAD_FUNCS
+
+dnl ** check for eventfd which is needed by the I/O manager
+AC_CHECK_HEADERS([sys/eventfd.h])
+AC_CHECK_FUNCS([eventfd])
+
+AC_CHECK_FUNCS([getpid getuid raise])
+
+dnl ** Check for __thread support in the compiler
+AC_MSG_CHECKING(for __thread support)
+AC_COMPILE_IFELSE(
+  [ AC_LANG_SOURCE([[__thread int tester = 0;]]) ],
+  [
+   AC_MSG_RESULT(yes)
+   AC_DEFINE([CC_SUPPORTS_TLS],[1],[Define to 1 if __thread is supported])
+  ],
+  [
+   AC_MSG_RESULT(no)
+   AC_DEFINE([CC_SUPPORTS_TLS],[0],[Define to 1 if __thread is supported])
+  ])
+
+dnl large address space support (see rts/include/rts/storage/MBlock.h)
+dnl
+dnl Darwin has vm_allocate/vm_protect
+dnl Linux has mmap(MAP_NORESERVE)/madv(MADV_DONTNEED)
+dnl FreeBSD, Solaris and maybe other have MAP_NORESERVE/MADV_FREE
+dnl (They also have MADV_DONTNEED, but it means something else!)
+dnl
+dnl Windows has VirtualAlloc MEM_RESERVE/MEM_COMMIT, however
+dnl it counts page-table space as committed memory, and so quickly
+dnl runs out of paging file when we have multiple processes reserving
+dnl 1TB of address space, we get the following error:
+dnl    VirtualAlloc MEM_RESERVE 1099512676352 bytes failed: The paging file is too small for this operation to complete.
+dnl
+
+AC_ARG_ENABLE(large-address-space,
+    [AS_HELP_STRING([--enable-large-address-space],
+        [Use a single large address space on 64 bit systems (enabled by default on 64 bit platforms)])],
+    EnableLargeAddressSpace=$enableval,
+    EnableLargeAddressSpace=yes
+)
+
+use_large_address_space=no
+AC_CHECK_SIZEOF([void *])
+if test "$ac_cv_sizeof_void_p" -eq 8 ; then
+    if test "x$EnableLargeAddressSpace" = "xyes" ; then
+        if test "$ghc_host_os" = "darwin" ; then
+            use_large_address_space=yes
+        elif test "$ghc_host_os" = "openbsd" ; then
+            # as of OpenBSD 5.8 (2015), OpenBSD does not support mmap with MAP_NORESERVE.
+            # The flag MAP_NORESERVE is supported for source compatibility reasons,
+            # but is completely ignored by OS mmap
+                  use_large_address_space=no
+        elif test "$ghc_host_os" = "mingw32" ; then
+            # as of Windows 8.1/Server 2012 windows does no longer allocate the page
+            # tabe for reserved memory eagerly. So we are now free to use LAS there too.
+                  use_large_address_space=yes
+        else
+            AC_CHECK_DECLS([MAP_NORESERVE, MADV_FREE, MADV_DONTNEED],[],[],
+                [
+                #include <unistd.h>
+                #include <sys/types.h>
+                #include <sys/mman.h>
+                #include <fcntl.h>
+            ])
+            if test "$ac_cv_have_decl_MAP_NORESERVE" = "yes" &&
+                test "$ac_cv_have_decl_MADV_FREE" = "yes" ||
+                test "$ac_cv_have_decl_MADV_DONTNEED" = "yes" ; then
+                    use_large_address_space=yes
+            fi
+        fi
+    fi
+fi
+if test "$use_large_address_space" = "yes" ; then
+   AC_DEFINE([USE_LARGE_ADDRESS_SPACE], [1], [Enable single heap address space support])
+fi
+
 dnl ** Use MMAP in the runtime linker?
 dnl --------------------------------------------------------------
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/96f85149d5e596dee9d188a2c0e34f825b1ce60d...bc87484224c08772bc78a0ba774c95a9665f1c3f

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/96f85149d5e596dee9d188a2c0e34f825b1ce60d...bc87484224c08772bc78a0ba774c95a9665f1c3f
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/20231011/b6574a91/attachment-0001.html>


More information about the ghc-commits mailing list