[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 12 commits: Move apple compat check to RTS configure

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Thu Oct 12 22:05:03 UTC 2023



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


Commits:
c74c4f00 by John Ericson at 2023-10-12T10:31:13-04:00
Move apple compat check to RTS configure

- - - - -
c80778ea by John Ericson at 2023-10-12T10:31:13-04:00
Move clock/timer fun checks to RTS configure

Actual library check (which will set the Cabal flag) is left in the
top-level configure for now.

Progress towards #17191

- - - - -
7f9f2686 by John Ericson at 2023-10-12T10:31:13-04:00
Move visibility and "musttail" annotation checks to the RTS configure

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

- - - - -
ffb3efe6 by John Ericson at 2023-10-12T10:31:13-04:00
Move leading underscore checks to RTS configure

`CabalLeadingUnderscore` is done via Hadrian already, so we can stop
`AC_SUBST`ing it completely.

- - - - -
25fa4b02 by John Ericson at 2023-10-12T10:31:13-04:00
Move alloca, fork, const, and big endian checks to RTS configure

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.

- - - - -
5170f42a by John Ericson at 2023-10-12T10:31:13-04:00
Move libdl check to RTS configure

- - - - -
ea7a1447 by John Ericson at 2023-10-12T10:31:13-04:00
Adjust `FP_FIND_LIBFFI`

Just set vars, and `AC_SUBST` in top-level configure.

Don't define `HAVE_SYSTEM_LIBFFI` because nothing is using it. It hasn't
be in used since 3609340743c1b25fdfd0e18b1670dac54c8d8623 (part of the
make build system).

- - - - -
f399812c by John Ericson at 2023-10-12T10:31:13-04:00
Split BFD support to RTS configure

The flag is still in the top-level configure, but the other checks
(which define various macros --- important) are in the RTS configure.

- - - - -
f64f44e9 by John Ericson at 2023-10-12T10:31:13-04:00
Split libm check between top level and RTS

- - - - -
dafc4709 by Moritz Angermann at 2023-10-12T10:31:49-04:00
CgUtils.fixStgRegStmt respect register width

This change ensure that the reg + offset computation is always of the
same size.  Before this we could end up with a 64bit register, and then
add a 32bit offset (on 32bit platforms).  This not only would fail type
sanity checking, but also incorrectly truncate 64bit values into 32bit
values silently on 32bit architectures.

- - - - -
8ebb1316 by Matthew Pickering at 2023-10-12T18:04:55-04:00
hadrian: Decrease verbosity of cabal commands

In Normal, most tools do not produce output to stdout unless there are
error conditions.

Reverts 7ed65f5a1bc8e040e318ccff395f53a9bbfd8217

- - - - -
6cda769e by John Ericson at 2023-10-12T18:04:55-04:00
Do not substitute `@...@` for stage-specific values in cabal files

`rts` and `ghc-prim` now no longer have a `*.cabal.in` to set Cabal flag
defaults; instead manual choices are passed to configure in the usual
way.

The old way was fundamentally broken, because it meant we were baking
these Cabal files for a specific stage. Now we only do stage-agnostic
@...@ substitution in cabal files (the GHC version), and so all
stage-specific configuration is properly confined to `_build` and the
right stage dir.

Also `include-ghc-prim` is a flag that no longer exists for `ghc-prim`
(it was removed in 835d8ddbbfb11796ea8a03d1806b7cee38ba17a6) so I got
rid of it.

Co-Authored-By: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -


12 changed files:

- .gitignore
- compiler/GHC/StgToCmm/CgUtils.hs
- configure.ac
- hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Settings/Packages.hs
- libraries/ghc-prim/ghc-prim.cabal.in → libraries/ghc-prim/ghc-prim.cabal
- m4/fp_bfd_support.m4
- m4/fp_find_libffi.m4
- rts/.gitignore
- rts/configure.ac
- rts/rts.cabal.in → rts/rts.cabal


Changes:

=====================================
.gitignore
=====================================
@@ -167,7 +167,6 @@ _darcs/
 /libraries/ghc-boot-th/ghc-boot-th.cabal
 /libraries/ghc-boot-th/ghc.mk
 /libraries/ghc-heap/ghc-heap.cabal
-/libraries/ghc-prim/ghc-prim.cabal
 /libraries/ghci/GNUmakefile
 /libraries/ghci/ghci.cabal
 /libraries/ghci/ghc.mk


=====================================
compiler/GHC/StgToCmm/CgUtils.hs
=====================================
@@ -177,16 +177,18 @@ fixStgRegStmt platform stmt = fixAssign $ mapExpDeep fixExpr stmt
                                      (globalRegSpillType platform reg)
                                      NaturallyAligned
 
-        CmmRegOff (CmmGlobal reg_use) offset ->
+        CmmRegOff greg@(CmmGlobal reg) offset ->
             -- RegOf leaves are just a shorthand form. If the reg maps
             -- to a real reg, we keep the shorthand, otherwise, we just
             -- expand it and defer to the above code.
-            let reg = globalRegUseGlobalReg reg_use in
-            case reg `elem` activeStgRegs platform of
+            -- NB: to ensure type correctness we need to ensure the Add
+            --     as well as the Int need to be of the same size as the
+            --     register.
+            case globalRegUseGlobalReg reg `elem` activeStgRegs platform of
                 True  -> expr
-                False -> CmmMachOp (MO_Add (wordWidth platform)) [
-                                    fixExpr (CmmReg (CmmGlobal reg_use)),
+                False -> CmmMachOp (MO_Add (cmmRegWidth greg)) [
+                                    fixExpr (CmmReg greg),
                                     CmmLit (CmmInt (fromIntegral offset)
-                                                   (wordWidth platform))]
+                                                   (cmmRegWidth greg))]
 
         other_expr -> other_expr


=====================================
configure.ac
=====================================
@@ -951,18 +951,13 @@ 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([UseLibm],[YES])
-else
-  AC_SUBST([UseLibm],[NO])
-fi
-TargetHasLibm=$HaveLibM
+AC_CHECK_LIB(m, atan, UseLibm=YES, UseLibm=NO)
+AC_SUBST([UseLibm])
+TargetHasLibm=$UseLibm
 AC_SUBST(TargetHasLibm)
 
-FP_BFD_SUPPORT
+FP_BFD_FLAG
+AC_SUBST([UseLibbfd])
 
 dnl ################################################################
 dnl Check for libraries
@@ -970,70 +965,20 @@ dnl ################################################################
 
 FP_FIND_LIBFFI
 AC_SUBST(UseSystemLibFFI)
+AC_SUBST(FFILibDir)
+AC_SUBST(FFIIncludeDir)
 
 dnl ** check whether we need -ldl to get dlopen()
-AC_CHECK_LIB([dl], [dlopen])
-AC_CHECK_LIB([dl], [dlopen], HaveLibdl=YES, HaveLibdl=NO)
-AC_SUBST([UseLibdl],[$HaveLibdl])
-dnl ** check whether we have dlinfo
-AC_CHECK_FUNCS([dlinfo])
-
-dnl --------------------------------------------------
-dnl * Miscellaneous feature tests
-dnl --------------------------------------------------
-
-dnl ** can we get alloca?
-AC_FUNC_ALLOCA
-
-dnl ** working vfork?
-AC_FUNC_FORK
-
-dnl ** determine whether or not const works
-AC_C_CONST
-
-dnl ** are we big endian?
-AC_C_BIGENDIAN
-FPTOOLS_FLOAT_WORD_ORDER_BIGENDIAN
+AC_CHECK_LIB([dl], [dlopen], UseLibdl=YES, UseLibdl=NO)
+AC_SUBST([UseLibdl])
 
 dnl ** check for leading underscores in symbol names
 FP_LEADING_UNDERSCORE
 AC_SUBST([LeadingUnderscore], [`echo $fptools_cv_leading_underscore | sed 'y/yesno/YESNO/'`])
-if test x"$fptools_cv_leading_underscore" = xyes; then
-   AC_SUBST([CabalLeadingUnderscore],[True])
-   AC_DEFINE([LEADING_UNDERSCORE], [1], [Define to 1 if C symbols have a leading underscore added by the compiler.])
-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], HaveLibrt=YES, HaveLibrt=NO)
-if test $HaveLibrt = YES
-then
-  AC_SUBST([UseLibrt],[YES])
-else
-  AC_SUBST([UseLibrt],[NO])
-fi
-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])],
-    [
-        AC_MSG_RESULT(yes)
-        AC_DEFINE([HAVE_PRINTF_LDBLSTUB],[1],
-            [Define to 1 if we have printf$LDBLStub (Apple Mac OS >= 10.4, PPC).])
-    ],
-    [
-        AC_MSG_RESULT(no)
-        AC_DEFINE([HAVE_PRINTF_LDBLSTUB],[0],
-            [Define to 1 if we have printf$LDBLStub (Apple Mac OS >= 10.4, PPC).])
-    ])
+AC_CHECK_LIB([rt], [clock_gettime], UseLibrt=YES, UseLibrt=NO)
+AC_SUBST([UseLibrt])
 
 FP_CHECK_PTHREAD_LIB
 AC_SUBST([UseLibpthread])


=====================================
hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
=====================================
@@ -198,9 +198,10 @@ copyPackage context at Context {..} = do
 shakeVerbosityToCabalFlag :: Verbosity -> String
 shakeVerbosityToCabalFlag = \case
     Diagnostic -> "-v3"
-    Verbose -> "-v3"
+    Verbose -> "-v2"
+    -- Normal levels should not produce output to stdout
     Silent -> "-v0"
-    _ -> "-v2"
+    _ -> "-v1"
 
 -- | What type of file is Main
 data MainSourceType = HsMain | CppMain | CMain


=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -268,17 +268,6 @@ runInterpolations (Interpolations mk_substs) input = do
         subst = foldr (.) id [replace ("@"++k++"@") v | (k,v) <- substs]
     return (subst input)
 
-toCabalBool :: Bool -> String
-toCabalBool True  = "True"
-toCabalBool False = "False"
-
--- | Interpolate the given variable with the value of the given 'Flag', using
--- Cabal's boolean syntax.
-interpolateCabalFlag :: String -> Flag -> Interpolations
-interpolateCabalFlag name flg = interpolateVar name $ do
-    val <- flag flg
-    return (toCabalBool val)
-
 -- | Interpolate the given variable with the value of the given 'Setting'.
 interpolateSetting :: String -> Setting -> Interpolations
 interpolateSetting name settng = interpolateVar name $ setting settng
@@ -290,31 +279,6 @@ projectVersion = mconcat
     , interpolateSetting "ProjectVersionMunged" ProjectVersionMunged
     ]
 
-rtsCabalFlags :: Interpolations
-rtsCabalFlags = mconcat
-    [ flag "CabalHaveLibdw" UseLibdw
-    , flag "CabalHaveLibm" UseLibm
-    , flag "CabalHaveLibrt" UseLibrt
-    , flag "CabalHaveLibdl" UseLibdl
-    , flag "CabalNeedLibpthread" UseLibpthread
-    , flag "CabalHaveLibbfd" UseLibbfd
-    , flag "CabalHaveLibNuma" UseLibnuma
-    , flag "CabalHaveLibZstd" UseLibzstd
-    , flag "CabalStaticLibZstd" StaticLibzstd
-    , flag "CabalNeedLibatomic" NeedLibatomic
-    , flag "CabalUseSystemLibFFI" UseSystemFfi
-    , targetFlag "CabalLibffiAdjustors" tgtUseLibffiForAdjustors
-    , targetFlag "CabalLeadingUnderscore" tgtSymbolsHaveLeadingUnderscore
-    ]
-  where
-    flag = interpolateCabalFlag
-    targetFlag name q = interpolateVar name $ do
-      val <- queryTargetTarget q
-      return (toCabalBool val)
-
-ghcPrimCabalFlags :: Interpolations
-ghcPrimCabalFlags = interpolateCabalFlag "CabalNeedLibatomic" NeedLibatomic
-
 packageVersions :: Interpolations
 packageVersions = foldMap f [ base, ghcPrim, compiler, ghc, cabal, templateHaskell, ghcCompact, array ]
   where
@@ -347,8 +311,6 @@ templateRule outPath interps = do
 templateRules :: Rules ()
 templateRules = do
   templateRule "compiler/ghc.cabal" $ projectVersion
-  templateRule "rts/rts.cabal" $ rtsCabalFlags
-  templateRule "libraries/ghc-prim/ghc-prim.cabal" $ ghcPrimCabalFlags
   templateRule "driver/ghci/ghci-wrapper.cabal" $ projectVersion
   templateRule "ghc/ghc-bin.cabal" $ projectVersion
   templateRule "utils/iserv/iserv.cabal" $ projectVersion


=====================================
hadrian/src/Settings/Packages.hs
=====================================
@@ -114,7 +114,7 @@ packageArgs = do
 
         -------------------------------- ghcPrim -------------------------------
         , package ghcPrim ? mconcat
-          [ builder (Cabal Flags) ? arg "include-ghc-prim"
+          [ builder (Cabal Flags) ? flag NeedLibatomic `cabalFlag` "need-atomic"
 
           , builder (Cc CompileC) ? (not <$> flag CcLlvmBackend) ?
             input "**/cbits/atomic.c"  ? arg "-Wno-sync-nand" ]
@@ -401,8 +401,19 @@ rtsPackageArgs = package rts ? do
           , any (wayUnit Debug) rtsWays     `cabalFlag` "debug"
           , any (wayUnit Dynamic) rtsWays   `cabalFlag` "dynamic"
           , any (wayUnit Threaded) rtsWays  `cabalFlag` "threaded"
+          , flag UseLibm                    `cabalFlag` "libm"
+          , flag UseLibrt                   `cabalFlag` "librt"
+          , flag UseLibdl                   `cabalFlag` "libdl"
           , useSystemFfi                    `cabalFlag` "use-system-libffi"
           , useLibffiForAdjustors           `cabalFlag` "libffi-adjustors"
+          , flag UseLibpthread              `cabalFlag` "need-pthread"
+          , flag UseLibbfd                  `cabalFlag` "libbfd"
+          , flag NeedLibatomic              `cabalFlag` "need-atomic"
+          , flag UseLibdw                   `cabalFlag` "libdw"
+          , flag UseLibnuma                 `cabalFlag` "libnuma"
+          , flag UseLibzstd                 `cabalFlag` "libzstd"
+          , flag StaticLibzstd              `cabalFlag` "static-libzstd"
+          , queryTargetTarget tgtSymbolsHaveLeadingUnderscore `cabalFlag` "leading-underscore"
           , Debug `wayUnit` way             `cabalFlag` "find-ptr"
           ]
         , builder (Cabal Setup) ? mconcat


=====================================
libraries/ghc-prim/ghc-prim.cabal.in → libraries/ghc-prim/ghc-prim.cabal
=====================================
@@ -28,7 +28,7 @@ custom-setup
     setup-depends: base >= 4 && < 5, process, filepath, directory, Cabal >= 1.23 && < 3.9
 
 flag need-atomic
-  default: @CabalNeedLibatomic@
+  default: False
 
 Library
     default-language: Haskell2010


=====================================
m4/fp_bfd_support.m4
=====================================
@@ -1,49 +1,59 @@
 # FP_BFD_SUPPORT()
 # ----------------------
-# whether to use libbfd for debugging RTS
-AC_DEFUN([FP_BFD_SUPPORT], [
-    HaveLibbfd=NO
-    AC_ARG_ENABLE(bfd-debug,
-        [AS_HELP_STRING([--enable-bfd-debug],
-              [Enable symbol resolution for -debug rts ('+RTS -Di') via binutils' libbfd [default=no]])],
-        [
-            # don't pollute general LIBS environment
-            save_LIBS="$LIBS"
-            AC_CHECK_HEADERS([bfd.h])
-            dnl ** check whether this machine has BFD and libiberty installed (used for debugging)
-            dnl    the order of these tests matters: bfd needs libiberty
-            AC_CHECK_LIB(iberty, xmalloc)
-            dnl 'bfd_init' is a rare non-macro in libbfd
-            AC_CHECK_LIB(bfd,    bfd_init)
+# Whether to use libbfd for debugging RTS
+#
+# Sets:
+#   UseLibbfd: [YES|NO]
+AC_DEFUN([FP_BFD_FLAG], [
+  UseLibbfd=NO
+  AC_ARG_ENABLE(bfd-debug,
+    [AS_HELP_STRING([--enable-bfd-debug],
+          [Enable symbol resolution for -debug rts ('+RTS -Di') via binutils' libbfd [default=no]])],
+    [UseLibbfd=YES],
+    [UseLibbfd=NO])
+])
+
+# FP_WHEN_ENABLED_BFD
+# ----------------------
+# Checks for libraries in the default way, which will define various
+# `HAVE_*` macros.
+AC_DEFUN([FP_WHEN_ENABLED_BFD], [
+  # don't pollute general LIBS environment
+  save_LIBS="$LIBS"
+  AC_CHECK_HEADERS([bfd.h])
+  dnl ** check whether this machine has BFD and libiberty installed (used for debugging)
+  dnl    the order of these tests matters: bfd needs libiberty
+  AC_CHECK_LIB(iberty, xmalloc)
+  dnl 'bfd_init' is a rare non-macro in libbfd
+  AC_CHECK_LIB(bfd,    bfd_init)
 
-            AC_LINK_IFELSE([AC_LANG_PROGRAM([[#include <bfd.h>]],
-                        [[
-                                /* mimic our rts/Printer.c */
-                                bfd* abfd;
-                                const char * name;
-                                char **matching;
+  AC_LINK_IFELSE(
+    [AC_LANG_PROGRAM(
+      [[#include <bfd.h>]],
+      [[
+        /* mimic our rts/Printer.c */
+        bfd* abfd;
+        const char * name;
+        char **matching;
 
-                                name = "some.executable";
-                                bfd_init();
-                                abfd = bfd_openr(name, "default");
-                                bfd_check_format_matches (abfd, bfd_object, &matching);
-                                {
-                                    long storage_needed;
-                                    storage_needed = bfd_get_symtab_upper_bound (abfd);
-                                }
-                                {
-                                    asymbol **symbol_table;
-                                    long number_of_symbols;
-                                    symbol_info info;
+        name = "some.executable";
+        bfd_init();
+        abfd = bfd_openr(name, "default");
+        bfd_check_format_matches (abfd, bfd_object, &matching);
+        {
+            long storage_needed;
+            storage_needed = bfd_get_symtab_upper_bound (abfd);
+        }
+        {
+            asymbol **symbol_table;
+            long number_of_symbols;
+            symbol_info info;
 
-                                    number_of_symbols = bfd_canonicalize_symtab (abfd, symbol_table);
-                                    bfd_get_symbol_info(abfd,symbol_table[0],&info);
-                                }
-                        ]])],
-                        HaveLibbfd=YES,dnl bfd seems to work
-                        [AC_MSG_ERROR([can't use 'bfd' library])])
-            LIBS="$save_LIBS"
-        ]
-    )
-    AC_SUBST([UseLibbfd],[$HaveLibbfd])
+            number_of_symbols = bfd_canonicalize_symtab (abfd, symbol_table);
+            bfd_get_symbol_info(abfd,symbol_table[0],&info);
+        }
+      ]])],
+    [], dnl bfd seems to work
+    [AC_MSG_ERROR([can't use 'bfd' library])])
+  LIBS="$save_LIBS"
 ])


=====================================
m4/fp_find_libffi.m4
=====================================
@@ -1,6 +1,11 @@
-dnl ** Have libffi?
-dnl --------------------------------------------------------------
-dnl Sets UseSystemLibFFI.
+# FP_FIND_LIBFFI
+# --------------------------------------------------------------
+# Should we used libffi? (yes or no)
+#
+# Sets variables:
+#   - UseSystemLibFFI: [YES|NO]
+#   - FFILibDir: optional path
+#   - FFIIncludeDir: optional path
 AC_DEFUN([FP_FIND_LIBFFI],
 [
   # system libffi
@@ -28,8 +33,6 @@ AC_DEFUN([FP_FIND_LIBFFI],
    fi
   ])
 
-  AC_SUBST(FFIIncludeDir)
-
   AC_ARG_WITH([ffi-libraries],
   [AS_HELP_STRING([--with-ffi-libraries=ARG],
     [Find libffi in ARG [default=system default]])
@@ -42,8 +45,6 @@ AC_DEFUN([FP_FIND_LIBFFI],
    fi
   ])
 
-  AC_SUBST(FFILibDir)
-
   AS_IF([test "$UseSystemLibFFI" = "YES"], [
    CFLAGS2="$CFLAGS"
    CFLAGS="$LIBFFI_CFLAGS $CFLAGS"
@@ -63,7 +64,7 @@ AC_DEFUN([FP_FIND_LIBFFI],
    AC_CHECK_LIB(ffi, ffi_call,
     [AC_CHECK_HEADERS(
       [ffi.h],
-      [AC_DEFINE([HAVE_SYSTEM_LIBFFI], [1], [Define to 1 if you have libffi.])],
+      [],
       [AC_MSG_ERROR([Cannot find ffi.h for system libffi])]
      )],
     [AC_MSG_ERROR([Cannot find system libffi])]


=====================================
rts/.gitignore
=====================================
@@ -2,8 +2,6 @@
 /dist/
 /dist-*/
 
-/rts.cabal
-
 /include/ghcversion.h
 
 /package.conf.inplace


=====================================
rts/configure.ac
=====================================
@@ -33,6 +33,70 @@ GHC_CONVERT_PLATFORM_PARTS([host], [Host])
 FPTOOLS_SET_PLATFORM_VARS([host], [Host])
 FPTOOLS_SET_HASKELL_PLATFORM_VARS([Host])
 
+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)
+AS_IF(
+  [test "$CABAL_FLAG_libm" = 1],
+  [AC_DEFINE([HAVE_LIBM], [1], [Define to 1 if you need to link with libm])])
+
+AS_IF([test "$CABAL_FLAG_libbfd" = 1], [FP_WHEN_ENABLED_BFD])
+
+dnl ################################################################
+dnl Check for libraries
+dnl ################################################################
+
+dnl ** check whether we need -ldl to get dlopen()
+AC_CHECK_LIB([dl], [dlopen])
+dnl ** check whether we have dlinfo
+AC_CHECK_FUNCS([dlinfo])
+
+dnl --------------------------------------------------
+dnl * Miscellaneous feature tests
+dnl --------------------------------------------------
+
+dnl ** can we get alloca?
+AC_FUNC_ALLOCA
+
+dnl ** working vfork?
+AC_FUNC_FORK
+
+dnl ** determine whether or not const works
+AC_C_CONST
+
+dnl ** are we big endian?
+AC_C_BIGENDIAN
+FPTOOLS_FLOAT_WORD_ORDER_BIGENDIAN
+
+dnl ** check for leading underscores in symbol names
+if test "$CABAL_FLAG_leading_underscore" = 1; then
+   AC_DEFINE([LEADING_UNDERSCORE], [1], [Define to 1 if C symbols have a leading underscore added by the compiler.])
+fi
+
+FP_VISIBILITY_HIDDEN
+
+FP_MUSTTAIL
+
+dnl ** check for librt
+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])],
+    [
+        AC_MSG_RESULT(yes)
+        AC_DEFINE([HAVE_PRINTF_LDBLSTUB],[1],
+            [Define to 1 if we have printf$LDBLStub (Apple Mac OS >= 10.4, PPC).])
+    ],
+    [
+        AC_MSG_RESULT(no)
+        AC_DEFINE([HAVE_PRINTF_LDBLSTUB],[0],
+            [Define to 1 if we have printf$LDBLStub (Apple Mac OS >= 10.4, PPC).])
+    ])
+
 FP_CHECK_PTHREAD_FUNCS
 
 dnl ** check for eventfd which is needed by the I/O manager


=====================================
rts/rts.cabal.in → rts/rts.cabal
=====================================
@@ -29,31 +29,31 @@ source-repository head
     subdir:   rts
 
 flag libm
-  default: @CabalHaveLibm@
+  default: False
 flag librt
-  default: @CabalHaveLibrt@
+  default: False
 flag libdl
-  default: @CabalHaveLibdl@
+  default: False
 flag use-system-libffi
-  default: @CabalUseSystemLibFFI@
+  default: False
 flag libffi-adjustors
-  default: @CabalLibffiAdjustors@
+  default: False
 flag need-pthread
-  default: @CabalNeedLibpthread@
+  default: False
 flag libbfd
-  default: @CabalHaveLibbfd@
+  default: False
 flag need-atomic
-  default: @CabalNeedLibatomic@
+  default: False
 flag libdw
-  default: @CabalHaveLibdw@
+  default: False
 flag libnuma
-  default: @CabalHaveLibNuma@
+  default: False
 flag libzstd
-  default: @CabalHaveLibZstd@
+  default: False
 flag static-libzstd
-  default: @CabalStaticLibZstd@
+  default: False
 flag leading-underscore
-  default: @CabalLeadingUnderscore@
+  default: False
 flag smp
   default: True
 flag find-ptr



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/81c169678de4004246212a1c5b2914ac171895ed...6cda769ec00498de73f7642c8fa9505eecc4b019

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/81c169678de4004246212a1c5b2914ac171895ed...6cda769ec00498de73f7642c8fa9505eecc4b019
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/20231012/e8fdd463/attachment-0001.html>


More information about the ghc-commits mailing list