diff --git a/compiler/prelude/primops.txt.pp b/compiler/prelude/primops.txt.pp
index 3bf0180c455b4eb3ce53b24b151b87f8513ec0fd..29e77b13a6298f2d76d761d2cae783bd8efb0f36 100644
--- a/compiler/prelude/primops.txt.pp
+++ b/compiler/prelude/primops.txt.pp
@@ -68,8 +68,8 @@
 
 defaults
    has_side_effects = False
-   out_of_line      = False   -- See Note Note [PrimOp can_fail and has_side_effects] in PrimOp
-   can_fail         = False   -- See Note Note [PrimOp can_fail and has_side_effects] in PrimOp
+   out_of_line      = False   -- See Note [When do out-of-line primops go in primops.txt.pp]
+   can_fail         = False   -- See Note [PrimOp can_fail and has_side_effects] in PrimOp
    commutable       = False
    code_size        = { primOpCodeSizeDefault }
    strictness       = { \ arity -> mkClosedStrictSig (replicate arity topDmd) topRes }
@@ -78,15 +78,48 @@ defaults
    vector           = []
    deprecated_msg   = {}      -- A non-empty message indicates deprecation
 
+
+-- Note [When do out-of-line primops go in primops.txt.pp]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+--
+-- Out of line primops are those with a C-- implementation. But that
+-- doesn't mean they *just* have an C-- implementation. As mentioned in
+-- Note [Inlining out-of-line primops and heap checks], some out-of-line
+-- primops also have additional internal implementations under certain
+-- conditions. Now that `foreign import prim` exists, only those primops
+-- which have both internal and external implementations ought to be
+-- this file. The rest aren't really primops, since they don't need
+-- bespoke compiler support but just a general way to interface with
+-- C--. They are just foreign calls.
+--
+-- Unfortunately, for the time being most of the primops which should be
+-- moved according to the previous paragraph can't yet. There are some
+-- superficial restrictions in `foreign import prim` which mus be fixed
+-- first. Specifically, `foreign import prim` always requires:
+--
+--   - No polymorphism in type
+--   - `strictness       = <default>`
+--   - `can_fail         = False`
+--   - `has_side_effects = True`
+--
+-- https://gitlab.haskell.org/ghc/ghc/issues/16929 tracks this issue,
+-- and has a table of which external-only primops are blocked by which
+-- of these. Hopefully those restrictions are relaxed so the rest of
+-- those can be moved over.
+--
+-- 'module GHC.Prim.Ext is a temporarily "holding ground" for primops
+-- that were formally in here, until they can be given a better home.
+-- Likewise, their underlying C-- implementation need not live in the
+-- RTS either. Best case (in my view), both the C-- and `foreign import
+-- prim` can be moved to a small library tailured to the features being
+-- implemented and dependencies of those features.
+
 -- Currently, documentation is produced using latex, so contents of
 -- description fields should be legal latex. Descriptions can contain
 -- matched pairs of embedded curly brackets.
 
 #include "MachDeps.h"
 
--- We need platform defines (tests for mingw32 below).
-#include "ghc_boot_platform.h"
-
 section "The word size story."
         {Haskell98 specifies that signed integers (type {\tt Int})
          must contain at least 30 bits. GHC always implements {\tt
@@ -2797,30 +2830,6 @@ primop  WaitWriteOp "waitWrite#" GenPrimOp
    has_side_effects = True
    out_of_line      = True
 
-#if defined(mingw32_TARGET_OS)
-primop  AsyncReadOp "asyncRead#" GenPrimOp
-   Int# -> Int# -> Int# -> Addr# -> State# RealWorld-> (# State# RealWorld, Int#, Int# #)
-   {Asynchronously read bytes from specified file descriptor.}
-   with
-   has_side_effects = True
-   out_of_line      = True
-
-primop  AsyncWriteOp "asyncWrite#" GenPrimOp
-   Int# -> Int# -> Int# -> Addr# -> State# RealWorld-> (# State# RealWorld, Int#, Int# #)
-   {Asynchronously write bytes from specified file descriptor.}
-   with
-   has_side_effects = True
-   out_of_line      = True
-
-primop  AsyncDoProcOp "asyncDoProc#" GenPrimOp
-   Addr# -> Addr# -> State# RealWorld-> (# State# RealWorld, Int#, Int# #)
-   {Asynchronously perform procedure (first arg), passing it 2nd arg.}
-   with
-   has_side_effects = True
-   out_of_line      = True
-
-#endif
-
 ------------------------------------------------------------------------
 section "Concurrency primitives"
 ------------------------------------------------------------------------
@@ -3413,13 +3422,6 @@ primop  TraceMarkerOp "traceMarker#" GenPrimOp
    has_side_effects = True
    out_of_line      = True
 
-primop  GetThreadAllocationCounter "getThreadAllocationCounter#" GenPrimOp
-   State# RealWorld -> (# State# RealWorld, INT64 #)
-   { Retrieves the allocation counter for the current thread. }
-   with
-   has_side_effects = True
-   out_of_line      = True
-
 primop  SetThreadAllocationCounter "setThreadAllocationCounter#" GenPrimOp
    INT64 -> State# RealWorld -> State# RealWorld
    { Sets the allocation counter for the current thread to the given value. }
diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs
index 264914681623b35954437c9baf721714e31c53e7..d0e181c74206a29422b751cb1f8744f2692cf1ce 100644
--- a/libraries/base/GHC/Base.hs
+++ b/libraries/base/GHC/Base.hs
@@ -116,7 +116,7 @@ module GHC.Base
         module GHC.Magic,
         module GHC.Types,
         module GHC.Prim,        -- Re-export GHC.Prim and [boot] GHC.Err,
-                                -- to avoid lots of people having to
+        module GHC.Prim.Ext,    -- to avoid lots of people having to
         module GHC.Err,         -- import it explicitly
         module GHC.Maybe
   )
@@ -127,6 +127,7 @@ import GHC.Classes
 import GHC.CString
 import GHC.Magic
 import GHC.Prim
+import GHC.Prim.Ext
 import GHC.Err
 import GHC.Maybe
 import {-# SOURCE #-} GHC.IO (failIO,mplusIO)
diff --git a/libraries/base/GHC/Conc/Windows.hs b/libraries/base/GHC/Conc/Windows.hs
index ed5e0452a0cf24d957dd75d2c541e3b5f13dc916..e7127ab5ef5eae833121b202d4fe7356e83a05b1 100644
--- a/libraries/base/GHC/Conc/Windows.hs
+++ b/libraries/base/GHC/Conc/Windows.hs
@@ -52,6 +52,7 @@ import GHC.Real (div, fromIntegral)
 import GHC.Show (Show)
 import GHC.Word (Word32, Word64)
 import GHC.Windows
+import GHC.Prim.Ext
 
 #if defined(mingw32_HOST_OS)
 # if defined(i386_HOST_ARCH)
diff --git a/libraries/base/GHC/Exts.hs b/libraries/base/GHC/Exts.hs
index 9fc1a638fc0e09d9d42880325c944e2f72d1df6a..622902a6731f57023003903e0c766408bf944f50 100755
--- a/libraries/base/GHC/Exts.hs
+++ b/libraries/base/GHC/Exts.hs
@@ -29,6 +29,7 @@ module GHC.Exts
 
         -- * Primitive operations
         module GHC.Prim,
+        module GHC.Prim.Ext,
         shiftL#, shiftRL#, iShiftL#, iShiftRA#, iShiftRL#,
         uncheckedShiftL64#, uncheckedShiftRL64#,
         uncheckedIShiftL64#, uncheckedIShiftRA64#,
@@ -89,6 +90,7 @@ module GHC.Exts
 
 import GHC.Prim hiding ( coerce, TYPE )
 import qualified GHC.Prim
+import qualified GHC.Prim.Ext
 import GHC.Base hiding ( coerce )
 import GHC.Word
 import GHC.Int
diff --git a/libraries/ghc-prim/GHC/Prim/Ext.hs b/libraries/ghc-prim/GHC/Prim/Ext.hs
new file mode 100644
index 0000000000000000000000000000000000000000..402d5725c8ee0897c605cce841526b90edfd9aea
--- /dev/null
+++ b/libraries/ghc-prim/GHC/Prim/Ext.hs
@@ -0,0 +1,105 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE UnboxedTuples #-}
+{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE GHCForeignImportPrim #-}
+{-# LANGUAGE UnliftedFFITypes #-}
+
+-- We need platform defines (tests for mingw32 below).
+#include "ghcplatform.h"
+#include "MachDeps.h"
+
+-- See note [When do out-of-line primops go in primops.txt.pp]. More primops
+-- there are elgible according to the description below, but cannot yet be moved
+-- here because of superficial restrictions to `foreign import prim`. Hopefully
+-- that is fixed soon.
+
+-- | Extra C-- routines exposed from the RTS
+--
+-- Actual primops are emitted by the compiler itself. They are special bits of
+-- code with backend support. The foreign functions in this module aren't actual
+-- primops because the compiler doesn't care about them at all: they just are
+-- extra foreign C-- calls libraries can make into the RTS.
+--
+-- Note that 'GHC.Prim' has the same haddock section names as this module, but
+-- with descriptions. Consult that module's documentation for what each section means.
+-- are described over there.
+module GHC.Prim.Ext
+  (
+  -- 64-bit bit aliases
+    INT64
+  , WORD64
+  -- * Delay\/wait operations
+#if defined(mingw32_TARGET_OS)
+  , asyncRead#
+  , asyncWrite#
+  , asyncDoProc#
+#endif
+  -- * Misc
+  , getThreadAllocationCounter#
+  ) where
+
+import GHC.Prim
+import GHC.Types () -- Make implicit dependency known to build system
+
+default () -- Double and Integer aren't available yet
+
+------------------------------------------------------------------------
+-- 64-bit bit aliases
+------------------------------------------------------------------------
+
+type INT64 =
+#if WORD_SIZE_IN_BITS < 64
+  Int64#
+#else
+  Int#
+#endif
+
+type WORD64 =
+#if WORD_SIZE_IN_BITS < 64
+  Word64#
+#else
+  Word#
+#endif
+
+------------------------------------------------------------------------
+-- Delay/wait operations
+------------------------------------------------------------------------
+
+#if defined(mingw32_TARGET_OS)
+
+-- | Asynchronously read bytes from specified file descriptor.
+foreign import prim "stg_asyncReadzh" asyncRead#
+  :: Int#
+  -> Int#
+  -> Int#
+  -> Addr#
+  -> State# RealWorld
+  -> (# State# RealWorld, Int#, Int# #)
+
+-- | Asynchronously write bytes from specified file descriptor.
+foreign import prim "stg_asyncWritezh" asyncWrite#
+  :: Int#
+  -> Int#
+  -> Int#
+  -> Addr#
+  -> State# RealWorld
+  -> (# State# RealWorld, Int#, Int# #)
+
+-- | Asynchronously perform procedure (first arg), passing it 2nd arg.
+foreign import prim "stg_asyncDoProczh" asyncDoProc#
+  :: Addr#
+  -> Addr#
+  -> State# RealWorld
+  -> (# State# RealWorld, Int#, Int# #)
+
+#endif
+
+------------------------------------------------------------------------
+-- Misc
+------------------------------------------------------------------------
+
+-- | Retrieves the allocation counter for the current thread.
+foreign import prim "stg_getThreadAllocationCounterzh" getThreadAllocationCounter#
+  :: State# RealWorld
+  -> (# State# RealWorld, INT64 #)
diff --git a/libraries/ghc-prim/ghc-prim.cabal b/libraries/ghc-prim/ghc-prim.cabal
index bfc47c87c2d1237fb5aa5dab2c933ce436919a1e..040eb43b2777a29c1ab8cf8b563922dbc0cbfc36 100644
--- a/libraries/ghc-prim/ghc-prim.cabal
+++ b/libraries/ghc-prim/ghc-prim.cabal
@@ -45,6 +45,7 @@ Library
         GHC.Debug
         GHC.IntWord64
         GHC.Magic
+        GHC.Prim.Ext
         GHC.PrimopWrappers
         GHC.Tuple
         GHC.Types