diff --git a/compiler/GHC/Driver/Session.hs b/compiler/GHC/Driver/Session.hs
index e6e055749264846a9c158dd2509e380523252591..997eb941406dcaf81df1afbce1c43cbb28e971b4 100644
--- a/compiler/GHC/Driver/Session.hs
+++ b/compiler/GHC/Driver/Session.hs
@@ -2106,7 +2106,10 @@ dynamic_flags_deps = [
 
     ------- ways ---------------------------------------------------------------
   , make_ord_flag defGhcFlag "prof"           (NoArg (addWayDynP WayProf))
-  , make_ord_flag defGhcFlag "eventlog"       (NoArg (addWayDynP WayTracing))
+  , (Deprecated, defFlag     "eventlog"
+     $ noArgM $ \d -> do
+         deprecate "the eventlog is now enabled in all runtime system ways"
+         return d)
   , make_ord_flag defGhcFlag "debug"          (NoArg (addWayDynP WayDebug))
   , make_ord_flag defGhcFlag "threaded"       (NoArg (addWayDynP WayThreaded))
 
diff --git a/compiler/GHC/Platform/Ways.hs b/compiler/GHC/Platform/Ways.hs
index 6bb8aed87f9c726b66bc78037573c1b343936acf..955a9bcea01ec283d1686bb5daecbbddd6a3f3e4 100644
--- a/compiler/GHC/Platform/Ways.hs
+++ b/compiler/GHC/Platform/Ways.hs
@@ -68,7 +68,6 @@ data Way
   | WayThreaded      -- ^ (RTS only) Multithreaded runtime system
   | WayDebug         -- ^ Debugging, enable trace messages and extra checks
   | WayProf          -- ^ Profiling, enable cost-centre stacks and profiling reports
-  | WayTracing       -- ^ (RTS only) enable event logging (tracing)
   | WayDyn           -- ^ Dynamic linking
   deriving (Eq, Ord, Show, Read)
 
@@ -118,7 +117,6 @@ wayTag WayThreaded    = "thr"
 wayTag WayDebug       = "debug"
 wayTag WayDyn         = "dyn"
 wayTag WayProf        = "p"
-wayTag WayTracing     = "l" -- "l" for "logging"
 
 -- | Return true for ways that only impact the RTS, not the generated code
 wayRTSOnly :: Way -> Bool
@@ -127,7 +125,6 @@ wayRTSOnly WayDyn         = False
 wayRTSOnly WayProf        = False
 wayRTSOnly WayThreaded    = True
 wayRTSOnly WayDebug       = True
-wayRTSOnly WayTracing     = True
 
 -- | Filter ways that have an impact on compilation
 fullWays :: Ways -> Ways
@@ -143,7 +140,6 @@ wayDesc WayThreaded    = "Threaded"
 wayDesc WayDebug       = "Debug"
 wayDesc WayDyn         = "Dynamic"
 wayDesc WayProf        = "Profiling"
-wayDesc WayTracing     = "Tracing"
 
 -- | Turn these flags on when enabling this way
 wayGeneralFlags :: Platform -> Way -> [GeneralFlag]
@@ -159,7 +155,6 @@ wayGeneralFlags _ WayDyn      = [Opt_PIC, Opt_ExternalDynamicRefs]
     -- PIC objects can be linked into a .so, we have to compile even
     -- modules of the main program with -fPIC when using -dynamic.
 wayGeneralFlags _ WayProf     = []
-wayGeneralFlags _ WayTracing  = []
 
 -- | Turn these flags off when enabling this way
 wayUnsetGeneralFlags :: Platform -> Way -> [GeneralFlag]
@@ -170,7 +165,6 @@ wayUnsetGeneralFlags _ WayDyn      = [Opt_SplitSections]
    -- There's no point splitting when we're going to be dynamically linking.
    -- Plus it breaks compilation on OSX x86.
 wayUnsetGeneralFlags _ WayProf     = []
-wayUnsetGeneralFlags _ WayTracing  = []
 
 -- | Pass these options to the C compiler when enabling this way
 wayOptc :: Platform -> Way -> [String]
@@ -182,7 +176,6 @@ wayOptc platform WayThreaded = case platformOS platform of
 wayOptc _ WayDebug      = []
 wayOptc _ WayDyn        = []
 wayOptc _ WayProf       = ["-DPROFILING"]
-wayOptc _ WayTracing    = ["-DTRACING"]
 
 -- | Pass these options to linker when enabling this way
 wayOptl :: Platform -> Way -> [String]
@@ -198,7 +191,6 @@ wayOptl platform WayThreaded =
 wayOptl _ WayDebug      = []
 wayOptl _ WayDyn        = []
 wayOptl _ WayProf       = []
-wayOptl _ WayTracing    = []
 
 -- | Pass these options to the preprocessor when enabling this way
 wayOptP :: Platform -> Way -> [String]
@@ -207,7 +199,6 @@ wayOptP _ WayThreaded = []
 wayOptP _ WayDebug    = []
 wayOptP _ WayDyn      = []
 wayOptP _ WayProf     = ["-DPROFILING"]
-wayOptP _ WayTracing  = ["-DTRACING"]
 
 
 -- | Consult the RTS to find whether it has been built with profiling enabled.
@@ -268,7 +259,6 @@ hostWays = Set.unions
    , if hostIsProfiled then Set.singleton WayProf     else Set.empty
    , if hostIsThreaded then Set.singleton WayThreaded else Set.empty
    , if hostIsDebugged then Set.singleton WayDebug    else Set.empty
-   , if hostIsTracing  then Set.singleton WayTracing  else Set.empty
    ]
 
 -- | Host "full" ways (i.e. ways that have an impact on the compilation,
diff --git a/compiler/GHC/Unit/Info.hs b/compiler/GHC/Unit/Info.hs
index db00a9b91a382b293452dc4443c984d5a696f9b9..41142f653fff0d3d85e61ccaaf96fe69ffccc1fc 100644
--- a/compiler/GHC/Unit/Info.hs
+++ b/compiler/GHC/Unit/Info.hs
@@ -211,14 +211,8 @@ unitHsLibs namever ways0 p = map (mkDynName . addSuffix . ST.unpack) (unitLibrar
         -- the name of a shared library is libHSfoo-ghc<version>.so
         -- we leave out the _dyn, because it is superfluous
 
-        -- debug and profiled RTSs include support for -eventlog
-        ways2 |  ways1 `hasWay` WayDebug || ways1 `hasWay` WayProf
-              = removeWay WayTracing ways1
-              | otherwise
-              = ways1
-
-        tag     = waysTag (fullWays ways2)
-        rts_tag = waysTag ways2
+        tag     = waysTag (fullWays ways1)
+        rts_tag = waysTag ways1
 
         mkDynName x
          | not (ways0 `hasWay` WayDyn) = x
diff --git a/compiler/GHC/Utils/Error.hs b/compiler/GHC/Utils/Error.hs
index db8107a65f3757b946da6406b862d45468cb815b..ef6dd4f07d16af54d5df2d6cdc5925521ddd47ca 100644
--- a/compiler/GHC/Utils/Error.hs
+++ b/compiler/GHC/Utils/Error.hs
@@ -521,16 +521,8 @@ easily compute totals with tools like ghc-events-analyze (see below).
 Producing an eventlog for GHC
 -----------------------------
 
-To actually produce the eventlog, you need an eventlog-capable GHC build:
-
-  With Hadrian:
-  $ hadrian/build -j "stage1.ghc-bin.ghc.link.opts += -eventlog"
-
-  With Make:
-  $ make -j GhcStage2HcOpts+=-eventlog
-
-You can then produce an eventlog when compiling say hello.hs by simply
-doing:
+You can produce an eventlog when compiling, for instance, hello.hs by simply
+running:
 
   If GHC was built by Hadrian:
   $ _build/stage1/bin/ghc -ddump-timings hello.hs -o hello +RTS -l
diff --git a/configure.ac b/configure.ac
index 6b41a7e392cf65023748abe930d5889f469e55f3..65d949988f1df8fe6b8b39e52a8832c72bafca3b 100644
--- a/configure.ac
+++ b/configure.ac
@@ -219,14 +219,6 @@ if test "$WithGhc" != ""; then
   else
       AC_SUBST(GhcThreadedRts, NO)
   fi
-
-  dnl Same for an event-logging RTS.
-  if echo ${RTS_WAYS_STAGE0} | tr ' ' '\n' | grep '^l$' 2>&1 >/dev/null
-  then
-      AC_SUBST(GhcEventLoggingRts, YES)
-  else
-      AC_SUBST(GhcEventLoggingRts, NO)
-  fi
 fi
 
 dnl ** Must have GHC to build GHC
@@ -1260,7 +1252,6 @@ echo "\
    Bootstrapping using   : $WithGhc
       which is version   : $GhcVersion
       with threaded RTS? : $GhcThreadedRts
-      with eventlog RTS? : $GhcEventLoggingRts
 "
 
 if test "x$CcLlvmBackend" = "xYES"; then
diff --git a/docs/users_guide/9.4.1-notes.rst b/docs/users_guide/9.4.1-notes.rst
index 027385917377a96ca6a8ad503f2fd82df53ca0d9..345badec57c414d942fd757a11141d2ca6307c4c 100644
--- a/docs/users_guide/9.4.1-notes.rst
+++ b/docs/users_guide/9.4.1-notes.rst
@@ -192,6 +192,13 @@ Compiler
   type variables when given a polymorphic type. (It used to instantiate
   inferred type variables.)
 
+Runtime system
+~~~~~~~~~~~~~~~~
+
+- Support for GHC's eventlog is now enabled in all runtime system configurations,
+  eliminating the need to pass the :ghc-flag:`-eventlog` flag to use the eventlog.
+  This flag has been deprecated (:ghc-ticket:`18948`).
+
 ``base`` library
 ~~~~~~~~~~~~~~~~
 
diff --git a/docs/users_guide/phases.rst b/docs/users_guide/phases.rst
index fdb08a4209ec6195bd9b8c0864f03c5b06a3ac6c..54ed63a06c30aa3cb96f1f6f0a84deb4212d4581 100644
--- a/docs/users_guide/phases.rst
+++ b/docs/users_guide/phases.rst
@@ -1046,14 +1046,16 @@ for example).
     :type: dynamic
     :category: linking
 
+    :since: Unconditionally enabled with 9.4 and later
+
     Link the program with the "eventlog" version of the runtime system.
     A program linked in this way can generate a runtime trace of events
     (such as thread start/stop) to a binary file :file:`{program}.eventlog`,
     which can then be interpreted later by various tools. See
     :ref:`rts-eventlog` for more information.
 
-    :ghc-flag:`-eventlog` can be used with :ghc-flag:`-threaded`. It is implied by
-    :ghc-flag:`-debug`.
+    Note that as of GHC 9.4 and later eventlog support is included in
+    the RTS by default and the :ghc-flag:`-eventlog` is deprecated.
 
 .. ghc-flag:: -rtsopts[=⟨none|some|all|ignore|ignoreAll⟩]
     :shortdesc: Control whether the RTS behaviour can be tweaked via command-line
diff --git a/ghc/ghc-bin.cabal.in b/ghc/ghc-bin.cabal.in
index 8a9178a183411ac7d9b141752a0c78d626a90abc..946086b305ab40dc1f6d450f2436f4820376eaee 100644
--- a/ghc/ghc-bin.cabal.in
+++ b/ghc/ghc-bin.cabal.in
@@ -27,11 +27,6 @@ Flag threaded
     Default: True
     Manual: True
 
-Flag eventlog
-    Description: Link the ghc executable against the event-logging RTS
-    Default: True
-    Manual: True
-
 Executable ghc
     Default-Language: Haskell2010
 
@@ -94,10 +89,6 @@ Executable ghc
     if flag(threaded)
       ghc-options: -threaded
 
-    -- Same for GhcEventLoggingRts
-    if flag(eventlog)
-      ghc-options: -eventlog
-
     Other-Extensions:
         CPP
         NondecreasingIndentation
diff --git a/ghc/ghc.mk b/ghc/ghc.mk
index 627f4bc13c1a26d74b351af2743d921c3a0b8f15..fcfb61f65add4cd815b10227b8239bbfc0b1a4fe 100644
--- a/ghc/ghc.mk
+++ b/ghc/ghc.mk
@@ -67,11 +67,6 @@ else
 ghc_stage1_CONFIGURE_OPTS += -f-threaded
 endif
 
-# Same for an event-logging RTS.
-ifeq "$(GhcEventLoggingRts)" "NO"
-ghc_stage1_CONFIGURE_OPTS += -f-eventlog
-endif
-
 ifeq "$(GhcProfiled)" "YES"
 ghc_stage2_PROGRAM_WAY = p
 endif
diff --git a/hadrian/cfg/system.config.in b/hadrian/cfg/system.config.in
index ddb6f54cb61b06cd7bccd7951027cdff5e50bb27..ae70823202f3e91a441069f02dad5d5cba5d7b41 100644
--- a/hadrian/cfg/system.config.in
+++ b/hadrian/cfg/system.config.in
@@ -88,7 +88,6 @@ ghc-minor-version     = @GhcMinVersion@
 ghc-patch-level       = @GhcPatchLevel@
 
 bootstrap-threaded-rts      = @GhcThreadedRts@
-bootstrap-event-logging-rts = @GhcEventLoggingRts@
 
 project-name          = @ProjectName@
 project-version       = @ProjectVersion@
diff --git a/hadrian/doc/flavours.md b/hadrian/doc/flavours.md
index f0d34ddc905431cb2ee7fc0e52581a0dbb42de4e..3ef7ac5a3abd572d13aa015d046f1dabd14b4617 100644
--- a/hadrian/doc/flavours.md
+++ b/hadrian/doc/flavours.md
@@ -292,26 +292,16 @@ information. The following table lists ways that are built in different flavours
     <th>default<br>perf<br>prof<br>devel1<br>devel2</td>
     <td>vanilla</td>
     <td>vanilla<br>profiling<br>dynamic</td>
-    <td>logging<br>debug<br>threaded<br>threadedDebug<br>threadedLogging
-        <br>debugDynamic<br>threadedDynamic<br>threadedDebugDynamic
-        <br>loggingDynamic<br>threadedLoggingDynamic
-    </td>
-    <td>
-        logging<br>debug<br>threaded<br>threadedDebug<br>
-        threadedLogging<br>threadedProfiling
-        <br>debugDynamic<br>threadedDynamic<br>threadedDebugDynamic
-        <br>loggingDynamic<br>threadedLoggingDynamic
-    </td>
+    <td>debug<br>threaded<br>threadedDebug<br>debugDynamic<br>threadedDynamic<br>threadedDebugDynamic</td>
+    <td>debug<br>threaded<br>threadedDebug<br>threadedProfiling<br>debugDynamic<br>threadedDynamic<br>threadedDebugDynamic</td>
 </tr>
 <tr>
     <th>static</td>
     <td>vanilla</td>
     <td>vanilla<br>profiling</td>
-    <td>logging<br>debug<br>threaded<br>threadedDebug<br>threadedLogging
-    </td>
+    <td>debug<br>threaded<br>threadedDebug</td>
     <td>
-        logging<br>debug<br>threaded<br>threadedDebug<br>
-        threadedLogging<br>threadedProfiling
+        debug<br>threaded<br>threadedDebug<br>threadedProfiling
     </td>
     <td>Only in<br>prof<br>flavour</td>
     <td>Only in<br>prof<br>flavour</td>
@@ -320,14 +310,8 @@ information. The following table lists ways that are built in different flavours
     <th>quick<br>quick-validate<br>quick-debug</th>
     <td>vanilla</td>
     <td>vanilla<br>dynamic</td>
-    <td>logging<br>debug<br>threaded<br>threadedDebug<br>threadedLogging
-        <br>debugDynamic<br>threadedDynamic<br>threadedDebugDynamic
-        <br>loggingDynamic<br>threadedLoggingDynamic
-    </td>
-    <td>logging<br>debug<br>threaded<br>threadedDebug<br>threadedLogging
-        <br>debugDynamic<br>threadedDynamic<br>threadedDebugDynamic
-        <br>loggingDynamic<br>threadedLoggingDynamic
-    </td>
+    <td>debug<br>threaded<br>threadedDebug<br>debugDynamic<br>threadedDynamic<br>threadedDebugDynamic</td>
+    <td>debug<br>threaded<br>threadedDebug<br>debugDynamic<br>threadedDynamic<br>threadedDebugDynamic</td>
 </tr>
 <tr>
     <th>quickest<br>bench</th>
diff --git a/hadrian/doc/user-settings.md b/hadrian/doc/user-settings.md
index 0cc7807755e8341cb43ea3835abadbcea2859d8a..82f9964ac623d4d3c645d155ef89294cfb8e4010 100644
--- a/hadrian/doc/user-settings.md
+++ b/hadrian/doc/user-settings.md
@@ -324,15 +324,14 @@ One can alternatively supply settings from the command line or a
 For example, putting the following in a file at `_build/hadrian.settings`:
 
 ``` make
-stage1.ghc-bin.ghc.link.opts += -eventlog
+stage1.ghc-bin.ghc.link.opts += -debug
 *.base.ghc.*.opts += -v3
 ```
 
 and running hadrian with the default build root (`_build`), would respectively
-link the stage 2 GHC executable (using the stage 1 GHC) with the `-eventlog`
-flag, so that stage 2 GHC supports producing eventlogs with `+RTS -l`, and use
-`-v3` on all GHC commands used to build anything related to `base`, whatever
-the stage.
+link the stage 2 GHC executable (using the stage 1 GHC) with the `-debug`
+flag and use `-v3` on all GHC commands used to build anything related to
+`base`, whatever the stage.
 
 We could equivalently specify those settings on the command-line:
 
diff --git a/hadrian/src/Expression.hs b/hadrian/src/Expression.hs
index 821b7d5a1e89da7816527ada8a09b889ab8eda74..3d6b9b896cdb98f76b8e2ee0533433b57c9e6ec8 100644
--- a/hadrian/src/Expression.hs
+++ b/hadrian/src/Expression.hs
@@ -9,7 +9,7 @@ module Expression (
 
     -- ** Predicates
     (?), stage, stage0, stage1, stage2, notStage0, threadedBootstrapper,
-     eventLoggingBootstrapper, package, notPackage, packageOneOf,
+     package, notPackage, packageOneOf,
      libraryPackage, builder, way, input, inputs, output, outputs,
 
     -- ** Evaluation
@@ -132,10 +132,6 @@ notStage0 = notM stage0
 threadedBootstrapper :: Predicate
 threadedBootstrapper = expr (flag BootstrapThreadedRts)
 
--- | Whether or not the bootstrapping compiler provides an event-logging RTS.
-eventLoggingBootstrapper :: Predicate
-eventLoggingBootstrapper = expr (flag BootstrapEventLoggingRts)
-
 -- | Is a certain package /not/ built right now?
 notPackage :: Package -> Predicate
 notPackage = notM . package
diff --git a/hadrian/src/Settings/Builders/Ghc.hs b/hadrian/src/Settings/Builders/Ghc.hs
index 6c47c2fba1fe8209a785f34ff293808623442dfd..9dd481d7fe303e8469e0b221daa84eee2311728b 100644
--- a/hadrian/src/Settings/Builders/Ghc.hs
+++ b/hadrian/src/Settings/Builders/Ghc.hs
@@ -240,12 +240,9 @@ wayGhcArgs = do
             , (Threaded  `wayUnit` way) ? arg "-optc-DTHREADED_RTS"
             , (Debug     `wayUnit` way) ? arg "-optc-DDEBUG"
             , (Profiling `wayUnit` way) ? arg "-prof"
-            , supportsEventlog way ? arg "-eventlog"
             , (way == debug || way == debugDynamic) ?
               pure ["-ticky", "-DTICKY_TICKY"] ]
 
-  where supportsEventlog w = any (`wayUnit` w) [Logging, Profiling, Debug]
-
 packageGhcArgs :: Args
 packageGhcArgs = do
     package <- getPackage
diff --git a/hadrian/src/Settings/Default.hs b/hadrian/src/Settings/Default.hs
index 3b3498461c06dbc9a5b3cb18af478af34f318227..b13f65cd92f5f8352d394f624538a5d269391048 100644
--- a/hadrian/src/Settings/Default.hs
+++ b/hadrian/src/Settings/Default.hs
@@ -178,12 +178,10 @@ defaultRtsWays = Set.fromList <$>
   [ pure [vanilla, threaded]
   , notStage0 ? pure
       [ profiling, threadedProfiling, debugProfiling, threadedDebugProfiling
-      , logging, threadedLogging
       , debug, threadedDebug
       ]
   , notStage0 ? platformSupportsSharedLibs ? pure
-      [ dynamic, threadedDynamic, debugDynamic, loggingDynamic
-      , threadedDebugDynamic, threadedLoggingDynamic
+      [ dynamic, threadedDynamic, debugDynamic, threadedDebugDynamic
       ]
   ]
 
diff --git a/hadrian/src/Settings/Flavours/Benchmark.hs b/hadrian/src/Settings/Flavours/Benchmark.hs
index e4c5de0199d7ef01b1425048213ee182ebbc7833..4e5cea0635de11093c980c02ef5c696b6735e2dc 100644
--- a/hadrian/src/Settings/Flavours/Benchmark.hs
+++ b/hadrian/src/Settings/Flavours/Benchmark.hs
@@ -11,7 +11,7 @@ benchmarkFlavour = defaultFlavour
     { name = "bench"
     , args = defaultBuilderArgs <> benchmarkArgs <> defaultPackageArgs
     , libraryWays = pure $ Set.fromList [vanilla]
-    , rtsWays = pure $ Set.fromList [vanilla, threaded, logging, threadedLogging] }
+    , rtsWays = pure $ Set.fromList [vanilla, threaded] }
 
 benchmarkArgs :: Args
 benchmarkArgs = sourceArgs SourceArgs
diff --git a/hadrian/src/Settings/Flavours/Development.hs b/hadrian/src/Settings/Flavours/Development.hs
index 7e83c5641d7164a66cac7ff034b8d2d25ea0bc76..75c0886bce9ba2099347de4dfb88462d7926e58f 100644
--- a/hadrian/src/Settings/Flavours/Development.hs
+++ b/hadrian/src/Settings/Flavours/Development.hs
@@ -13,7 +13,7 @@ developmentFlavour ghcStage = defaultFlavour
     { name = "devel" ++ show (fromEnum ghcStage)
     , args = defaultBuilderArgs <> developmentArgs ghcStage <> defaultPackageArgs
     , libraryWays = pure $ Set.fromList [vanilla]
-    , rtsWays = pure $ Set.fromList [vanilla, logging, debug, threaded, threadedLogging, threadedDebug]
+    , rtsWays = pure $ Set.fromList [vanilla, debug, threaded, threadedDebug]
     , dynamicGhcPrograms = return False
     , ghcDebugAssertions = True }
 
diff --git a/hadrian/src/Settings/Flavours/Quick.hs b/hadrian/src/Settings/Flavours/Quick.hs
index 2ddf45b1a1ba042e407ba28f077fb3af797b337a..afffa4ceb754631f6f3f7e636b93a4e33e41e3df 100644
--- a/hadrian/src/Settings/Flavours/Quick.hs
+++ b/hadrian/src/Settings/Flavours/Quick.hs
@@ -23,11 +23,10 @@ quickFlavour = defaultFlavour
     , rtsWays     = Set.fromList <$>
                     mconcat
                     [ pure
-                      [ vanilla, threaded, logging, debug
-                      , threadedDebug, threadedLogging, threaded ]
+                      [ vanilla, threaded, debug
+                      , threadedDebug, threaded ]
                     , notStage0 ? platformSupportsSharedLibs ? pure
-                      [ dynamic, debugDynamic, threadedDynamic, loggingDynamic
-                      , threadedDebugDynamic, threadedLoggingDynamic ]
+                      [ dynamic, debugDynamic, threadedDynamic, threadedDebugDynamic ]
                     ] }
 
 quickArgs :: Args
diff --git a/hadrian/src/Settings/Flavours/QuickCross.hs b/hadrian/src/Settings/Flavours/QuickCross.hs
index 35b0dcc98859d45c9141e1fcb1965b3d9d163f02..45e23402e4375ea14a9203a97b8384efcc93eb09 100644
--- a/hadrian/src/Settings/Flavours/QuickCross.hs
+++ b/hadrian/src/Settings/Flavours/QuickCross.hs
@@ -20,11 +20,10 @@ quickCrossFlavour = defaultFlavour
     , rtsWays     = Set.fromList <$>
                     mconcat
                     [ pure
-                      [ vanilla, threaded, logging, debug
-                      , threadedDebug, threadedLogging, threaded ]
+                      [ vanilla, threaded, debug, threadedDebug, threaded ]
                     , notStage0 ? platformSupportsSharedLibs ? pure
-                      [ dynamic, debugDynamic, threadedDynamic, loggingDynamic
-                      , threadedDebugDynamic, threadedLoggingDynamic ]
+                      [ dynamic, debugDynamic, threadedDynamic
+                      , threadedDebugDynamic ]
                     ] }
 
 quickCrossArgs :: Args
diff --git a/hadrian/src/Settings/Flavours/Quickest.hs b/hadrian/src/Settings/Flavours/Quickest.hs
index 6ab1ed306806925f40c2c4aae47857e2cac5bd13..ee695d99b1f0012d6e7f2cce3391929429bee1c8 100644
--- a/hadrian/src/Settings/Flavours/Quickest.hs
+++ b/hadrian/src/Settings/Flavours/Quickest.hs
@@ -12,7 +12,7 @@ quickestFlavour = defaultFlavour
     { name        = "quickest"
     , args        = defaultBuilderArgs <> quickestArgs <> defaultPackageArgs
     , libraryWays = pure (Set.fromList [vanilla])
-    , rtsWays     = pure (Set.fromList [vanilla, threaded, threadedLogging, logging])
+    , rtsWays     = pure (Set.fromList [vanilla, threaded])
     , dynamicGhcPrograms = return False }
 
 quickestArgs :: Args
diff --git a/hadrian/src/Settings/Flavours/Validate.hs b/hadrian/src/Settings/Flavours/Validate.hs
index 913e431b58ca14995bb5359696041c46d0541dcb..e722d16061bce668f903cdadb6fd17b70408fdff 100644
--- a/hadrian/src/Settings/Flavours/Validate.hs
+++ b/hadrian/src/Settings/Flavours/Validate.hs
@@ -18,10 +18,9 @@ validateFlavour = werror $ defaultFlavour
                             , notStage0 ? platformSupportsSharedLibs ? pure [dynamic]
                             ]
     , rtsWays = Set.fromList <$>
-                mconcat [ pure [vanilla, threaded, debug, logging, threadedDebug, threadedLogging]
+                mconcat [ pure [vanilla, threaded, debug, threadedDebug]
                         , notStage0 ? platformSupportsSharedLibs ? pure
                             [ dynamic, threadedDynamic, debugDynamic, threadedDebugDynamic
-                            , loggingDynamic, threadedLoggingDynamic
                             ]
                         ]
     }
diff --git a/hadrian/src/Settings/Packages.hs b/hadrian/src/Settings/Packages.hs
index d4b8810810fb34c96063abe0359fc5a02cd40ccb..d88c96115e6c6dad6462bf73d1c1cdc6bdf9c762 100644
--- a/hadrian/src/Settings/Packages.hs
+++ b/hadrian/src/Settings/Packages.hs
@@ -94,9 +94,6 @@ packageArgs = do
                   -- We build a threaded stage N, N>1 if the configuration calls
                   -- for it.
                   ((ghcThreaded <$> expr flavour) `cabalFlag` "threaded")
-              -- Don't try to build stage 1 with an event-logging RTS if
-              -- the bootstrapping compiler doesn't support it.
-            , orM [notStage0, eventLoggingBootstrapper] `cabalFlag` "eventlog"
             ]
           ]
 
@@ -376,7 +373,6 @@ rtsPackageArgs = package rts ? do
         [ builder (Cabal Flags) ? mconcat
           [ any (wayUnit Profiling) rtsWays `cabalFlag` "profiling"
           , any (wayUnit Debug) rtsWays     `cabalFlag` "debug"
-          , any (wayUnit Logging) rtsWays   `cabalFlag` "logging"
           , any (wayUnit Dynamic) rtsWays   `cabalFlag` "dynamic"
           , useSystemFfi                    `cabalFlag` "use-system-libffi"
           , useLibffiForAdjustors           `cabalFlag` "libffi-adjustors"
diff --git a/hadrian/src/Way.hs b/hadrian/src/Way.hs
index 99aa7e28a95884f2eceab7e158bed0bf718393d6..044d7816612d33fe80ebc4160bc8d634025f702e 100644
--- a/hadrian/src/Way.hs
+++ b/hadrian/src/Way.hs
@@ -1,10 +1,10 @@
 module Way (
     WayUnit (..), Way, wayUnit, addWayUnit, removeWayUnit, wayFromUnits, allWays,
 
-    vanilla, profiling, dynamic, profilingDynamic, threaded, debug, logging,
-    threadedDebug, threadedProfiling, threadedLogging, threadedDynamic,
+    vanilla, profiling, dynamic, profilingDynamic, threaded, debug,
+    threadedDebug, threadedProfiling, threadedDynamic,
     threadedDebugProfiling, threadedDebugDynamic, threadedProfilingDynamic,
-    threadedLoggingDynamic, debugProfiling, debugDynamic, loggingDynamic,
+    debugProfiling, debugDynamic,
 
     wayPrefix, waySuffix, hisuf, osuf, hcsuf, obootsuf, hibootsuf, ssuf
     ) where
@@ -28,10 +28,6 @@ profilingDynamic :: Way
 profilingDynamic = wayFromUnits [Profiling, Dynamic]
 
 -- RTS only ways below. See compiler/GHC/Driver/Session.hs.
--- | Build RTS with event logging.
-logging :: Way
-logging = wayFromUnits [Logging]
-
 -- | Build multithreaded RTS.
 threaded :: Way
 threaded = wayFromUnits [Threaded]
@@ -41,28 +37,25 @@ debug :: Way
 debug = wayFromUnits [Debug]
 
 -- | Various combinations of RTS only ways.
-threadedDebug, threadedProfiling, threadedLogging, threadedDynamic,
+threadedDebug, threadedProfiling, threadedDynamic,
     threadedDebugProfiling, threadedDebugDynamic, threadedProfilingDynamic,
-    threadedLoggingDynamic, debugProfiling, debugDynamic, loggingDynamic :: Way
+    debugProfiling, debugDynamic :: Way
 threadedDebug            = wayFromUnits [Threaded, Debug]
 threadedProfiling        = wayFromUnits [Threaded, Profiling]
-threadedLogging          = wayFromUnits [Threaded, Logging]
 threadedDynamic          = wayFromUnits [Threaded, Dynamic]
 threadedDebugProfiling   = wayFromUnits [Threaded, Debug, Profiling]
 threadedDebugDynamic     = wayFromUnits [Threaded, Debug, Dynamic]
 threadedProfilingDynamic = wayFromUnits [Threaded, Profiling, Dynamic]
-threadedLoggingDynamic   = wayFromUnits [Threaded, Logging, Dynamic]
 debugProfiling           = wayFromUnits [Debug, Profiling]
 debugDynamic             = wayFromUnits [Debug, Dynamic]
-loggingDynamic           = wayFromUnits [Logging, Dynamic]
 
 -- | All ways supported by the build system.
 allWays :: [Way]
 allWays =
-    [ vanilla, profiling, dynamic, profilingDynamic, threaded, debug, logging
-    , threadedDebug, threadedProfiling, threadedLogging, threadedDynamic
+    [ vanilla, profiling, dynamic, profilingDynamic, threaded, debug
+    , threadedDebug, threadedProfiling, threadedDynamic
     , threadedDebugProfiling, threadedDebugDynamic, threadedProfilingDynamic
-    , threadedLoggingDynamic, debugProfiling, debugDynamic, loggingDynamic ]
+    , debugProfiling, debugDynamic ]
 
 wayPrefix :: Way -> String
 wayPrefix way | way == vanilla = ""
diff --git a/mk/config.mk.in b/mk/config.mk.in
index a80d47abe85bf635105bfd0b97ba8301042ccc11..10ba35b79b6860b01ed1cb479eb4e7635e0d5dfc 100644
--- a/mk/config.mk.in
+++ b/mk/config.mk.in
@@ -169,9 +169,6 @@ GhcWithSMP := $(strip $(if $(filter YESNO, $(ArchSupportsSMP)$(GhcUnregisterised
 # Whether or not the bootstrapping GHC supplies a threaded RTS.
 GhcThreadedRts = @GhcThreadedRts@
 
-# Whether or not the bootstrapping GHC supplies an event-logging RTS.
-GhcEventLoggingRts = @GhcEventLoggingRts@
-
 # Whether to include GHCi in the compiler.  Depends on whether the RTS linker
 # has support for this OS/ARCH combination.
 
@@ -230,31 +227,22 @@ BuildSharedLibs=$(strip $(if $(findstring dyn,$(GhcLibWays)),YES,NO))
 # make sense here:
 #
 #   thr           : threaded
-#   thr_p         : threaded + profiled + eventlog
-#   debug         : debugging + eventlog
-#   thr_debug     : debugging + threaded, + eventlog
-#   l             : eventlog
-#   p             : profiled + eventlog
-#   thr_l         : threaded + eventlog
-#
-# Note how there are a few cases which are handled specially (in packageHsLibs)
-# to reduce the number of distinct ways,
-#
-#   debug     implies  eventlog
-#   profiled  implies  eventlog
-#
-# This means, for instance, that there is no debug_l way.
+#   thr_p         : threaded + profiled
+#   debug         : debugging
+#   thr_debug     : debugging + threaded
+#   p             : profiled
 #
-GhcRTSWays=l
+# While the eventlog used to be enabled in only a subset of ways, we now always
+# enable it.
 
 # Usually want the debug version
-GhcRTSWays += debug
+GhcRTSWays = debug
 
 # We always have the threaded versions, but note that SMP support may be disabled
 # (see GhcWithSMP).
-GhcRTSWays += thr thr_debug thr_l
+GhcRTSWays += thr thr_debug
 GhcRTSWays += $(if $(findstring p, $(GhcLibWays)),thr_p,)
-GhcRTSWays += $(if $(findstring dyn, $(GhcLibWays)),dyn debug_dyn thr_dyn thr_debug_dyn l_dyn thr_l_dyn,)
+GhcRTSWays += $(if $(findstring dyn, $(GhcLibWays)),dyn debug_dyn thr_dyn thr_debug_dyn,)
 GhcRTSWays += $(if $(findstring p, $(GhcLibWays)),thr_debug_p debug_p,)
 
 # We can only build GHCi threaded if we have a threaded RTS:
diff --git a/mk/ways.mk b/mk/ways.mk
index 4a1305e33ba30078f675223e78c208b8b5c8477d..53f900f80e35a4a195f56de5a7ec771542d736b5 100644
--- a/mk/ways.mk
+++ b/mk/ways.mk
@@ -24,13 +24,12 @@
 #    - thr:   threaded
 #    - debug: debugging
 #    - p:     profiled
-#    - l:     eventlog
 #    - dyn:   dynamically-linked
 
 #
 # The ways currently defined.
 #
-ALL_WAYS=v l debug dyn thr thr_l p_dyn p debug_dyn thr_dyn thr_p_dyn thr_debug_dyn thr_debug debug_p thr_debug_p l_dyn thr_l_dyn thr_p
+ALL_WAYS=v debug dyn thr p_dyn p debug_dyn thr_dyn thr_p_dyn thr_debug_dyn thr_debug debug_p thr_debug_p thr_p
 
 #
 # The following ways currently are treated specially,
@@ -46,11 +45,7 @@ WAY_v_HC_OPTS= -static
 
 # Way 'p':
 WAY_p_NAME=profiling
-WAY_p_HC_OPTS= -static -prof -eventlog
-
-# Way 'l':
-WAY_l_NAME=event logging
-WAY_l_HC_OPTS= -static -eventlog
+WAY_p_HC_OPTS= -static -prof
 
 #
 # These ways apply to the RTS only:
@@ -62,31 +57,27 @@ WAY_thr_HC_OPTS= -static -optc-DTHREADED_RTS
 
 # Way 'thr_p':
 WAY_thr_p_NAME=threaded profiling
-WAY_thr_p_HC_OPTS= -static -prof -eventlog -optc-DTHREADED_RTS
-
-# Way 'thr_l':
-WAY_thr_l_NAME=threaded event logging
-WAY_thr_l_HC_OPTS= -static -optc-DTHREADED_RTS -eventlog
+WAY_thr_p_HC_OPTS= -static -prof -optc-DTHREADED_RTS
 
 # Way 'debug':
 WAY_debug_NAME=debug
-WAY_debug_HC_OPTS= -static -optc-DDEBUG -ticky -DTICKY_TICKY -optc-DTICKY_TICKY -eventlog
+WAY_debug_HC_OPTS= -static -optc-DDEBUG -ticky -DTICKY_TICKY -optc-DTICKY_TICKY
 
 # Way 'debug_p':
 WAY_debug_p_NAME=debug profiled
-WAY_debug_p_HC_OPTS= -static -optc-DDEBUG -prof -eventlog
+WAY_debug_p_HC_OPTS= -static -optc-DDEBUG -prof
 
 # Way 'p':
 WAY_p_NAME=profiling
-WAY_p_HC_OPTS= -static -prof -eventlog
+WAY_p_HC_OPTS= -static -prof
 
 # Way 'thr_debug':
 WAY_thr_debug_NAME=threaded debug
-WAY_thr_debug_HC_OPTS= -static -optc-DTHREADED_RTS -optc-DDEBUG -eventlog
+WAY_thr_debug_HC_OPTS= -static -optc-DTHREADED_RTS -optc-DDEBUG
 
 # Way 'thr_debug_p':
-WAY_thr_debug_p_NAME=threaded debug profiling event logging
-WAY_thr_debug_p_HC_OPTS= -static -optc-DTHREADED_RTS -optc-DDEBUG -prof -eventlog
+WAY_thr_debug_p_NAME=threaded debug profiling
+WAY_thr_debug_p_HC_OPTS= -static -optc-DTHREADED_RTS -optc-DDEBUG -prof
 
 # Way 'dyn': build dynamic shared libraries
 WAY_dyn_NAME=dyn
@@ -94,11 +85,11 @@ WAY_dyn_HC_OPTS=-fPIC -dynamic
 
 # Way 'p_dyn':
 WAY_p_dyn_NAME=p_dyn
-WAY_p_dyn_HC_OPTS=-fPIC -dynamic -prof -eventlog
+WAY_p_dyn_HC_OPTS=-fPIC -dynamic -prof
 
 # Way 'thr_p_dyn':
 WAY_thr_p_dyn_NAME=thr_p_dyn
-WAY_thr_p_dyn_HC_OPTS=-fPIC -dynamic -prof -eventlog -optc-DTHREADED_RTS
+WAY_thr_p_dyn_HC_OPTS=-fPIC -dynamic -prof -optc-DTHREADED_RTS
 
 # Way 'thr_dyn':
 WAY_thr_dyn_NAME=thr_dyn
@@ -106,16 +97,9 @@ WAY_thr_dyn_HC_OPTS=-fPIC -dynamic -optc-DTHREADED_RTS
 
 # Way 'thr_debug_dyn':
 WAY_thr_debug_dyn_NAME=thr_debug_dyn
-WAY_thr_debug_dyn_HC_OPTS=-fPIC -dynamic -optc-DTHREADED_RTS -optc-DDEBUG -eventlog
+WAY_thr_debug_dyn_HC_OPTS=-fPIC -dynamic -optc-DTHREADED_RTS -optc-DDEBUG
 
 # Way 'debug_dyn':
 WAY_debug_dyn_NAME=debug_dyn
-WAY_debug_dyn_HC_OPTS=-fPIC -dynamic -optc-DDEBUG -ticky -DTICKY_TICKY -optc-DTICKY_TICKY -eventlog
-
-# Way 'l_dyn':
-WAY_l_dyn_NAME=event logging dynamic
-WAY_l_dyn_HC_OPTS= -fPIC -dynamic -eventlog
+WAY_debug_dyn_HC_OPTS=-fPIC -dynamic -optc-DDEBUG -ticky -DTICKY_TICKY -optc-DTICKY_TICKY
 
-# Way 'thr_l_dyn':
-WAY_thr_l_dyn_NAME=threaded event logging dynamic
-WAY_thr_l_dyn_HC_OPTS= -fPIC -dynamic -optc-DTHREADED_RTS -eventlog
diff --git a/rts/StgMiscClosures.cmm b/rts/StgMiscClosures.cmm
index c2e4071ddf49eb4e5434e4da93061010601dbedb..dbdd2d71facf14926b34f96cbf5804233654c108 100644
--- a/rts/StgMiscClosures.cmm
+++ b/rts/StgMiscClosures.cmm
@@ -18,6 +18,11 @@ import ghczmprim_GHCziTypes_Izh_info;
 import AcquireSRWLockExclusive;
 import ReleaseSRWLockExclusive;
 
+#if defined(PROF_SPIN)
+import whitehole_lockClosure_spin;
+import whitehole_lockClosure_yield;
+#endif
+
 /* ----------------------------------------------------------------------------
    Stack underflow
    ------------------------------------------------------------------------- */
diff --git a/rts/include/Cmm.h b/rts/include/Cmm.h
index 55d201d94d7b91d077d39e549e8f8225918bc2b4..0bdb704035f156a4b25e2f6e8812b1e4cdef1489 100644
--- a/rts/include/Cmm.h
+++ b/rts/include/Cmm.h
@@ -354,6 +354,7 @@
    Constants.
    -------------------------------------------------------------------------- */
 
+#include "rts/Config.h"
 #include "rts/Constants.h"
 #include "DerivedConstants.h"
 #include "rts/storage/ClosureTypes.h"
diff --git a/rts/include/rts/Config.h b/rts/include/rts/Config.h
index cb1e90a78d6471098ba2b072721a6a1d261b9ecb..c5f34638e0986b18fdc408269bd34dec2b9bfcba 100644
--- a/rts/include/rts/Config.h
+++ b/rts/include/rts/Config.h
@@ -26,12 +26,11 @@
 #define USING_LIBBFD 1
 #endif
 
-/* DEBUG and PROFILING both imply TRACING */
-#if defined(DEBUG) || defined(PROFILING)
-#if !defined(TRACING)
+/*
+ * We previously only offer the eventlog in a subset of RTS ways; we now
+ * enable it unconditionally to simplify packaging. See #18948.
+ */
 #define TRACING
-#endif
-#endif
 
 /* DEBUG implies TICKY_TICKY */
 #if defined(DEBUG)
diff --git a/rts/rts.cabal.in b/rts/rts.cabal.in
index 3602db3b9105a1e3595a8c121720a19eb1e81055..ff60f1b4564f51856287b86013b77b6968c81d4f 100644
--- a/rts/rts.cabal.in
+++ b/rts/rts.cabal.in
@@ -91,10 +91,6 @@ library
       extra-library-flavours: _debug _thr_debug
       if flag(dynamic)
         extra-dynamic-library-flavours: _debug _thr_debug
-    if flag(logging)
-      extra-library-flavours: _l _thr_l
-      if flag(dynamic)
-        extra-dynamic-library-flavours: _l _thr_l
     if flag(dynamic)
       extra-dynamic-library-flavours: _thr
 
diff --git a/testsuite/config/ghc b/testsuite/config/ghc
index 79dd1b02946d9adbd77325c495a270f7981f1d6f..4cf62776ab9e40f3b8740a0eaad3663d5b0e7f90 100644
--- a/testsuite/config/ghc
+++ b/testsuite/config/ghc
@@ -82,7 +82,7 @@ config.way_flags = {
     'sanity'       : ['-debug'],
     'threaded1'    : ['-threaded', '-debug'],
     'threaded1_ls' : ['-threaded', '-debug'],
-    'threaded2'    : ['-O', '-threaded', '-eventlog'],
+    'threaded2'    : ['-O', '-threaded'],
     'threaded2_hT' : ['-O', '-threaded'],
     'hpc'          : ['-O', '-fhpc'],
     'prof_hc_hb'   : ['-O', '-prof', '-static', '-fprof-auto'],
diff --git a/testsuite/tests/rts/Makefile b/testsuite/tests/rts/Makefile
index fe35bd4d2cc793583dda94e0fe952624888b784b..d7bb87ae91c03b7dca1258a301571e7340208c2c 100644
--- a/testsuite/tests/rts/Makefile
+++ b/testsuite/tests/rts/Makefile
@@ -121,19 +121,19 @@ KeepCafs:
 
 .PHONY: EventlogOutput1
 EventlogOutput1:
-	"$(TEST_HC)" -eventlog -v0 EventlogOutput.hs
+	"$(TEST_HC)" -v0 EventlogOutput.hs
 	./EventlogOutput +RTS -l -olhello.eventlog
 	ls hello.eventlog >/dev/null
 
 .PHONY: EventlogOutput2
 EventlogOutput2:
-	"$(TEST_HC)" -eventlog -v0 EventlogOutput.hs
+	"$(TEST_HC)" -v0 EventlogOutput.hs
 	./EventlogOutput +RTS -l
 	ls EventlogOutput.eventlog >/dev/null
 
 .PHONY: EventlogOutputNull
 EventlogOutputNull:
-	"$(TEST_HC)" -eventlog -rtsopts -v0 EventlogOutput.hs
+	"$(TEST_HC)" -rtsopts -v0 EventlogOutput.hs
 	./EventlogOutput +RTS -l --null-eventlog-writer
 	test ! -e EventlogOutput.eventlog
 
diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T
index 75dcf5ac58a65068d614ef29073c5a5b3e17fa38..d907ceff624bac2925c171298e2a4a9425bad263 100644
--- a/testsuite/tests/rts/all.T
+++ b/testsuite/tests/rts/all.T
@@ -160,11 +160,11 @@ test('rtsflags002', [ only_ways(['normal']) ], compile_and_run, ['-with-rtsopts=
 # variants of the RTS by default
 test('traceEvent', [ omit_ways(['dyn', 'ghci'] + prof_ways),
                      extra_run_opts('+RTS -ls -RTS') ],
-                   compile_and_run, ['-eventlog'])
+                   compile_and_run, [''])
 
 test('traceBinaryEvent', [ omit_ways(['dyn', 'ghci'] + prof_ways),
                            extra_run_opts('+RTS -ls -RTS') ],
-                         compile_and_run, ['-eventlog'])
+                         compile_and_run, [''])
 
 # Test that -ol flag works as expected
 test('EventlogOutput1',
@@ -209,7 +209,7 @@ test('ipeEventLog',
        # In general this test should work on Darwin - Just not on our CI.
        when(opsys('darwin'), fragile(0))
      ],
-     compile_and_run, ['ipeEventLog_lib.c -eventlog'])
+     compile_and_run, ['ipeEventLog_lib.c'])
 
 # Manually create IPE entries, force the initialization of the underlying hash map
 # and dump them to event log (stderr).
@@ -225,7 +225,7 @@ test('ipeEventLog_fromMap',
        # In general this test should work on Darwin - Just not on our CI.
        when(opsys('darwin'), fragile(0))
      ],
-     compile_and_run, ['ipeEventLog_lib.c -eventlog'])
+     compile_and_run, ['ipeEventLog_lib.c'])
 
 test('T4059', [], makefile_test, ['T4059'])
 
@@ -486,10 +486,10 @@ test('T13676',
      ghci_script, ['T13676.script'])
 test('InitEventLogging',
      [only_ways(['normal']), extra_run_opts('+RTS -RTS')],
-     compile_and_run, ['-eventlog InitEventLogging_c.c'])
+     compile_and_run, ['InitEventLogging_c.c'])
 test('RestartEventLogging',
      [only_ways(['threaded1','threaded2']), extra_run_opts('+RTS -la -RTS')],
-     compile_and_run, ['-eventlog RestartEventLogging_c.c'])
+     compile_and_run, ['RestartEventLogging_c.c'])
 
 test('T17088',
      [only_ways(['normal']), extra_run_opts('+RTS -c -A256k -RTS')],
diff --git a/testsuite/tests/rts/flags/all.T b/testsuite/tests/rts/flags/all.T
index 04c2907fce3323d87c8ad104faf62fb99f747b8f..e60e58f0c1a3b71286d95599fd9f1afe8dbc8fb7 100644
--- a/testsuite/tests/rts/flags/all.T
+++ b/testsuite/tests/rts/flags/all.T
@@ -54,4 +54,4 @@ test('T12870h',
 
 test('T20006', [extra_run_opts('+RTS --eventlog-flush-interval=1')],
     compile_and_run,
-    ['-eventlog'])
+    [''])