[Git][ghc/ghc][wip/rts-configure-2] rts configure script

Ben Gamari (@bgamari) gitlab at gitlab.haskell.org
Mon Oct 31 13:51:39 UTC 2022



Ben Gamari pushed to branch wip/rts-configure-2 at Glasgow Haskell Compiler / GHC


Commits:
645faebe by Ben Gamari at 2022-10-31T09:51:21-04:00
rts configure script

- - - - -


26 changed files:

- boot
- compiler/GHC/Linker/Dynamic.hs
- compiler/GHC/Linker/Static.hs
- compiler/GHC/Platform.hs
- compiler/GHC/Settings/IO.hs
- configure.ac
- distrib/configure.ac.in
- hadrian/bindist/Makefile
- hadrian/bindist/config.mk.in
- hadrian/cabal.project
- hadrian/cfg/system.config.in
- hadrian/hadrian.cabal
- hadrian/src/Oracles/Flag.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Rules/Lint.hs
- hadrian/src/Settings/Packages.hs
- libraries/Cabal
- rts/.gitignore
- + rts/configure.ac
- + rts/external-symbols.list.in
- m4/fp_musttail.m4 → rts/m4/fp_musttail.m4
- m4/fp_visibility_hidden.m4 → rts/m4/fp_visibility_hidden.m4
- rts/package.conf.in
- rts/posix/OSThreads.c
- + rts/rts.buildinfo.in
- rts/rts.cabal.in


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/Linker/Dynamic.hs
=====================================
@@ -3,8 +3,6 @@
 -- | Dynamic linker
 module GHC.Linker.Dynamic
    ( linkDynLib
-   -- * Platform-specifics
-   , libmLinkOpts
    )
 where
 
@@ -210,7 +208,6 @@ linkDynLib logger tmpfs dflags0 unit_env o_files dep_packages
 
             runLink logger tmpfs dflags (
                     map Option verbFlags
-                 ++ libmLinkOpts platform
                  ++ [ Option "-o"
                     , FileOption "" output_fn
                     ]
@@ -226,13 +223,6 @@ linkDynLib logger tmpfs dflags0 unit_env o_files dep_packages
                  ++ map Option pkg_link_opts
               )
 
--- | Some platforms require that we explicitly link against @libm@ if any
--- math-y things are used (which we assume to include all programs). See #14022.
-libmLinkOpts :: Platform -> [Option]
-libmLinkOpts platform
-  | platformHasLibm platform = [Option "-lm"]
-  | otherwise                = []
-
 {-
 Note [-Bsymbolic assumptions by GHC]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~


=====================================
compiler/GHC/Linker/Static.hs
=====================================
@@ -188,7 +188,6 @@ linkBinary logger tmpfs dflags unit_env o_files dep_units = do
                       ++ [ GHC.SysTools.Option "-o"
                          , GHC.SysTools.FileOption "" output_fn
                          ]
-                      ++ libmLinkOpts platform
                       ++ map GHC.SysTools.Option (
                          []
 


=====================================
compiler/GHC/Platform.hs
=====================================
@@ -79,10 +79,6 @@ data Platform = Platform
       -- ^ Determines whether we will be compiling info tables that reside just
       --   before the entry code, or with an indirection to the entry code. See
       --   TABLES_NEXT_TO_CODE in rts/include/rts/storage/InfoTables.h.
-   , platformHasLibm                  :: !Bool
-      -- ^ Some platforms require that we explicitly link against @libm@ if any
-      -- math-y things are used (which we assume to include all programs). See
-      -- #14022.
 
    , platform_constants               :: !(Maybe PlatformConstants)
       -- ^ Constants such as structure offsets, type sizes, etc.
@@ -136,7 +132,6 @@ genericPlatform = Platform
    , platformHasGnuNonexecStack      = False
    , platformHasIdentDirective       = False
    , platformHasSubsectionsViaSymbols= False
-   , platformHasLibm                 = False
    , platformIsCrossCompiling        = False
    , platformLeadingUnderscore       = False
    , platformTablesNextToCode        = True


=====================================
compiler/GHC/Settings/IO.hs
=====================================
@@ -234,7 +234,6 @@ getTargetPlatform settingsFile settings = do
   targetHasGnuNonexecStack <- getBooleanSetting "target has GNU nonexec stack"
   targetHasIdentDirective <- getBooleanSetting "target has .ident directive"
   targetHasSubsectionsViaSymbols <- getBooleanSetting "target has subsections via symbols"
-  targetHasLibm <- getBooleanSetting "target has libm"
   crossCompiling <- getBooleanSetting "cross compiling"
   tablesNextToCode <- getBooleanSetting "Tables next to code"
 
@@ -249,6 +248,5 @@ getTargetPlatform settingsFile settings = do
     , platformIsCrossCompiling = crossCompiling
     , platformLeadingUnderscore = targetLeadingUnderscore
     , platformTablesNextToCode  = tablesNextToCode
-    , platformHasLibm = targetHasLibm
     , platform_constants = Nothing -- will be filled later when loading (or building) the RTS unit
     }


=====================================
configure.ac
=====================================
@@ -845,48 +845,11 @@ dnl    off_t, because it will affect the result of that test.
 AC_SYS_LARGEFILE
 
 dnl ** check for specific header (.h) files that we are interested in
-AC_CHECK_HEADERS([ctype.h dirent.h dlfcn.h errno.h fcntl.h grp.h limits.h locale.h nlist.h pthread.h pwd.h signal.h sys/param.h sys/mman.h sys/resource.h sys/select.h sys/time.h sys/timeb.h sys/timerfd.h sys/timers.h sys/times.h sys/utsname.h sys/wait.h termios.h utime.h windows.h winsock.h sched.h])
-
-dnl sys/cpuset.h needs sys/param.h to be included first on FreeBSD 9.1; #7708
-AC_CHECK_HEADERS([sys/cpuset.h], [], [],
-[[#if HAVE_SYS_PARAM_H
-# include <sys/param.h>
-#endif
-]])
-
-dnl ** check whether a declaration for `environ` is provided by libc.
-FP_CHECK_ENVIRON
 
 dnl ** do we have long longs?
 AC_CHECK_TYPES([long long])
 
 dnl ** what are the sizes of various types
-FP_CHECK_SIZEOF_AND_ALIGNMENT(char)
-FP_CHECK_SIZEOF_AND_ALIGNMENT(double)
-FP_CHECK_SIZEOF_AND_ALIGNMENT(float)
-FP_CHECK_SIZEOF_AND_ALIGNMENT(int)
-FP_CHECK_SIZEOF_AND_ALIGNMENT(long)
-if test "$ac_cv_type_long_long" = yes; then
-FP_CHECK_SIZEOF_AND_ALIGNMENT(long long)
-fi
-FP_CHECK_SIZEOF_AND_ALIGNMENT(short)
-FP_CHECK_SIZEOF_AND_ALIGNMENT(unsigned char)
-FP_CHECK_SIZEOF_AND_ALIGNMENT(unsigned int)
-FP_CHECK_SIZEOF_AND_ALIGNMENT(unsigned long)
-if test "$ac_cv_type_long_long" = yes; then
-FP_CHECK_SIZEOF_AND_ALIGNMENT(unsigned long long)
-fi
-FP_CHECK_SIZEOF_AND_ALIGNMENT(unsigned short)
-FP_CHECK_SIZEOF_AND_ALIGNMENT(void *)
-
-FP_CHECK_SIZEOF_AND_ALIGNMENT(int8_t)
-FP_CHECK_SIZEOF_AND_ALIGNMENT(uint8_t)
-FP_CHECK_SIZEOF_AND_ALIGNMENT(int16_t)
-FP_CHECK_SIZEOF_AND_ALIGNMENT(uint16_t)
-FP_CHECK_SIZEOF_AND_ALIGNMENT(int32_t)
-FP_CHECK_SIZEOF_AND_ALIGNMENT(uint32_t)
-FP_CHECK_SIZEOF_AND_ALIGNMENT(int64_t)
-FP_CHECK_SIZEOF_AND_ALIGNMENT(uint64_t)
 
 
 dnl for use in settings file
@@ -901,16 +864,6 @@ AC_SUBST(TargetWordSize)
 AC_C_BIGENDIAN([TargetWordBigEndian=YES],[TargetWordBigEndian=NO])
 AC_SUBST(TargetWordBigEndian)
 
-FP_CHECK_FUNC([WinExec],
-  [@%:@include <windows.h>], [WinExec("",0)])
-
-FP_CHECK_FUNC([GetModuleFileName],
-  [@%:@include <windows.h>], [GetModuleFileName((HMODULE)0,(LPTSTR)0,0)])
-
-dnl ** check for more functions
-dnl ** The following have been verified to be used in ghc/, but might be used somewhere else, too.
-AC_CHECK_FUNCS([getclock getrusage gettimeofday setitimer siginterrupt sysconf times ctime_r sched_setaffinity sched_getaffinity setlocale uselocale])
-
 dnl ** On OS X 10.4 (at least), time.h doesn't declare ctime_r if
 dnl ** _POSIX_C_SOURCE is defined
 AC_CHECK_DECLS([ctime_r], , ,
@@ -918,38 +871,6 @@ AC_CHECK_DECLS([ctime_r], , ,
 #define _POSIX_C_SOURCE 199506L
 #include <time.h>])
 
-dnl On Linux we should have program_invocation_short_name
-AC_CHECK_DECLS([program_invocation_short_name], , ,
-[#define _GNU_SOURCE 1
-#include <errno.h>])
-
-dnl ** check for mingwex library
-AC_CHECK_LIB(
-  [mingwex],
-  [closedir],
-  [AC_SUBST([HaveLibMingwEx],[YES])] [AC_SUBST([CabalMingwex],[True])],
-  [AC_SUBST([HaveLibMingwEx],[NO])] [AC_SUBST([CabalMingwex],[False])])
-
-if test $HaveLibMingwEx = YES ; then
-  AC_DEFINE([HAVE_MINGWEX], [1], [Define to 1 if you have the mingwex library.])
-fi
-
-dnl ** check for math library
-dnl    Keep that check as early as possible.
-dnl    as we need to know whether we need libm
-dnl    for math functions or not
-dnl    (see https://gitlab.haskell.org/ghc/ghc/issues/3730)
-AC_CHECK_LIB(m, atan, HaveLibM=YES, HaveLibM=NO)
-if test $HaveLibM = YES
-then
-  AC_DEFINE([HAVE_LIBM], [1], [Define to 1 if you need to link with libm])
-  AC_SUBST([CabalHaveLibm],[True])
-else
-  AC_SUBST([CabalHaveLibm],[False])
-fi
-TargetHasLibm=$HaveLibM
-AC_SUBST(TargetHasLibm)
-
 FP_BFD_SUPPORT
 
 dnl ################################################################
@@ -964,12 +885,6 @@ AS_IF([test "x$with_system_libffi" = "xyes"],
 )
 AC_SUBST(CabalUseSystemLibFFI)
 
-dnl ** check whether we need -ldl to get dlopen()
-AC_CHECK_LIB([dl], [dlopen])
-AC_CHECK_LIB([dl], [dlopen], [AC_SUBST([CabalHaveLibdl], [True])], [AC_SUBST([CabalHaveLibdl], [False])])
-dnl ** check whether we have dlinfo
-AC_CHECK_FUNCS([dlinfo])
-
 dnl --------------------------------------------------
 dnl * Miscellaneous feature tests
 dnl --------------------------------------------------
@@ -997,16 +912,6 @@ else
    AC_SUBST([CabalLeadingUnderscore],[False])
 fi
 
-FP_VISIBILITY_HIDDEN
-
-FP_MUSTTAIL
-
-dnl ** check for librt
-AC_CHECK_LIB([rt], [clock_gettime])
-AC_CHECK_LIB([rt], [clock_gettime], [AC_SUBST([CabalHaveLibrt], [True])], [AC_SUBST([CabalHaveLibrt], [False])])
-AC_CHECK_FUNCS(clock_gettime timer_settime)
-FP_CHECK_TIMER_CREATE
-
 dnl ** check for Apple's "interesting" long double compatibility scheme
 AC_MSG_CHECKING(for printf\$LDBLStub)
 AC_LINK_IFELSE([AC_LANG_CALL([], [printf\$LDBLStub])],
@@ -1027,106 +932,6 @@ dnl ** check for eventfd which is needed by the I/O manager
 AC_CHECK_HEADERS([sys/eventfd.h])
 AC_CHECK_FUNCS([eventfd])
 
-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
-
-dnl ** Use MMAP in the runtime linker?
-dnl --------------------------------------------------------------
-
-case ${TargetOS} in
-    linux|linux-android|freebsd|dragonfly|netbsd|openbsd|kfreebsdgnu|gnu|solaris2)
-        RtsLinkerUseMmap=1
-        ;;
-    darwin|ios|watchos|tvos)
-        RtsLinkerUseMmap=1
-        ;;
-    *)
-        # Windows (which doesn't have mmap) and everything else.
-        RtsLinkerUseMmap=0
-        ;;
-    esac
-
-AC_DEFINE_UNQUOTED([RTS_LINKER_USE_MMAP], [$RtsLinkerUseMmap],
-                   [Use mmap in the runtime linker])
-
-
-GHC_ADJUSTORS_METHOD([Target])
-AC_SUBST([UseLibffiForAdjustors])
-AS_IF([test x"${UseLibffiForAdjustors}" = x"YES"],
-  [CabalLibffiAdjustors=True],
-  [CabalLibffiAdjustors=False]
-)
-AC_SUBST([CabalLibffiAdjustors])
-
-dnl ** Other RTS features
-dnl --------------------------------------------------------------
-FP_FIND_LIBDW
-FP_FIND_LIBNUMA
 
 dnl ** Documentation
 dnl --------------------------------------------------------------


=====================================
distrib/configure.ac.in
=====================================
@@ -21,9 +21,6 @@ bootstrap_target=@TargetPlatform@
 TargetHasRTSLinker=@TargetHasRTSLinker@
 AC_SUBST(TargetHasRTSLinker)
 
-TargetHasLibm=@TargetHasLibm@
-AC_SUBST(TargetHasLibm)
-
 FFIIncludeDir=@FFIIncludeDir@
 FFILibDir=@FFILibDir@
 AC_SUBST(FFILibDir)


=====================================
hadrian/bindist/Makefile
=====================================
@@ -116,7 +116,6 @@ lib/settings :
 	@echo ',("target has .ident directive", "$(TargetHasIdentDirective)")' >> $@
 	@echo ',("target has subsections via symbols", "$(TargetHasSubsectionsViaSymbols)")' >> $@
 	@echo ',("target has RTS linker", "$(TargetHasRTSLinker)")' >> $@
-	@echo ',("target has libm", "$(TargetHasLibm)")' >> $@
 	@echo ',("Unregisterised", "$(GhcUnregisterised)")' >> $@
 	@echo ',("LLVM target", "$(LLVMTarget_CPP)")' >> $@
 	@echo ',("LLVM llc command", "$(SettingsLlcCommand)")' >> $@


=====================================
hadrian/bindist/config.mk.in
=====================================
@@ -251,7 +251,6 @@ TargetHasGnuNonexecStack = @TargetHasGnuNonexecStack@
 TargetHasIdentDirective = @TargetHasIdentDirective@
 TargetHasSubsectionsViaSymbols = @TargetHasSubsectionsViaSymbols@
 TargetHasRTSLinker = @TargetHasRTSLinker@
-TargetHasLibm = @TargetHasLibm@
 TablesNextToCode = @TablesNextToCode@
 
 SettingsCCompilerCommand = @SettingsCCompilerCommand@


=====================================
hadrian/cabal.project
=====================================
@@ -1,4 +1,5 @@
 packages: ./
+packages: ../libraries/Cabal/Cabal, ../libraries/Cabal/Cabal-syntax
 
 -- This essentially freezes the build plan for hadrian
 index-state: 2022-09-10T18:46:55Z


=====================================
hadrian/cfg/system.config.in
=====================================
@@ -171,7 +171,6 @@ target-has-gnu-nonexec-stack = @TargetHasGnuNonexecStack@
 target-has-ident-directive = @TargetHasIdentDirective@
 target-has-subsections-via-symbols = @TargetHasSubsectionsViaSymbols@
 target-has-rts-linker = @TargetHasRTSLinker@
-target-has-libm = @TargetHasLibm@
 target-arm-version    = @ARM_ISA@
 
 # Include and library directories:
@@ -203,4 +202,3 @@ libnuma-lib-dir       = @LibNumaLibDir@
 
 with-libdw = @UseLibdw@
 with-libnuma = @UseLibNuma@
-have-lib-mingw-ex = @HaveLibMingwEx@


=====================================
hadrian/hadrian.cabal
=====================================
@@ -147,7 +147,7 @@ executable hadrian
                        , BangPatterns
     other-extensions:    MultiParamTypeClasses
                        , TypeFamilies
-    build-depends:       Cabal                >= 3.2     && < 3.9
+    build-depends:       Cabal                >= 3.2     && < 3.10
                        , base                 >= 4.8     && < 5
                        , bytestring           >= 0.10    && < 0.12
                        , containers           >= 0.5     && < 0.7


=====================================
hadrian/src/Oracles/Flag.hs
=====================================
@@ -28,7 +28,6 @@ data Flag = ArSupportsAtFile
           | SolarisBrokenShld
           | WithLibdw
           | WithLibnuma
-          | HaveLibMingwEx
           | UseSystemFfi
           | BootstrapThreadedRts
           | BootstrapEventLoggingRts
@@ -52,7 +51,6 @@ flag f = do
             SolarisBrokenShld    -> "solaris-broken-shld"
             WithLibdw            -> "with-libdw"
             WithLibnuma          -> "with-libnuma"
-            HaveLibMingwEx       -> "have-lib-mingw-ex"
             UseSystemFfi         -> "use-system-ffi"
             BootstrapThreadedRts -> "bootstrap-threaded-rts"
             BootstrapEventLoggingRts -> "bootstrap-event-logging-rts"


=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -138,7 +138,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" %> \_ -> do
+            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"
@@ -339,7 +340,6 @@ generateSettings = do
         , ("target has .ident directive", expr $ lookupSystemConfig "target-has-ident-directive")
         , ("target has subsections via symbols", expr $ lookupSystemConfig "target-has-subsections-via-symbols")
         , ("target has RTS linker", expr $ lookupSystemConfig "target-has-rts-linker")
-        , ("target has libm", expr $  lookupSystemConfig "target-has-libm")
         , ("Unregisterised", expr $ yesNo <$> flag GhcUnregisterised)
         , ("LLVM target", getSetting LlvmTarget)
         , ("LLVM llc command", expr $ settingsFileSetting SettingsFileSetting_LlcCommand)
@@ -410,27 +410,6 @@ generateConfigHs = do
     stageString Stage3 = "4"
     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/Settings/Packages.hs
=====================================
@@ -403,8 +403,7 @@ rtsPackageArgs = package rts ? do
         , builder HsCpp ? pure
           [ "-DTOP="             ++ show top ]
 
-        , builder HsCpp ? flag WithLibdw ? arg "-DUSE_LIBDW"
-        , builder HsCpp ? flag HaveLibMingwEx ? arg "-DHAVE_LIBMINGWEX" ]
+        , builder HsCpp ? flag WithLibdw ? arg "-DUSE_LIBDW" ]
 
 -- Compile various performance-critical pieces *without* -fPIC -dynamic
 -- even when building a shared library.  If we don't do this, then the


=====================================
libraries/Cabal
=====================================
@@ -1 +1 @@
-Subproject commit 410f871df899e5af0847089354e0031fe051551d
+Subproject commit a36e1aefa0e03ca54901f4bdea36a3d91d31155f


=====================================
rts/.gitignore
=====================================
@@ -16,3 +16,7 @@
 /config.log
 /config.status
 /configure
+/aclocal.m4
+/external-symbols.list
+/include/ghcautoconf.h.in
+/include/ghcautoconf.h


=====================================
rts/configure.ac
=====================================
@@ -0,0 +1,264 @@
+# 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 ../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.71])
+
+AC_CONFIG_HEADERS([include/ghcautoconf.h])
+
+# We have to run these unconditionally, but we may discard their
+# results in the following code
+AC_CANONICAL_BUILD
+AC_CANONICAL_HOST
+
+dnl GHC_CONVERT_PLATFORM_PARTS([host], [Host])
+dnl FPTOOLS_SET_PLATFORM_VARS([host],[Host])
+dnl FPTOOLS_SET_HASKELL_PLATFORM_VARS([Host])
+
+AC_CHECK_HEADERS([ctype.h dirent.h dlfcn.h errno.h fcntl.h grp.h limits.h locale.h nlist.h pthread.h pwd.h signal.h sys/param.h sys/mman.h sys/resource.h sys/select.h sys/time.h sys/timeb.h sys/timerfd.h sys/timers.h sys/times.h sys/utsname.h sys/wait.h termios.h utime.h windows.h winsock.h sched.h])
+
+AC_CHECK_FUNCS([getclock getrusage gettimeofday setitimer siginterrupt sysconf times ctime_r sched_setaffinity sched_getaffinity setlocale uselocale])
+
+dnl sys/cpuset.h needs sys/param.h to be included first on FreeBSD 9.1; #7708
+AC_CHECK_HEADERS([sys/cpuset.h], [], [],
+[[#if HAVE_SYS_PARAM_H
+# include <sys/param.h>
+#endif
+]])
+
+dnl ** check whether a declaration for `environ` is provided by libc.
+FP_CHECK_ENVIRON
+
+dnl ** Other RTS features
+dnl --------------------------------------------------------------
+FP_FIND_LIBDW
+FP_FIND_LIBNUMA
+
+FP_LEADING_UNDERSCORE
+FP_MUSTTAIL
+
+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
+
+dnl ** Use MMAP in the runtime linker?
+dnl --------------------------------------------------------------
+
+case ${TargetOS} in
+    linux|linux-android|freebsd|dragonfly|netbsd|openbsd|kfreebsdgnu|gnu|solaris2)
+        RtsLinkerUseMmap=1
+        ;;
+    darwin|ios|watchos|tvos)
+        RtsLinkerUseMmap=1
+        ;;
+    *)
+        # Windows (which doesn't have mmap) and everything else.
+        RtsLinkerUseMmap=0
+        ;;
+    esac
+
+AC_DEFINE_UNQUOTED([RTS_LINKER_USE_MMAP], [$RtsLinkerUseMmap],
+                   [Use mmap in the runtime linker])
+
+
+GHC_ADJUSTORS_METHOD([Target])
+AC_SUBST([UseLibffiForAdjustors])
+AS_IF([test x"${UseLibffiForAdjustors}" = x"YES"],
+  [CabalLibffiAdjustors=True],
+  [CabalLibffiAdjustors=False]
+)
+AC_SUBST([CabalLibffiAdjustors])
+
+
+dnl ** check for librt
+AC_CHECK_LIB([rt], [clock_gettime])
+AC_CHECK_LIB([rt], [clock_gettime], [AC_SUBST([CabalHaveLibrt], [True])], [AC_SUBST([CabalHaveLibrt], [False])])
+AC_CHECK_FUNCS(clock_gettime timer_settime)
+FP_CHECK_TIMER_CREATE
+
+dnl ** do we have long longs?
+AC_CHECK_TYPES([long long])
+
+dnl ** what are the sizes of various types
+FP_CHECK_SIZEOF_AND_ALIGNMENT(char)
+FP_CHECK_SIZEOF_AND_ALIGNMENT(double)
+FP_CHECK_SIZEOF_AND_ALIGNMENT(float)
+FP_CHECK_SIZEOF_AND_ALIGNMENT(int)
+FP_CHECK_SIZEOF_AND_ALIGNMENT(long)
+if test "$ac_cv_type_long_long" = yes; then
+FP_CHECK_SIZEOF_AND_ALIGNMENT(long long)
+fi
+FP_CHECK_SIZEOF_AND_ALIGNMENT(short)
+FP_CHECK_SIZEOF_AND_ALIGNMENT(unsigned char)
+FP_CHECK_SIZEOF_AND_ALIGNMENT(unsigned int)
+FP_CHECK_SIZEOF_AND_ALIGNMENT(unsigned long)
+if test "$ac_cv_type_long_long" = yes; then
+FP_CHECK_SIZEOF_AND_ALIGNMENT(unsigned long long)
+fi
+FP_CHECK_SIZEOF_AND_ALIGNMENT(unsigned short)
+FP_CHECK_SIZEOF_AND_ALIGNMENT(void *)
+
+FP_CHECK_SIZEOF_AND_ALIGNMENT(int8_t)
+FP_CHECK_SIZEOF_AND_ALIGNMENT(uint8_t)
+FP_CHECK_SIZEOF_AND_ALIGNMENT(int16_t)
+FP_CHECK_SIZEOF_AND_ALIGNMENT(uint16_t)
+FP_CHECK_SIZEOF_AND_ALIGNMENT(int32_t)
+FP_CHECK_SIZEOF_AND_ALIGNMENT(uint32_t)
+FP_CHECK_SIZEOF_AND_ALIGNMENT(int64_t)
+FP_CHECK_SIZEOF_AND_ALIGNMENT(uint64_t)
+
+dnl ** check for math library
+dnl    Keep that check as early as possible.
+dnl    as we need to know whether we need libm
+dnl    for math functions or not
+dnl    (see https://gitlab.haskell.org/ghc/ghc/issues/3730)
+AC_CHECK_LIB(m, atan, HaveLibM=YES, HaveLibM=NO)
+if test $HaveLibM = YES
+then
+  AC_DEFINE([HAVE_LIBM], [1], [Define to 1 if you need to link with libm])
+  AC_SUBST([CabalHaveLibm],[True])
+else
+  AC_SUBST([CabalHaveLibm],[False])
+fi
+TargetHasLibm=$HaveLibM
+AC_SUBST(TargetHasLibm)
+
+dnl ** check whether we need -ldl to get dlopen()
+AC_CHECK_LIB([dl], [dlopen])
+AC_CHECK_LIB([dl], [dlopen], [CabalHaveLibdl=True], [CabalHaveLibdl=False])
+AC_SUBST(CabalHaveLibdl)
+dnl ** check whether we have dlinfo
+AC_CHECK_FUNCS([dlinfo])
+
+dnl On Linux we should have program_invocation_short_name
+AC_CHECK_DECLS([program_invocation_short_name], , ,
+[#define _GNU_SOURCE 1
+#include <errno.h>])
+
+AC_CONFIG_FILES([rts.buildinfo])
+
+AC_OUTPUT
+
+pwd
+if test ! -f external-symbols.list.in; then
+    exit 1
+fi
+cat 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
+
+cat rts.buildinfo.in | \
+    "$CC" -E -P -traditional - -o - \
+    > rts.buildinfo
+
+if test "$CabalHaveLibrt" = "True"; then
+    echo 'extra-libraries: rt' >> rts.buildinfo
+fi
+if test "$CabalHaveLibm" = "True"; then
+    echo 'extra-libraries: m' >> rts.buildinfo
+fi
+if test "$CabalHaveLibdl" = "True"; then
+    echo 'extra-libraries: dl' >> rts.buildinfo
+fi
+if test "$CabalNeedLibatomic" = "True"; then
+    # for sub-word-sized atomic operations (#19119)
+    echo 'extra-libraries: atomic' >> rts.buildinfo
+fi
+if test "$CabalNeedLibpthread" = "True"; then
+    # for pthread_getthreadid_np, pthread_create, ...
+    echo 'extra-libraries: pthread' >> rts.buildinfo
+fi
+
+rm -f external-symbols.list


=====================================
rts/external-symbols.list.in
=====================================
@@ -0,0 +1,103 @@
+#include "ghcautoconf.h"
+
+#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
+
+#if darwin_HOST_OS
+#if 0
+See Note [fd_set_overflow]
+#endif
+__darwin_check_fd_set_overflow
+#endif
+
+#if FIND_PTR
+findPtr
+#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


=====================================
m4/fp_musttail.m4 → rts/m4/fp_musttail.m4
=====================================


=====================================
m4/fp_visibility_hidden.m4 → rts/m4/fp_visibility_hidden.m4
=====================================


=====================================
rts/package.conf.in
=====================================
@@ -54,11 +54,6 @@ extra-libraries:
 #if defined(DEBUG) && defined(HAVE_LIBBFD)
                               ,"bfd", "iberty"  /* for debugging */
 #endif
-#if defined(HAVE_LIBMINGWEX)
-# if !defined(INSTALLING)                             /* Bundled Mingw is behind */
-                              ,"mingwex"
-# endif
-#endif
 #if USE_LIBDW
                              , "elf"
                              , "dw"             /* for backtraces */


=====================================
rts/posix/OSThreads.c
=====================================
@@ -32,6 +32,9 @@
 #if defined(netbsd_HOST_OS)
 #define _NETBSD_SOURCE 1
 #endif
+#if defined(linux_HOST_OS)
+#define _GNU_SOURCE 1
+#endif
 
 #include "Rts.h"
 


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


=====================================
rts/rts.cabal.in
=====================================
@@ -3,39 +3,37 @@ name: rts
 version: 1.0.2
 license: BSD-3-Clause
 maintainer: glasgow-haskell-users at haskell.org
-build-type: Simple
+build-type: Configure
+description: The GHC runtime system.
+
+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
     location: https://gitlab.haskell.org/ghc/ghc.git
     subdir:   rts
 
-flag libm
-  default: @CabalHaveLibm@
-flag librt
-  default: @CabalHaveLibrt@
-flag libdl
-  default: @CabalHaveLibdl@
+-- Configuration
 flag use-system-libffi
   default: @CabalUseSystemLibFFI@
 flag libffi-adjustors
   default: @CabalLibffiAdjustors@
-flag need-pthread
-  default: @CabalNeedLibpthread@
 flag libbfd
   default: @CabalHaveLibbfd@
-flag mingwex
-  default: @CabalMingwex@
-flag need-atomic
-  default: @CabalNeedLibatomic@
 flag libdw
   default: @CabalHaveLibdw@
 flag libnuma
   default: @CabalHaveLibNuma@
-flag 64bit
-  default: @Cabal64bit@
-flag leading-underscore
-  default: @CabalLeadingUnderscore@
 flag smp
   default: True
 flag find-ptr
@@ -115,11 +113,6 @@ library
        -- that it is ordered correctly with libpthread, since ghc-prim.cabal
        -- also explicitly lists libc. See #19029.
        extra-libraries: c
-    if flag(libm)
-       -- for ldexp()
-       extra-libraries: m
-    if flag(librt)
-       extra-libraries: rt
     if flag(libdl)
        extra-libraries: dl
     if flag(use-system-libffi)
@@ -141,16 +134,10 @@ library
        -- and also centralizes the versioning.
        cpp-options: -D_WIN32_WINNT=0x06010000
        cc-options: -D_WIN32_WINNT=0x06010000
-    if flag(need-pthread)
-       -- for pthread_getthreadid_np, pthread_create, ...
-       extra-libraries: pthread
-    if flag(need-atomic)
-       -- for sub-word-sized atomic operations (#19119)
-       extra-libraries: atomic
     if flag(libbfd)
        -- for debugging
        extra-libraries: bfd iberty
-    if flag(mingwex)
+    if os(windows)
        extra-libraries: mingwex
     if flag(libdw)
        -- for backtraces
@@ -164,6 +151,7 @@ library
                   @FFIIncludeDir@
                   @LibdwIncludeDir@
     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
@@ -233,205 +221,9 @@ library
                       stg/SMP.h
                       stg/Ticky.h
                       stg/Types.h
-    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"
-    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]
-                  "-Wl,-U,___darwin_check_fd_set_overflow"
       if !arch(x86_64) && !arch(aarch64)
          ld-options: -read_only_relocs warning
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/645faebe32b3d9f76d3ab728b342834a16c0b7f5

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/645faebe32b3d9f76d3ab728b342834a16c0b7f5
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/20221031/1cd78380/attachment-0001.html>


More information about the ghc-commits mailing list