[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 11 commits: Move function checks to RTS configure

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Mon Oct 23 10:29:54 UTC 2023



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


Commits:
02efc181 by John Ericson at 2023-10-22T02:48:55-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.

- - - - -
5f4bccab by John Ericson at 2023-10-22T02:48:55-04:00
Move over a number of C-style checks to RTS configure

- - - - -
5cf04f58 by John Ericson at 2023-10-22T02:48:55-04:00
Move/Copy more `AC_DEFINE` to RTS config

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

- - - - -
b8ce5dfe by John Ericson at 2023-10-22T02:48:55-04:00
Define `TABLES_NEXT_TO_CODE` in the RTS configure

We create a new cabal flag to facilitate this.

- - - - -
4a40271e by John Ericson at 2023-10-22T02:48:55-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.

- - - - -
16bec0a0 by John Ericson at 2023-10-22T02:48:55-04:00
Generate `ghcplatform.h` from RTS configure

We create a new cabal flag to facilitate this.

- - - - -
7dfcab2f by John Ericson at 2023-10-22T02:48:55-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.

- - - - -
c1e3719c by Cheng Shao at 2023-10-22T02:49:33-04:00
rts: drop stale mentions of MIN_UPD_SIZE

We used to have MIN_UPD_SIZE macro that describes the minimum reserved
size for thunks, so that the thunk can be overwritten in place as
indirections or blackholes. However, this macro has not been actually
defined or used anywhere since a long time ago; StgThunkHeader already
reserves a padding word for this purpose. Hence this patch which drops
stale mentions of MIN_UPD_SIZE.

- - - - -
d24b0d85 by Andrew Lelechenko at 2023-10-22T02:50:11-04:00
base changelog: move non-backported entries from 4.19 section to 4.20

Neither !10933 (check https://hackage.haskell.org/package/base-4.19.0.0/docs/src/Text.Read.Lex.html#numberToRangedRational)
nor !10189 (check https://hackage.haskell.org/package/base-4.19.0.0/docs/src/Data.List.NonEmpty.html#unzip)
were backported to `base-4.19.0.0`. Moving them to `base-4.20.0.0` section.

Also minor stylistic changes to other entries, bringing them to a uniform form.

- - - - -
f8534f46 by Alan Zimmerman at 2023-10-23T06:29:33-04:00
EPA Some tweaks to annotations

- Fix span for GRHS
- Move TrailingAnns from last match to FunBind
- Fix GADT 'where' clause span
- Capture full range for a CaseAlt Match

- - - - -
0be70e34 by Simon Hengel at 2023-10-23T06:29:35-04:00
Update primitives.rst
- - - - -


27 changed files:

- .gitignore
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- configure.ac
- distrib/cross-port
- docs/coding-style.html
- docs/rts/rts.tex
- docs/users_guide/exts/primitives.rst
- 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/base/changelog.md
- m4/fp_cc_supports__atomics.m4
- m4/fptools_set_haskell_platform_vars.m4
- m4/ghc_convert_os.m4
- rts/PrimOps.cmm
- rts/configure.ac
- + rts/ghcplatform.h.bottom
- + rts/ghcplatform.h.top.in
- rts/rts.cabal
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- testsuite/tests/parser/should_compile/T15323.stderr
- testsuite/tests/printer/Test20297.stdout


Changes:

=====================================
.gitignore
=====================================
@@ -184,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.
 


=====================================
compiler/GHC/Parser.y
=====================================
@@ -2269,7 +2269,7 @@ atype :: { LHsType GhcPs }
         | PREFIX_TILDE atype             {% acsA (\cs -> sLL $1 $> (mkBangTy (EpAnn (glR $1) [mj AnnTilde $1] cs) SrcLazy $2)) }
         | PREFIX_BANG  atype             {% acsA (\cs -> sLL $1 $> (mkBangTy (EpAnn (glR $1) [mj AnnBang $1] cs) SrcStrict $2)) }
 
-        | '{' fielddecls '}'             {% do { decls <- acsA (\cs -> (sLL $1 $> $ HsRecTy (EpAnn (glR $1) (AnnList (Just $ listAsAnchor $2) (Just $ moc $1) (Just $ mcc $3) [] []) cs) $2))
+        | '{' fielddecls '}'             {% do { decls <- acsA (\cs -> (sLL $1 $> $ HsRecTy (EpAnn (glR $1) (AnnList (listAsAnchorM $2) (Just $ moc $1) (Just $ mcc $3) [] []) cs) $2))
                                                ; checkRecordSyntax decls }}
                                                         -- Constructor sigs only
         | '(' ')'                        {% acsA (\cs -> sLL $1 $> $ HsTupleTy (EpAnn (glR $1) (AnnParen AnnParens (glAA $1) (glAA $2)) cs)
@@ -2407,7 +2407,7 @@ gadt_constrlist :: { Located ([AddEpAnn]
                           ,[LConDecl GhcPs]) } -- Returned in order
 
         : 'where' '{'        gadt_constrs '}'    {% checkEmptyGADTs $
-                                                      L (comb2 $1 $3)
+                                                      L (comb2 $1 $4)
                                                         ([mj AnnWhere $1
                                                          ,moc $2
                                                          ,mcc $4]
@@ -2588,8 +2588,9 @@ rhs     :: { Located (GRHSs GhcPs (LHsExpr GhcPs)) }
         : '=' exp wherebinds    {% runPV (unECP $2) >>= \ $2 ->
                                   do { let L l (bs, csw) = adaptWhereBinds $3
                                      ; let loc = (comb3 $1 $2 (L l bs))
+                                     ; let locg = (comb2 $1 $2)
                                      ; acs (\cs ->
-                                       sL loc (GRHSs csw (unguardedRHS (EpAnn (anc $ rs loc) (GrhsAnn Nothing (mj AnnEqual $1)) cs) loc $2)
+                                       sL loc (GRHSs csw (unguardedRHS (EpAnn (anc $ rs locg) (GrhsAnn Nothing (mj AnnEqual $1)) cs) locg $2)
                                                       bs)) } }
         | gdrhs wherebinds      {% do { let {L l (bs, csw) = adaptWhereBinds $2}
                                       ; acs (\cs -> sL (comb2 $1 (L l bs))
@@ -3324,7 +3325,7 @@ alts1(PATS) :: { forall b. DisambECP b => PV (Located ([AddEpAnn],[LMatch GhcPs
 alt(PATS) :: { forall b. DisambECP b => PV (LMatch GhcPs (LocatedA b)) }
         : PATS alt_rhs { $2 >>= \ $2 ->
                          acsA (\cs -> sLLAsl $1 $>
-                                         (Match { m_ext = EpAnn (listAsAnchor $1) [] cs
+                                         (Match { m_ext = EpAnn (listAsAnchor $1 $>) [] cs
                                                 , m_ctxt = CaseAlt -- for \case and \cases, this will be changed during post-processing
                                                 , m_pats = $1
                                                 , m_grhss = unLoc $2 }))}
@@ -3336,7 +3337,7 @@ alt_rhs :: { forall b. DisambECP b => PV (Located (GRHSs GhcPs (LocatedA b))) }
 
 ralt :: { forall b. DisambECP b => PV (Located [LGRHS GhcPs (LocatedA b)]) }
         : '->' exp            { unECP $2 >>= \ $2 ->
-                                acs (\cs -> sLL $1 $> (unguardedRHS (EpAnn (glR $1) (GrhsAnn Nothing (mu AnnRarrow $1)) cs) (comb2 $1 $2) $2)) }
+                                acs (\cs -> sLL $1 $> (unguardedRHS (EpAnn (spanAsAnchor $ comb2 $1 (reLoc $2)) (GrhsAnn Nothing (mu AnnRarrow $1)) cs) (comb2 $1 (reLoc $2)) $2)) }
         | gdpats              { $1 >>= \gdpats ->
                                 return $ sL1 gdpats (reverse (unLoc gdpats)) }
 
@@ -4465,9 +4466,16 @@ hsDoAnn :: Located a -> LocatedAn t b -> AnnKeywordId -> AnnList
 hsDoAnn (L l _) (L ll _) kw
   = AnnList (Just $ spanAsAnchor (locA ll)) Nothing Nothing [AddEpAnn kw (srcSpan2e l)] []
 
-listAsAnchor :: [LocatedAn t a] -> Anchor
-listAsAnchor [] = spanAsAnchor noSrcSpan
-listAsAnchor (L l _:_) = spanAsAnchor (locA l)
+listAsAnchor :: [LocatedAn t a] -> Located b -> Anchor
+listAsAnchor [] (L l _) = spanAsAnchor l
+listAsAnchor (h:_) s = spanAsAnchor (comb2 (reLoc h) s)
+
+listAsAnchorM :: [LocatedAn t a] -> Maybe Anchor
+listAsAnchorM [] = Nothing
+listAsAnchorM (L l _:_) =
+  case locA l of
+    RealSrcSpan ll _ -> Just $ realSpanAsAnchor ll
+    _                -> Nothing
 
 hsTok :: Located Token -> LHsToken tok GhcPs
 hsTok (L l _) = L (mkTokenLocation l) HsTok
@@ -4528,7 +4536,6 @@ addTrailingAnnL (L (SrcSpanAnn anns l) a) ta = do
 -- Mostly use to add AnnComma, special case it to NOP if adding a zero-width annotation
 addTrailingCommaN :: MonadP m => LocatedN a -> SrcSpan -> m (LocatedN a)
 addTrailingCommaN (L (SrcSpanAnn anns l) a) span = do
-  -- cs <- getCommentsFor l
   let cs = emptyComments
   -- AZ:TODO: generalise updating comments into an annotation
   let anns' = if isZeroWidthSpan span


=====================================
compiler/GHC/Parser/Annotation.hs
=====================================
@@ -19,8 +19,8 @@ module GHC.Parser.Annotation (
   DeltaPos(..), deltaPos, getDeltaLine,
 
   EpAnn(..), Anchor(..), AnchorOperation(..),
-  spanAsAnchor, realSpanAsAnchor,
   NoAnn(..),
+  spanAsAnchor, realSpanAsAnchor, spanFromAnchor,
 
   -- ** Comments in Annotations
 
@@ -549,6 +549,9 @@ spanAsAnchor s  = Anchor (realSrcSpan s) UnchangedAnchor
 realSpanAsAnchor :: RealSrcSpan -> Anchor
 realSpanAsAnchor s  = Anchor s UnchangedAnchor
 
+spanFromAnchor :: Anchor -> SrcSpan
+spanFromAnchor a = RealSrcSpan (anchor a) Strict.Nothing
+
 -- ---------------------------------------------------------------------
 
 -- | When we are parsing we add comments that belong a particular AST


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -831,11 +831,18 @@ mkGadtDecl loc names dcol ty = do
 
   let an = EpAnn (spanAsAnchor loc) annsa (cs Semi.<> csa)
 
+  let bndrs_loc = case outer_bndrs of
+        HsOuterImplicit{} -> getLoc ty
+        HsOuterExplicit an _ ->
+          case an of
+            EpAnnNotUsed -> getLoc ty
+            an' -> SrcSpanAnn (EpAnn (entry an') noAnn emptyComments) (spanFromAnchor (entry an'))
+
   pure $ L l ConDeclGADT
                      { con_g_ext  = an
                      , con_names  = names
                      , con_dcolon = dcol
-                     , con_bndrs  = L (getLoc ty) outer_bndrs
+                     , con_bndrs  = L bndrs_loc outer_bndrs
                      , con_mb_cxt = mcxt
                      , con_g_args = args
                      , con_res_ty = res_ty


=====================================
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
 
@@ -84,8 +84,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)
 
@@ -138,27 +141,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])],
@@ -319,9 +301,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.
@@ -617,12 +596,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])
@@ -845,88 +827,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 */


=====================================
docs/rts/rts.tex
=====================================
@@ -1970,10 +1970,9 @@ Here the right-hand sides of @range@ and @ys@ are both thunks; the former
 is static while the latter is dynamic.
 
 The layout of a thunk is the same as that for a function closure.
-However, thunks must have a payload of at least @MIN_UPD_SIZE@
-words to allow it to be overwritten with a black hole and an
-indirection.  The compiler may have to add extra non-pointer fields to
-satisfy this constraint.
+However, a thunk header always contains an extra padding word at the
+end. This allows the thunk to be overwritten with an indirection,
+where the padding word will be repurposed as the indirectee pointer.
 
 \begin{center}
 \begin{tabular}{|l|l|l|l|l|}\hline


=====================================
docs/users_guide/exts/primitives.rst
=====================================
@@ -12,7 +12,7 @@ you write will be optimised to the efficient unboxed version in any
 case. And if it isn't, we'd like to know about it.
 
 All these primitive data types and operations are exported by the
-library :base-ref:`GHC.Exts.`.
+module :base-ref:`GHC.Exts.`.
 
 If you want to mention any of the primitive data types or operations in
 your program, you must first import ``GHC.Exts`` to bring them into


=====================================
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"
@@ -357,62 +357,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
=====================================
@@ -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 ++ "\""
             ]
 
@@ -414,6 +414,8 @@ rtsPackageArgs = package rts ? do
           , 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/base/changelog.md
=====================================
@@ -9,14 +9,16 @@
   * Always use `safe` call to `read` for regular files and block devices on unix if the RTS is multi-threaded, regardless of `O_NONBLOCK`.
     ([CLC proposal #166](https://github.com/haskell/core-libraries-committee/issues/166))
   * Export List from Data.List ([CLC proposal #182](https://github.com/haskell/core-libraries-committee/issues/182)).
+  * Deprecate `Data.List.NonEmpty.unzip` ([CLC proposal #86](https://github.com/haskell/core-libraries-committee/issues/86))
+  * Fix exponent overflow/underflow bugs in the `Read` instances for `Float` and `Double` ([CLC proposal #192](https://github.com/haskell/core-libraries-committee/issues/192))
 
-## 4.19.0.0 *TBA*
+## 4.19.0.0 *October 2023*
   * Add `{-# WARNING in "x-partial" #-}` to `Data.List.{head,tail}`.
     Use `{-# OPTIONS_GHC -Wno-x-partial #-}` to disable it.
     ([CLC proposal #87](https://github.com/haskell/core-libraries-committee/issues/87) and [#114](https://github.com/haskell/core-libraries-committee/issues/114))
-  * `GHC.Conc.Sync` now exports `fromThreadId :: ThreadId -> Word64`, which maps a thread to a per-process-unique identifier ([CLC proposal #117](https://github.com/haskell/core-libraries-committee/issues/117))
+  * Add `fromThreadId :: ThreadId -> Word64` to `GHC.Conc.Sync`, which maps a thread to a per-process-unique identifier ([CLC proposal #117](https://github.com/haskell/core-libraries-committee/issues/117))
   * Add `Data.List.!?` ([CLC proposal #110](https://github.com/haskell/core-libraries-committee/issues/110))
-  * `maximumBy`/`minimumBy` are now marked as `INLINE` improving performance for unpackable
+  * Mark `maximumBy`/`minimumBy` as `INLINE` improving performance for unpackable
     types significantly.
   * Add INLINABLE pragmas to `generic*` functions in Data.OldList ([CLC proposal #129](https://github.com/haskell/core-libraries-committee/issues/130))
   * Export `getSolo` from `Data.Tuple`.
@@ -34,20 +36,18 @@
   * Add `COMPLETE` pragmas to the `TypeRep`, `SSymbol`, `SChar`, and `SNat` pattern synonyms.
       ([CLC proposal #149](https://github.com/haskell/core-libraries-committee/issues/149))
   * Make `($)` representation polymorphic ([CLC proposal #132](https://github.com/haskell/core-libraries-committee/issues/132))
-  * Implemented [GHC Proposal #433](https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0433-unsatisfiable.rst),
+  * Implement [GHC Proposal #433](https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0433-unsatisfiable.rst),
     adding the class `Unsatisfiable :: ErrorMessage -> TypeError` to `GHC.TypeError`,
     which provides a mechanism for custom type errors that reports the errors in
     a more predictable behaviour than `TypeError`.
   * Add more instances for `Compose`: `Enum`, `Bounded`, `Num`, `Real`, `Integral` ([CLC proposal #160](https://github.com/haskell/core-libraries-committee/issues/160))
   * Make `(&)` representation polymorphic in the return type ([CLC proposal #158](https://github.com/haskell/core-libraries-committee/issues/158))
   * Implement `GHC.IORef.atomicSwapIORef` via a new dedicated primop `atomicSwapMutVar#` ([CLC proposal #139](https://github.com/haskell/core-libraries-committee/issues/139))
-  * Change codebuffers to use an unboxed implementation, while providing a compatibility layer using pattern synonyms. ([CLC proposal #134](https://github.com/haskell/core-libraries-committee/issues/134))
-  * Add nominal role annotations to SNat/SSymbol/SChar ([CLC proposal #170](https://github.com/haskell/core-libraries-committee/issues/170))
+  * Change `BufferCodec` to use an unboxed implementation, while providing a compatibility layer using pattern synonyms. ([CLC proposal #134](https://github.com/haskell/core-libraries-committee/issues/134))
+  * Add nominal role annotations to `SNat` / `SSymbol` / `SChar` ([CLC proposal #170](https://github.com/haskell/core-libraries-committee/issues/170))
   * Make `Semigroup`'s `stimes` specializable. ([CLC proposal #8](https://github.com/haskell/core-libraries-committee/issues/8))
-  * Deprecate `Data.List.NonEmpty.unzip` ([CLC proposal #86](https://github.com/haskell/core-libraries-committee/issues/86))
-  * Fixed exponent overflow/underflow bugs in the `Read` instances for `Float` and `Double` ([CLC proposal #192](https://github.com/haskell/core-libraries-committee/issues/192))
   * Implement `copyBytes`, `fillBytes`, `moveBytes` and `stimes` for `Data.Array.Byte.ByteArray` using primops ([CLC proposal #188](https://github.com/haskell/core-libraries-committee/issues/188))
-  * Add rewrite rules for conversion between Int64/Word64 and Float/Double on 64-bit architectures ([CLC proposal #203](https://github.com/haskell/core-libraries-committee/issues/203)).
+  * Add rewrite rules for conversion between `Int64` / `Word64` and `Float` / `Double` on 64-bit architectures ([CLC proposal #203](https://github.com/haskell/core-libraries-committee/issues/203)).
 
 ## 4.18.0.0 *March 2023*
   * Shipped with GHC 9.6.1


=====================================
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/PrimOps.cmm
=====================================
@@ -740,25 +740,15 @@ stg_atomicModifyMutVar2zh ( gcptr mv, gcptr f )
 
         obviously we can share (f x).
 
-         z = [stg_ap_2 f x]  (max (HS + 2) MIN_UPD_SIZE)
-         y = [stg_sel_0 z]   (max (HS + 1) MIN_UPD_SIZE)
+         z = [stg_ap_2 f x]  (SIZEOF_StgThunkHeader + WDS(2))
+         y = [stg_sel_0 z]   (SIZEOF_StgThunkHeader + WDS(1))
     */
 
-#if defined(MIN_UPD_SIZE) && MIN_UPD_SIZE > 1
-#define THUNK_1_SIZE (SIZEOF_StgThunkHeader + WDS(MIN_UPD_SIZE))
-#define TICK_ALLOC_THUNK_1() TICK_ALLOC_UP_THK(WDS(1),WDS(MIN_UPD_SIZE-1))
-#else
 #define THUNK_1_SIZE (SIZEOF_StgThunkHeader + WDS(1))
 #define TICK_ALLOC_THUNK_1() TICK_ALLOC_UP_THK(WDS(1),0)
-#endif
 
-#if defined(MIN_UPD_SIZE) && MIN_UPD_SIZE > 2
-#define THUNK_2_SIZE (SIZEOF_StgThunkHeader + WDS(MIN_UPD_SIZE))
-#define TICK_ALLOC_THUNK_2() TICK_ALLOC_UP_THK(WDS(2),WDS(MIN_UPD_SIZE-2))
-#else
 #define THUNK_2_SIZE (SIZEOF_StgThunkHeader + WDS(2))
 #define TICK_ALLOC_THUNK_2() TICK_ALLOC_UP_THK(WDS(2),0)
-#endif
 
 #define SIZE (THUNK_2_SIZE + THUNK_1_SIZE)
 
@@ -815,13 +805,8 @@ stg_atomicModifyMutVarzuzh ( gcptr mv, gcptr f )
          z = [stg_ap_2 f x]  (max (HS + 2) MIN_UPD_SIZE)
     */
 
-#if defined(MIN_UPD_SIZE) && MIN_UPD_SIZE > 2
-#define THUNK_SIZE (SIZEOF_StgThunkHeader + WDS(MIN_UPD_SIZE))
-#define TICK_ALLOC_THUNK() TICK_ALLOC_UP_THK(WDS(2),WDS(MIN_UPD_SIZE-2))
-#else
 #define THUNK_SIZE (SIZEOF_StgThunkHeader + WDS(2))
 #define TICK_ALLOC_THUNK() TICK_ALLOC_UP_THK(WDS(2),0)
-#endif
 
     HP_CHK_GEN_TICKY(THUNK_SIZE);
 


=====================================
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
=====================================
@@ -54,6 +54,10 @@ flag static-libzstd
   default: False
 flag leading-underscore
   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


=====================================
testsuite/tests/parser/should_compile/DumpSemis.stderr
=====================================
@@ -1829,7 +1829,7 @@
                      (Match
                       (EpAnn
                        (Anchor
-                        { DumpSemis.hs:39:6 }
+                        { DumpSemis.hs:39:6-13 }
                         (UnchangedAnchor))
                        []
                        (EpaComments
@@ -1862,7 +1862,7 @@
                          (GRHS
                           (EpAnn
                            (Anchor
-                            { DumpSemis.hs:39:8-9 }
+                            { DumpSemis.hs:39:8-13 }
                             (UnchangedAnchor))
                            (GrhsAnn
                             (Nothing)
@@ -1898,7 +1898,7 @@
                      (Match
                       (EpAnn
                        (Anchor
-                        { DumpSemis.hs:40:6 }
+                        { DumpSemis.hs:40:6-13 }
                         (UnchangedAnchor))
                        []
                        (EpaComments
@@ -1931,7 +1931,7 @@
                          (GRHS
                           (EpAnn
                            (Anchor
-                            { DumpSemis.hs:40:8-9 }
+                            { DumpSemis.hs:40:8-13 }
                             (UnchangedAnchor))
                            (GrhsAnn
                             (Nothing)
@@ -1969,7 +1969,7 @@
                      (Match
                       (EpAnn
                        (Anchor
-                        { DumpSemis.hs:41:6 }
+                        { DumpSemis.hs:41:6-13 }
                         (UnchangedAnchor))
                        []
                        (EpaComments
@@ -2002,7 +2002,7 @@
                          (GRHS
                           (EpAnn
                            (Anchor
-                            { DumpSemis.hs:41:8-9 }
+                            { DumpSemis.hs:41:8-13 }
                             (UnchangedAnchor))
                            (GrhsAnn
                             (Nothing)
@@ -2042,7 +2042,7 @@
                      (Match
                       (EpAnn
                        (Anchor
-                        { DumpSemis.hs:42:6 }
+                        { DumpSemis.hs:42:6-13 }
                         (UnchangedAnchor))
                        []
                        (EpaComments
@@ -2075,7 +2075,7 @@
                          (GRHS
                           (EpAnn
                            (Anchor
-                            { DumpSemis.hs:42:8-9 }
+                            { DumpSemis.hs:42:8-13 }
                             (UnchangedAnchor))
                            (GrhsAnn
                             (Nothing)
@@ -2100,3 +2100,5 @@
                         (NoExtField)))))]))))))]
             (EmptyLocalBinds
              (NoExtField)))))])))))]))
+
+


=====================================
testsuite/tests/parser/should_compile/T15323.stderr
=====================================
@@ -100,7 +100,14 @@
              (EpaSpan { T15323.hs:6:17-18 }))
             (HsNormalTok))
            (L
-            (SrcSpanAnn (EpAnnNotUsed) { T15323.hs:6:20-54 })
+            (SrcSpanAnn (EpAnn
+                         (Anchor
+                          { T15323.hs:6:20-25 }
+                          (UnchangedAnchor))
+                         (AnnListItem
+                          [])
+                         (EpaComments
+                          [])) { T15323.hs:6:20-25 })
             (HsOuterExplicit
              (EpAnn
               (Anchor


=====================================
testsuite/tests/printer/Test20297.stdout
=====================================
@@ -82,11 +82,11 @@
             [(L
               (SrcSpanAnn
                (EpAnnNotUsed)
-               { Test20297.hs:(5,5)-(7,7) })
+               { Test20297.hs:5:5-7 })
               (GRHS
                (EpAnn
                 (Anchor
-                 { Test20297.hs:(5,5)-(7,7) }
+                 { Test20297.hs:5:5-7 }
                  (UnchangedAnchor))
                 (GrhsAnn
                  (Nothing)
@@ -182,11 +182,11 @@
             [(L
               (SrcSpanAnn
                (EpAnnNotUsed)
-               { Test20297.hs:(9,5)-(11,26) })
+               { Test20297.hs:9:5-7 })
               (GRHS
                (EpAnn
                 (Anchor
-                 { Test20297.hs:(9,5)-(11,26) }
+                 { Test20297.hs:9:5-7 }
                  (UnchangedAnchor))
                 (GrhsAnn
                  (Nothing)
@@ -422,11 +422,11 @@
             [(L
               (SrcSpanAnn
                (EpAnnNotUsed)
-               { Test20297.ppr.hs:(4,3)-(5,7) })
+               { Test20297.ppr.hs:4:3-5 })
               (GRHS
                (EpAnn
                 (Anchor
-                 { Test20297.ppr.hs:(4,3)-(5,7) }
+                 { Test20297.ppr.hs:4:3-5 }
                  (UnchangedAnchor))
                 (GrhsAnn
                  (Nothing)
@@ -508,11 +508,11 @@
             [(L
               (SrcSpanAnn
                (EpAnnNotUsed)
-               { Test20297.ppr.hs:(7,3)-(9,24) })
+               { Test20297.ppr.hs:7:3-5 })
               (GRHS
                (EpAnn
                 (Anchor
-                 { Test20297.ppr.hs:(7,3)-(9,24) }
+                 { Test20297.ppr.hs:7:3-5 }
                  (UnchangedAnchor))
                 (GrhsAnn
                  (Nothing)
@@ -655,4 +655,3 @@
                         (EmptyLocalBinds
                          (NoExtField)))))]))))]}
               [])))))])))))]))
-



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/96719ad7617c4f55a3ead99c3e2811e2f3934928...0be70e34d14e99b8f5b9a6daa839482d49c83dcc

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/96719ad7617c4f55a3ead99c3e2811e2f3934928...0be70e34d14e99b8f5b9a6daa839482d49c83dcc
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/20231023/b6380e9f/attachment-0001.html>


More information about the ghc-commits mailing list