[Git][ghc/ghc][wip/rts-configure] 8 commits: Do not substitute `@...@` for stage-specific values in cabal files

John Ericson (@Ericson2314) gitlab at gitlab.haskell.org
Thu Oct 12 18:43:50 UTC 2023



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


Commits:
49f00097 by John Ericson at 2023-10-12T14:35:42-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>

- - - - -
512b884b by John Ericson at 2023-10-12T14:36:38-04:00
Move function checks to RTS configure

Some of these functions are used in `base` too, but we can copy the
checks over to its configure if that's an issue.

- - - - -
8766b7ce by John Ericson at 2023-10-12T14:36:41-04:00
Move over a number of C-style checks to RTS configure

- - - - -
960fc54f by John Ericson at 2023-10-12T14:36:44-04:00
Move/Copy more `AC_DEFINE` to RTS config

Only exception is the LLVM version macros, which are used for GHC
itself.

- - - - -
58944c9d by John Ericson at 2023-10-12T14:38:33-04:00
Define `TABLES_NEXT_TO_CODE` in the RTS configure

We create a new cabal flag to facilitate this.

- - - - -
d357e533 by John Ericson at 2023-10-12T14:38:40-04:00
Configure scripts: `checkOS`: Make a bit more robust

`mingw64` and `mingw32` are now both accepted for `OSMinGW32`. This
allows us to cope with configs/triples that we haven't normalized extra
being what GNU `config.sub` does.

- - - - -
4ecdde35 by John Ericson at 2023-10-12T14:41:23-04:00
Generate `ghcplatform.h` from RTS configure

We create a new cabal flag to facilitate this.

- - - - -
47c36720 by John Ericson at 2023-10-12T14:41:24-04:00
Get rid of all mention of `mk/config.h`

The RTS configure script is now solely responsible for managing its
headers; the top level configure script does not help.

- - - - -


19 changed files:

- .gitignore
- compiler/GHC/Builtin/primops.txt.pp
- configure.ac
- distrib/cross-port
- docs/coding-style.html
- hadrian/src/Rules/Generate.hs
- hadrian/src/Rules/Lint.hs
- hadrian/src/Rules/Register.hs
- hadrian/src/Rules/SourceDist.hs
- hadrian/src/Settings/Packages.hs
- libraries/ghc-prim/ghc-prim.cabal.in → libraries/ghc-prim/ghc-prim.cabal
- m4/fp_cc_supports__atomics.m4
- m4/fptools_set_haskell_platform_vars.m4
- m4/ghc_convert_os.m4
- rts/.gitignore
- rts/configure.ac
- + rts/ghcplatform.h.bottom
- + rts/ghcplatform.h.top.in
- 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
@@ -185,8 +184,8 @@ _darcs/
 /linter.log
 /mk/are-validating.mk
 /mk/build.mk
-/mk/config.h
-/mk/config.h.in
+/mk/unused.h
+/mk/unused.h.in
 /mk/config.mk
 /mk/config.mk.old
 /mk/system-cxx-std-lib-1.0.conf


=====================================
compiler/GHC/Builtin/primops.txt.pp
=====================================
@@ -229,7 +229,7 @@ section "The word size story."
          must contain at least 30 bits. GHC always implements
          'Int' using the primitive type 'Int#', whose size equals
          the @MachDeps.h@ constant @WORD\_SIZE\_IN\_BITS at .
-         This is normally set based on the @config.h@ parameter
+         This is normally set based on the RTS @ghcautoconf.h@ parameter
          @SIZEOF\_HSWORD@, i.e., 32 bits on 32-bit machines, 64
          bits on 64-bit machines.
 


=====================================
configure.ac
=====================================
@@ -32,8 +32,8 @@ AC_CONFIG_MACRO_DIRS([m4])
 # checkout), then we ship a file 'VERSION' containing the full version
 # when the source distribution was created.
 
-if test ! -f mk/config.h.in; then
-   echo "mk/config.h.in doesn't exist: perhaps you haven't run 'python3 boot'?"
+if test ! -f rts/ghcautoconf.h.autoconf.in; then
+   echo "rts/ghcautoconf.h.autoconf.in doesn't exist: perhaps you haven't run 'python3 boot'?"
    exit 1
 fi
 
@@ -101,8 +101,11 @@ AC_PREREQ([2.69])
 # Prepare to generate the following header files
 #
 
-# This one is autogenerated by autoheader.
-AC_CONFIG_HEADER(mk/config.h)
+dnl so the next header, which is manually maintained, doesn't get
+dnl overwritten by an autogenerated header. Once we have no more
+dnl `AC_CONFIG_HEADER` calls (issue #23966) we can delete all mention
+dnl of `mk/unused.h`.
+AC_CONFIG_HEADER(mk/unused.h)
 # This one is manually maintained.
 AC_CONFIG_HEADER(compiler/ghc-llvm-version.h)
 dnl manually outputted above, for reasons described there.
@@ -157,27 +160,6 @@ if test "$EnableDistroToolchain" = "YES"; then
   TarballsAutodownload=NO
 fi
 
-AC_ARG_ENABLE(asserts-all-ways,
-[AS_HELP_STRING([--enable-asserts-all-ways],
-                [Usually ASSERTs are only compiled in the DEBUG way,
-                 this will enable them in all ways.])],
-  [FP_CAPITALIZE_YES_NO(["$enableval"], [EnableAssertsAllWays])],
-  [EnableAssertsAllWays=NO]
-)
-if test "$enable_asserts_all_ways" = "yes" ; then
-   AC_DEFINE([USE_ASSERTS_ALL_WAYS], [1], [Compile-in ASSERTs in all ways.])
-fi
-
-AC_ARG_ENABLE(native-io-manager,
-[AS_HELP_STRING([--enable-native-io-manager],
-                [Enable the native I/O manager by default.])],
-  [FP_CAPITALIZE_YES_NO(["$enableval"], [EnableNativeIOManager])],
-  [EnableNativeIOManager=NO]
-)
-if test "$EnableNativeIOManager" = "YES"; then
-  AC_DEFINE_UNQUOTED([DEFAULT_NATIVE_IO_MANAGER], [1], [Enable Native I/O manager as default.])
-fi
-
 AC_ARG_ENABLE(ghc-toolchain,
 [AS_HELP_STRING([--enable-ghc-toolchain],
                 [Whether to use the newer ghc-toolchain tool to configure ghc targets])],
@@ -338,9 +320,6 @@ dnl ** Do a build with tables next to code?
 dnl --------------------------------------------------------------
 
 GHC_TABLES_NEXT_TO_CODE
-if test x"$TablesNextToCode" = xYES; then
-   AC_DEFINE([TABLES_NEXT_TO_CODE], [1], [Define to 1 if info tables are laid out next to code])
-fi
 AC_SUBST(TablesNextToCode)
 
 # Requires FPTOOLS_SET_PLATFORMS_VARS to be run first.
@@ -636,12 +615,15 @@ dnl    unregisterised, Sparc, and PPC backends. Also determines whether
 dnl    linking to libatomic is required for atomic operations, e.g. on
 dnl    RISCV64 GCC.
 FP_CC_SUPPORTS__ATOMICS
+if test "$need_latomic" = 1; then
+    AC_SUBST([NeedLibatomic],[YES])
+else
+    AC_SUBST([NeedLibatomic],[NO])
+fi
 
 dnl ** look to see if we have a C compiler using an llvm back end.
 dnl
 FP_CC_LLVM_BACKEND
-AS_IF([test x"$CcLlvmBackend" = x"YES"],
-  [AC_DEFINE([CC_LLVM_BACKEND], [1], [Define (to 1) if C compiler has an LLVM back end])])
 AC_SUBST(CcLlvmBackend)
 
 FPTOOLS_SET_C_LD_FLAGS([target],[CFLAGS],[LDFLAGS],[IGNORE_LINKER_LD_FLAGS],[CPPFLAGS])
@@ -864,88 +846,14 @@ dnl --------------------------------------------------
 dnl ### program checking section ends here ###
 dnl --------------------------------------------------
 
-dnl --------------------------------------------------
-dnl * Platform header file and syscall feature tests
-dnl ### checking the state of the local header files and syscalls ###
-
-dnl ** Enable large file support.  NB. do this before testing the type of
-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
+AC_CHECK_SIZEOF([void *])
 TargetWordSize=$ac_cv_sizeof_void_p
 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], , ,
-[#define _POSIX_SOURCE 1
-#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 math library
 dnl    Keep that check as early as possible.
 dnl    as we need to know whether we need libm


=====================================
distrib/cross-port
=====================================
@@ -28,7 +28,7 @@ if [ ! -f b1-stamp ]; then
 
    # For cross-compilation, at this stage you may want to set up a source
    # tree on the target machine, run the configure script there, and bring
-   # the resulting mk/config.h file back into this tree before building
+   # the resulting rts/ghcautoconf.h.autoconf file back into this tree before building
    # the libraries.
 
    touch mk/build.mk
@@ -38,7 +38,7 @@ if [ ! -f b1-stamp ]; then
 
    # We could optimise slightly by not building hslibs here.  Also, building
    # the RTS is not necessary (and might not be desirable if we're using
-   # a config.h from the target system).
+   # a ghcautoconf.h from the target system).
    make stage1
 
   cd ..


=====================================
docs/coding-style.html
=====================================
@@ -108,7 +108,7 @@ POSIX-compliant to explicitly say so by having <code>#include
 
 <p><li> Some architectures have memory alignment constraints.  Others
 don't have any constraints but go faster if you align things.  These
-macros (from <tt>config.h</tt>) tell you which alignment to use
+macros (from <tt>ghcautoconf.h</tt>) tell you which alignment to use
 
 <pre>
   /* minimum alignment of unsigned int */


=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -155,10 +155,10 @@ generatePackageCode context@(Context stage pkg _ _) = do
     when (pkg == rts) $ 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" %> \_ ->
             need . pure =<< pkgSetupConfigFile context
-        root -/- "**" -/- dir -/- "include/ghcplatform.h" %> go generateGhcPlatformH
+        root -/- "**" -/- dir -/- "include/ghcplatform.h" %> \_ ->
+            need . pure =<< pkgSetupConfigFile context
         root -/- "**" -/- dir -/- "include/DerivedConstants.h" %> genPlatformConstantsHeader context
         root -/- "**" -/- dir -/- "include/rts/EventLogConstants.h" %> genEventTypes "--event-types-defines"
         root -/- "**" -/- dir -/- "include/rts/EventTypes.h" %> genEventTypes "--event-types-array"
@@ -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
@@ -384,62 +346,6 @@ ghcWrapper stage  = do
                                      else [])
                                ++ [ "$@" ]
 
--- | Given a 'String' replace characters '.' and '-' by underscores ('_') so that
--- the resulting 'String' is a valid C preprocessor identifier.
-cppify :: String -> String
-cppify = replaceEq '-' '_' . replaceEq '.' '_'
-
--- | Generate @ghcplatform.h@ header.
--- ROMES:TODO: For the runtime-retargetable GHC, these will eventually have to
--- be determined at runtime, and no longer hardcoded to a file (passed as -D
--- flags to the preprocessor, probably)
-generateGhcPlatformH :: Expr String
-generateGhcPlatformH = do
-    trackGenerateHs
-    stage    <- getStage
-    let chooseSetting x y = case stage of { Stage0 {} -> x; _ -> y }
-    buildPlatform  <- chooseSetting (queryBuild targetPlatformTriple) (queryHost targetPlatformTriple)
-    buildArch      <- chooseSetting (queryBuild queryArch)   (queryHost queryArch)
-    buildOs        <- chooseSetting (queryBuild queryOS)     (queryHost queryOS)
-    buildVendor    <- chooseSetting (queryBuild queryVendor) (queryHost queryVendor)
-    hostPlatform   <- chooseSetting (queryHost targetPlatformTriple) (queryTarget targetPlatformTriple)
-    hostArch       <- chooseSetting (queryHost queryArch)    (queryTarget queryArch)
-    hostOs         <- chooseSetting (queryHost queryOS)      (queryTarget queryOS)
-    hostVendor     <- chooseSetting (queryHost queryVendor)  (queryTarget queryVendor)
-    ghcUnreg       <- queryTarget tgtUnregisterised
-    return . unlines $
-        [ "#if !defined(__GHCPLATFORM_H__)"
-        , "#define __GHCPLATFORM_H__"
-        , ""
-        , "#define BuildPlatform_TYPE  " ++ cppify buildPlatform
-        , "#define HostPlatform_TYPE   " ++ cppify hostPlatform
-        , ""
-        , "#define " ++ cppify buildPlatform   ++ "_BUILD 1"
-        , "#define " ++ cppify hostPlatform ++ "_HOST 1"
-        , ""
-        , "#define " ++ buildArch   ++ "_BUILD_ARCH 1"
-        , "#define " ++ hostArch ++ "_HOST_ARCH 1"
-        , "#define BUILD_ARCH " ++ show buildArch
-        , "#define HOST_ARCH "  ++ show hostArch
-        , ""
-        , "#define " ++ buildOs   ++ "_BUILD_OS 1"
-        , "#define " ++ hostOs ++ "_HOST_OS 1"
-        , "#define BUILD_OS " ++ show buildOs
-        , "#define HOST_OS "  ++ show hostOs
-        , ""
-        , "#define " ++ buildVendor   ++ "_BUILD_VENDOR 1"
-        , "#define " ++ hostVendor ++ "_HOST_VENDOR 1"
-        , "#define BUILD_VENDOR " ++ show buildVendor
-        , "#define HOST_VENDOR "  ++ show hostVendor
-        , ""
-        ]
-        ++
-        [ "#define UnregisterisedCompiler 1" | ghcUnreg ]
-        ++
-        [ ""
-        , "#endif /* __GHCPLATFORM_H__ */"
-        ]
-
 generateSettings :: Expr String
 generateSettings = do
     ctx <- getContext


=====================================
hadrian/src/Rules/Lint.hs
=====================================
@@ -22,6 +22,8 @@ lintRules = do
       cmd_ (Cwd "libraries/base") "./configure"
   "rts" -/- "include" -/- "ghcautoconf.h" %> \_ ->
       cmd_ (Cwd "rts") "./configure"
+  "rts" -/- "include" -/- "ghcplatform.h" %> \_ ->
+      cmd_ (Cwd "rts") "./configure"
 
 lint :: Action () -> Action ()
 lint lintAction = do
@@ -68,7 +70,6 @@ base = do
   let includeDirs =
         [ "rts/include"
         , "libraries/base/include"
-        , stage1RtsInc
         ]
   runHLint includeDirs [] "libraries/base"
 


=====================================
hadrian/src/Rules/Register.hs
=====================================
@@ -51,12 +51,6 @@ configurePackageRules = do
           isGmp <- (== "gmp") <$> interpretInContext ctx getBignumBackend
           when isGmp $
             need [buildP -/- "include/ghc-gmp.h"]
-        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 this, so we must ensure it exists
-          -- for that check to work.
-          need [buildP -/- "include/ghcplatform.h"]
         Cabal.configurePackage ctx
 
     root -/- "**/autogen/cabal_macros.h" %> \out -> do


=====================================
hadrian/src/Rules/SourceDist.hs
=====================================
@@ -156,7 +156,8 @@ prepareTree dest = do
       , pkgPath terminfo -/- "configure"
       , "configure"
       , "aclocal.m4"
-      , "mk" -/- "config.h.in" ]
+      , "mk" -/- "unused.h.in"
+      ]
 
     copyAlexHappyFiles =
       forM_ alexHappyFiles $ \(stg, pkg, inp, out) -> do


=====================================
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" ]
@@ -281,8 +281,8 @@ rtsPackageArgs = package rts ? do
     targetArch     <- queryTarget queryArch
     targetOs       <- queryTarget queryOS
     targetVendor   <- queryTarget queryVendor
-    ghcUnreg       <- yesNo <$> queryTarget tgtUnregisterised
-    ghcEnableTNC   <- yesNo <$> queryTarget tgtTablesNextToCode
+    ghcUnreg       <- queryTarget tgtUnregisterised
+    ghcEnableTNC   <- queryTarget tgtTablesNextToCode
     rtsWays        <- getRtsWays
     way            <- getWay
     path           <- getBuildPath
@@ -355,8 +355,8 @@ rtsPackageArgs = package rts ? do
             , "-DTargetArch="                ++ show targetArch
             , "-DTargetOS="                  ++ show targetOs
             , "-DTargetVendor="              ++ show targetVendor
-            , "-DGhcUnregisterised="         ++ show ghcUnreg
-            , "-DTablesNextToCode="          ++ show ghcEnableTNC
+            , "-DGhcUnregisterised="         ++ show (yesNo ghcUnreg)
+            , "-DTablesNextToCode="          ++ show (yesNo ghcEnableTNC)
             , "-DRtsWay=\"rts_" ++ show way ++ "\""
             ]
 
@@ -401,8 +401,21 @@ 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"
+          , ghcUnreg                        `cabalFlag` "unregisterised"
+          , ghcEnableTNC                    `cabalFlag` "tables-next-to-code"
           , 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_cc_supports__atomics.m4
=====================================
@@ -61,12 +61,4 @@ AC_DEFUN([FP_CC_SUPPORTS__ATOMICS],
         AC_MSG_RESULT(no)
         AC_MSG_ERROR([C compiler needs to support __atomic primitives.])
     ])
-    AC_DEFINE([HAVE_C11_ATOMICS], [1], [Does C compiler support __atomic primitives?])
-    if test "$need_latomic" = 1; then
-        AC_SUBST([NeedLibatomic],[YES])
-    else
-        AC_SUBST([NeedLibatomic],[NO])
-    fi
-    AC_DEFINE_UNQUOTED([NEED_ATOMIC_LIB], [$need_latomic],
-        [Define to 1 if we need -latomic.])
 ])


=====================================
m4/fptools_set_haskell_platform_vars.m4
=====================================
@@ -82,7 +82,7 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_VARS_SHELL_FUNCTIONS],
         solaris2)
             test -z "[$]2" || eval "[$]2=OSSolaris2"
             ;;
-        mingw32|windows)
+        mingw32|mingw64|windows)
             test -z "[$]2" || eval "[$]2=OSMinGW32"
             ;;
         freebsd)
@@ -162,8 +162,6 @@ AC_DEFUN([GHC_SUBSECTIONS_VIA_SYMBOLS],
             TargetHasSubsectionsViaSymbols=NO
          else
             TargetHasSubsectionsViaSymbols=YES
-            AC_DEFINE([HAVE_SUBSECTIONS_VIA_SYMBOLS],[1],
-                   [Define to 1 if Apple-style dead-stripping is supported.])
          fi
         ],
         [TargetHasSubsectionsViaSymbols=NO


=====================================
m4/ghc_convert_os.m4
=====================================
@@ -22,7 +22,7 @@ AC_DEFUN([GHC_CONVERT_OS],[
       openbsd*)
         $3="openbsd"
         ;;
-      windows|mingw32)
+      windows|mingw32|mingw64)
         $3="mingw32"
         ;;
       # As far as I'm aware, none of these have relevant variants


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


=====================================
rts/configure.ac
=====================================
@@ -22,17 +22,153 @@ dnl     #define SIZEOF_CHAR 0
 dnl   recently.
 AC_PREREQ([2.69])
 
+AC_CONFIG_FILES([ghcplatform.h.top])
+
 AC_CONFIG_HEADERS([ghcautoconf.h.autoconf])
 
+AC_ARG_ENABLE(asserts-all-ways,
+[AS_HELP_STRING([--enable-asserts-all-ways],
+                [Usually ASSERTs are only compiled in the DEBUG way,
+                 this will enable them in all ways.])],
+  [FP_CAPITALIZE_YES_NO(["$enableval"], [EnableAssertsAllWays])],
+  [EnableAssertsAllWays=NO]
+)
+if test "$enable_asserts_all_ways" = "yes" ; then
+   AC_DEFINE([USE_ASSERTS_ALL_WAYS], [1], [Compile-in ASSERTs in all ways.])
+fi
+
+AC_ARG_ENABLE(native-io-manager,
+[AS_HELP_STRING([--enable-native-io-manager],
+                [Enable the native I/O manager by default.])],
+  [FP_CAPITALIZE_YES_NO(["$enableval"], [EnableNativeIOManager])],
+  [EnableNativeIOManager=NO]
+)
+if test "$EnableNativeIOManager" = "YES"; then
+  AC_DEFINE_UNQUOTED([DEFAULT_NATIVE_IO_MANAGER], [1], [Enable Native I/O manager as default.])
+fi
+
 # We have to run these unconditionally, but we may discard their
 # results in the following code
 AC_CANONICAL_BUILD
 AC_CANONICAL_HOST
 
+dnl ** Do a build with tables next to code?
+dnl --------------------------------------------------------------
+
+AS_IF(
+  [test "$CABAL_FLAG_tables_next_to_code" = 1],
+  [AC_DEFINE([TABLES_NEXT_TO_CODE], [1], [Define to 1 if info tables are laid out next to code])])
+
+dnl detect compiler (prefer gcc over clang) and set $CC (unless CC already set),
+dnl later CC is copied to CC_STAGE{1,2,3}
+AC_PROG_CC([cc gcc clang])
+
+dnl make extensions visible to allow feature-tests to detect them lateron
+AC_USE_SYSTEM_EXTENSIONS
+
+dnl ** Used to determine how to compile ghc-prim's atomics.c, used by
+dnl    unregisterised, Sparc, and PPC backends. Also determines whether
+dnl    linking to libatomic is required for atomic operations, e.g. on
+dnl    RISCV64 GCC.
+FP_CC_SUPPORTS__ATOMICS
+AC_DEFINE([HAVE_C11_ATOMICS], [1], [Does C compiler support __atomic primitives?])
+AC_DEFINE_UNQUOTED([NEED_ATOMIC_LIB], [$need_latomic],
+    [Define to 1 if we need -latomic for sub-word atomic operations.])
+
+dnl ** look to see if we have a C compiler using an llvm back end.
+dnl
+FP_CC_LLVM_BACKEND
+AS_IF([test x"$CcLlvmBackend" = x"YES"],
+  [AC_DEFINE([CC_LLVM_BACKEND], [1], [Define (to 1) if C compiler has an LLVM back end])])
+
+GHC_CONVERT_PLATFORM_PARTS([build], [Build])
+FPTOOLS_SET_PLATFORM_VARS([build],[Build])
+FPTOOLS_SET_HASKELL_PLATFORM_VARS([Build])
+
 GHC_CONVERT_PLATFORM_PARTS([host], [Host])
 FPTOOLS_SET_PLATFORM_VARS([host], [Host])
 FPTOOLS_SET_HASKELL_PLATFORM_VARS([Host])
 
+GHC_SUBSECTIONS_VIA_SYMBOLS
+AS_IF([test x"${TargetHasSubsectionsViaSymbols}" = x"YES"],
+  [AC_DEFINE([HAVE_SUBSECTIONS_VIA_SYMBOLS],[1],
+    [Define to 1 if Apple-style dead-stripping is supported.])])
+
+dnl --------------------------------------------------
+dnl * Platform header file and syscall feature tests
+dnl ### checking the state of the local header files and syscalls ###
+
+dnl ** Enable large file support.  NB. do this before testing the type of
+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)
+
+
+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], , ,
+[#define _POSIX_SOURCE 1
+#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 math library
 dnl    Keep that check as early as possible.
 dnl    as we need to know whether we need libm
@@ -140,7 +276,6 @@ AC_ARG_ENABLE(large-address-space,
 )
 
 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
@@ -223,19 +358,41 @@ dnl --------------------------------------------------------------
 AC_OUTPUT
 
 dnl ######################################################################
-dnl Generate ghcautoconf.h
+dnl Generate ghcplatform.h
 dnl ######################################################################
 
 [
 mkdir -p include
+
+touch include/ghcplatform.h
+> include/ghcplatform.h
+
+cat ghcplatform.h.top                          >> include/ghcplatform.h
+]
+
+dnl ** Do an unregisterised build?
+dnl --------------------------------------------------------------
+AS_IF(
+  [test "$CABAL_FLAG_unregisterised" = 1],
+  [echo "#define UnregisterisedCompiler 1"     >> include/ghcplatform.h])
+
+[
+cat $srcdir/ghcplatform.h.bottom               >> include/ghcplatform.h
+]
+
+dnl ######################################################################
+dnl Generate ghcautoconf.h
+dnl ######################################################################
+
+[
 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
+# Copy the contents of ghcautoconf.h.autoconf, turning '#define PACKAGE_FOO
 # "blah"' into '/* #undef PACKAGE_FOO */' to avoid clashes.
-cat $srcdir/../mk/config.h ghcautoconf.h.autoconf | sed \
+cat ghcautoconf.h.autoconf | sed \
    -e 's,^\([	 ]*\)#[	 ]*define[	 ][	 ]*\(PACKAGE_[A-Z]*\)[	 ][ 	]*".*".*$,\1/* #undef \2 */,' \
    -e '/__GLASGOW_HASKELL/d' \
    -e '/REMOVE ME/d' \


=====================================
rts/ghcplatform.h.bottom
=====================================
@@ -0,0 +1,2 @@
+
+#endif /* __GHCPLATFORM_H__ */


=====================================
rts/ghcplatform.h.top.in
=====================================
@@ -0,0 +1,23 @@
+#if !defined(__GHCPLATFORM_H__)
+#define __GHCPLATFORM_H__
+
+#define BuildPlatform_TYPE  @BuildPlatform_CPP@
+#define HostPlatform_TYPE   @HostPlatform_CPP@
+
+#define @BuildPlatform_CPP at _BUILD  1
+#define @HostPlatform_CPP at _HOST  1
+
+#define @BuildArch_CPP at _BUILD_ARCH  1
+#define @HostArch_CPP at _HOST_ARCH  1
+#define BUILD_ARCH  "@BuildArch_CPP@"
+#define HOST_ARCH  "@HostArch_CPP@"
+
+#define @BuildOS_CPP at _BUILD_OS  1
+#define @HostOS_CPP at _HOST_OS  1
+#define BUILD_OS  "@BuildOS_CPP@"
+#define HOST_OS  "@HostOS_CPP@"
+
+#define @BuildVendor_CPP at _BUILD_VENDOR  1
+#define @HostVendor_CPP at _HOST_VENDOR  1
+#define BUILD_VENDOR  "@BuildVendor_CPP@"
+#define HOST_VENDOR  "@HostVendor_CPP@"


=====================================
rts/rts.cabal.in → rts/rts.cabal
=====================================
@@ -29,31 +29,35 @@ 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 unregisterised
+  default: False
+flag tables-next-to-code
+  default: False
 flag smp
   default: True
 flag find-ptr
@@ -240,7 +244,7 @@ library
 
       include-dirs: include
       includes: Rts.h
-      autogen-includes: ghcautoconf.h
+      autogen-includes: ghcautoconf.h ghcplatform.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



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ac288d14bb99657393ff69a607c568702d3c65c7...47c3672018b1480178cbf81be64537d58cc68dc7

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ac288d14bb99657393ff69a607c568702d3c65c7...47c3672018b1480178cbf81be64537d58cc68dc7
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/e77ef225/attachment-0001.html>


More information about the ghc-commits mailing list