diff --git a/libraries/Cabal b/libraries/Cabal
index 75e340ceb9beaea9dfc4347684519b0ca3d6a8f8..baa767a90dd8c0d3bafd82b48ff8e83b779f238a 160000
--- a/libraries/Cabal
+++ b/libraries/Cabal
@@ -1 +1 @@
-Subproject commit 75e340ceb9beaea9dfc4347684519b0ca3d6a8f8
+Subproject commit baa767a90dd8c0d3bafd82b48ff8e83b779f238a
diff --git a/libraries/base/Data/Enum.hs b/libraries/base/Data/Enum.hs
new file mode 100644
index 0000000000000000000000000000000000000000..3ec83b5e5632727b165f5ce2ddf5dffe0242bcea
--- /dev/null
+++ b/libraries/base/Data/Enum.hs
@@ -0,0 +1,22 @@
+{-# LANGUAGE NoImplicitPrelude #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  Data.Enum
+-- Copyright   :  (c) The University of Glasgow, 1992-2002
+-- License     :  see libraries/base/LICENSE
+--
+-- Maintainer  :  cvs-ghc@haskell.org
+-- Stability   :  stable
+-- Portability :  non-portable (GHC extensions)
+--
+-- The 'Enum' and 'Bounded' classes.
+--
+-----------------------------------------------------------------------------
+
+module Data.Enum
+    ( Bounded(..)
+    , Enum(..)
+    ) where
+
+import GHC.Enum
diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs
index b4b6ebc4429f589410cda3b4b6d4209b84ae6f32..001af57825c4c353becf617d447367b8cff01baa 100644
--- a/libraries/base/Data/OldList.hs
+++ b/libraries/base/Data/OldList.hs
@@ -1548,13 +1548,13 @@ permutations xs0 = xs0 : perms xs0 []
     -- | @perms ts is@ is equivalent to
     --
     -- > concat
-    -- >   [ interleave {(ts!!n)} {(drop (n+1)} ts) xs []
+    -- >   [ interleave {(ts!!n)} {(drop (n+1) ts)} xs []
     -- >   | n <- [0..length ts - 1]
     -- >   , xs <- permutations (reverse (take n ts) ++ is)
     -- >   ]
     --
-    -- @{(ts!!n)}@ and @{(drop (n+1)}@ denote the values of variables @t@ and @ts@ which
-    -- appear free in the definition of @interleave@ and @interleave'@.
+    -- @{(ts!!n)}@ and @{(drop (n+1) ts)}@ denote the values of variables @t@ and @ts@
+    -- when they appear free in the definition of @interleave@ and @interleave'@.
     perms :: forall a. [a] -> [a] -> [[a]]
     perms []     _  = []
     perms (t:ts) is = foldr interleave (perms ts (t:is)) (permutations is)
@@ -1570,7 +1570,7 @@ permutations xs0 = xs0 : perms xs0 []
         interleave :: [a] -> [[a]] -> [[a]]
         interleave xs r = let (_,zs) = interleave' id xs r in zs
 
-        -- @interleave' f ys r@ is equivalent to
+        -- @interleave' {t} {ts} f ys r@ is equivalent to
         --
         -- > ( ys ++ ts
         -- > , [ f (insertAt n t ys ++ ts) | n <- [0..length ys - 1] ] ++ r
diff --git a/libraries/base/GHC/Arr.hs b/libraries/base/GHC/Arr.hs
index 307b31e9ff09b4c6b03cecea661f7e367c5e2f4f..9f24355e66f1cba281a03f010f09511b9dc8a47c 100644
--- a/libraries/base/GHC/Arr.hs
+++ b/libraries/base/GHC/Arr.hs
@@ -15,6 +15,11 @@
 --
 -- GHC\'s array implementation.
 --
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
+--
 -----------------------------------------------------------------------------
 
 module GHC.Arr (
diff --git a/libraries/base/GHC/Conc.hs b/libraries/base/GHC/Conc.hs
index fbb7521860e76c1eee6690804cdf3bb169ac4691..654d7af41ab818d1516c31b7e996ca63ad65c521 100644
--- a/libraries/base/GHC/Conc.hs
+++ b/libraries/base/GHC/Conc.hs
@@ -6,7 +6,7 @@
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  GHC.Conc
--- Copyright   :  (c) The University of Glasgow, 1994-2002
+-- Copyright   :  (c) The University of Glasgow, 1994-2023
 -- License     :  see libraries/base/LICENSE
 --
 -- Maintainer  :  cvs-ghc@haskell.org
@@ -15,6 +15,11 @@
 --
 -- Basic concurrency stuff.
 --
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
+--
 -----------------------------------------------------------------------------
 
 -- No: #hide, because bits of this module are exposed by the stm package.
diff --git a/libraries/base/GHC/Conc/IO.hs b/libraries/base/GHC/Conc/IO.hs
index 4f7795e3693bc8355d932b2ba1f06014da52d67f..f92e282d250c4976a96192c700dfc1569949d47d 100644
--- a/libraries/base/GHC/Conc/IO.hs
+++ b/libraries/base/GHC/Conc/IO.hs
@@ -18,6 +18,11 @@
 --
 -- Basic concurrency stuff.
 --
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
+--
 -----------------------------------------------------------------------------
 
 -- No: #hide, because bits of this module are exposed by the stm package.
diff --git a/libraries/base/GHC/Desugar.hs b/libraries/base/GHC/Desugar.hs
index bf25c99bb185db6ca52ac3e5161cef65e5414d36..3455d59d539ffaee6f79238b3de2ea47919cd4bc 100644
--- a/libraries/base/GHC/Desugar.hs
+++ b/libraries/base/GHC/Desugar.hs
@@ -17,6 +17,11 @@
 --
 -- Support code for desugaring in GHC
 --
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
+--
 -----------------------------------------------------------------------------
 
 module GHC.Desugar ((>>>), AnnotationWrapper(..), toAnnotationWrapper) where
diff --git a/libraries/base/GHC/Encoding/UTF8.hs b/libraries/base/GHC/Encoding/UTF8.hs
index 72ac176263fe698ab43f4b9b92f2f2b05c852c62..8098098b395199e5b96b300e4dcfc3c9a0db0c56 100644
--- a/libraries/base/GHC/Encoding/UTF8.hs
+++ b/libraries/base/GHC/Encoding/UTF8.hs
@@ -2,7 +2,21 @@
 {-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples, NoImplicitPrelude #-}
 {-# OPTIONS_GHC -O2 -fno-warn-name-shadowing #-}
 
--- | Simple UTF-8 codecs supporting non-streaming encoding/decoding.
+-- |
+-- Module      :  GHC.Encoding.UTF8
+-- Copyright   :  (c) The University of Glasgow, 1994-2023
+-- License     :  see libraries/base/LICENSE
+--
+-- Maintainer  :  cvs-ghc@haskell.org
+-- Stability   :  internal
+-- Portability :  non-portable (GHC extensions)
+--
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
+--
+-- Simple UTF-8 codecs supporting non-streaming encoding/decoding.
 -- For encoding where codepoints may be broken across buffers,
 -- see "GHC.IO.Encoding.UTF8".
 --
diff --git a/libraries/base/GHC/Event/TimeOut.hs b/libraries/base/GHC/Event/TimeOut.hs
index 4f525de1370546482e1d70f54901d2e9803dda6d..8048588b3e2cda253339ba8c8867508fc2827756 100644
--- a/libraries/base/GHC/Event/TimeOut.hs
+++ b/libraries/base/GHC/Event/TimeOut.hs
@@ -11,6 +11,11 @@
 --
 -- Common Timer definitions shared between WinIO and RIO.
 --
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
+--
 -------------------------------------------------------------------------------
 
 module GHC.Event.TimeOut where
diff --git a/libraries/base/GHC/Exception.hs b/libraries/base/GHC/Exception.hs
index 66982b00432cc9155b48bbe207aa3b77f9f3aab0..572df1e07d1fecbc5540715d03b918f50d849b52 100644
--- a/libraries/base/GHC/Exception.hs
+++ b/libraries/base/GHC/Exception.hs
@@ -20,19 +20,41 @@
 --
 -- Exceptions and exception-handling functions.
 --
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
+--
 -----------------------------------------------------------------------------
 
 module GHC.Exception
-       ( module GHC.Exception.Type
-       , throw
-       , ErrorCall(..,ErrorCall)
-       , errorCallException
-       , errorCallWithCallStackException
-         -- re-export CallStack and SrcLoc from GHC.Types
-       , CallStack, fromCallSiteList, getCallStack, prettyCallStack
-       , prettyCallStackLines, showCCSStack
-       , SrcLoc(..), prettySrcLoc
-       ) where
+    ( -- * 'Exception' class
+      Exception(..)
+
+      -- * 'SomeException'
+    , SomeException(..)
+
+      -- * Throwing
+    , throw
+
+      -- * Concrete exceptions
+      -- ** Arithmetic exceptions
+    , ArithException(..)
+    , divZeroException
+    , overflowException
+    , ratioZeroDenomException
+    , underflowException
+      -- ** 'ErrorCall'
+    , ErrorCall(..,ErrorCall)
+    , errorCallException
+    , errorCallWithCallStackException
+
+      -- * Reexports
+      -- Re-export CallStack and SrcLoc from GHC.Types
+    , CallStack, fromCallSiteList, getCallStack, prettyCallStack
+    , prettyCallStackLines, showCCSStack
+    , SrcLoc(..), prettySrcLoc
+    ) where
 
 import GHC.Base
 import GHC.Show
diff --git a/libraries/base/GHC/Exception/Type.hs b/libraries/base/GHC/Exception/Type.hs
index 7f915b0c5a9791f688d26c3848b55ce3d9677472..4721ea310e0d97c045f6878e3cd07c728bb5da4e 100644
--- a/libraries/base/GHC/Exception/Type.hs
+++ b/libraries/base/GHC/Exception/Type.hs
@@ -16,6 +16,11 @@
 --
 -- Exceptions and exception-handling functions.
 --
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
+--
 -----------------------------------------------------------------------------
 
 module GHC.Exception.Type
diff --git a/libraries/base/GHC/ExecutionStack/Internal.hsc b/libraries/base/GHC/ExecutionStack/Internal.hsc
index 87b2e419004e05d11e6fd694996e4e8164c282cf..5d616888c24dfe7c90f1521dda42f549ae794bdf 100644
--- a/libraries/base/GHC/ExecutionStack/Internal.hsc
+++ b/libraries/base/GHC/ExecutionStack/Internal.hsc
@@ -8,7 +8,12 @@
 -- Stability   :  internal
 -- Portability :  non-portable (GHC Extensions)
 --
--- Internals of the `GHC.ExecutionStack` module
+-- Internals of the "GHC.ExecutionStack" module.
+--
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
 --
 -- @since 4.9.0.0
 -----------------------------------------------------------------------------
diff --git a/libraries/base/GHC/Fingerprint/Type.hs b/libraries/base/GHC/Fingerprint/Type.hs
index 15e9d73983e89b2c3ad83f189e0c5a0d15154e54..5939cc9ba4ff1c4c2f076f4a30ef13132bedc6f4 100644
--- a/libraries/base/GHC/Fingerprint/Type.hs
+++ b/libraries/base/GHC/Fingerprint/Type.hs
@@ -1,14 +1,22 @@
 {-# LANGUAGE Trustworthy #-}
 {-# LANGUAGE NoImplicitPrelude #-}
 
--- ----------------------------------------------------------------------------
+-- |
+-- Module      :  GHC.Fingerprint.Type
+-- Copyright   :  (c) The University of Glasgow, 1994-2023
+-- License     :  see libraries/base/LICENSE
 --
---  (c) The University of Glasgow 2006
+-- Maintainer  :  cvs-ghc@haskell.org
+-- Stability   :  internal
+-- Portability :  non-portable (GHC extensions)
 --
 -- Fingerprints for recompilation checking and ABI versioning, and
 -- implementing fast comparison of Typeable.
 --
--- ----------------------------------------------------------------------------
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
 
 module GHC.Fingerprint.Type (Fingerprint(..)) where
 
diff --git a/libraries/base/GHC/Float.hs b/libraries/base/GHC/Float.hs
index 19f2b4ce34dc821bbf195c2cafb624bc448efdfe..65143f944aac91ccfe968b1aec770f1eb6b46ed5 100644
--- a/libraries/base/GHC/Float.hs
+++ b/libraries/base/GHC/Float.hs
@@ -45,14 +45,120 @@
 
 
 module GHC.Float
-   ( module GHC.Float
-   , Float(..), Double(..), Float#, Double#
-   , double2Int, int2Double, float2Int, int2Float
-
-    -- * Monomorphic equality operators
-    -- | See GHC.Classes#matching_overloaded_methods_in_rules
-   , eqFloat, eqDouble
-   ) where
+    ( -- * Classes
+      Floating(..)
+    , RealFloat(..)
+
+      -- * 'Float'
+    , Float(..), Float#
+      -- ** Conversion
+    , float2Int
+    , int2Float
+    , word2Float
+    , integerToFloat#
+    , naturalToFloat#
+    , rationalToFloat
+    , castWord32ToFloat
+    , castFloatToWord32
+    , float2Double
+      -- ** Operations
+    , floorFloat
+    , ceilingFloat
+    , truncateFloat
+    , roundFloat
+    , properFractionFloat
+      -- ** Predicate
+    , isFloatDenormalized
+    , isFloatFinite
+    , isFloatInfinite
+    , isFloatNaN
+    , isFloatNegativeZero
+      -- ** Comparison
+    , gtFloat, geFloat, leFloat, ltFloat
+      -- ** Arithmetic
+    , plusFloat, minusFloat, timesFloat, divideFloat
+    , negateFloat
+    , expFloat, expm1Float
+    , logFloat, log1pFloat, sqrtFloat, fabsFloat
+    , sinFloat, cosFloat, tanFloat
+    , asinFloat, acosFloat, atanFloat
+    , sinhFloat, coshFloat, tanhFloat
+    , asinhFloat, acoshFloat, atanhFloat
+
+      -- * 'Double'
+    , Double(..)
+    , Double#
+      -- ** Conversion
+    , double2Int
+    , int2Double
+    , word2Double
+    , integerToDouble#
+    , naturalToDouble#
+    , rationalToDouble
+    , castWord64ToDouble
+    , castDoubleToWord64
+    , double2Float
+      -- ** Operations
+    , floorDouble
+    , ceilingDouble
+    , truncateDouble
+    , roundDouble
+    , properFractionDouble
+      -- ** Predicate
+    , isDoubleDenormalized
+    , isDoubleFinite
+    , isDoubleInfinite
+    , isDoubleNaN
+    , isDoubleNegativeZero
+      -- ** Comparison
+    , gtDouble, geDouble, leDouble, ltDouble
+      -- ** Arithmetic
+    , plusDouble, minusDouble, timesDouble, divideDouble
+    , negateDouble
+    , expDouble, expm1Double
+    , logDouble, log1pDouble, sqrtDouble, fabsDouble
+    , sinDouble, cosDouble, tanDouble
+    , asinDouble, acosDouble, atanDouble
+    , sinhDouble, coshDouble, tanhDouble
+    , asinhDouble, acoshDouble, atanhDouble
+
+      -- * Formatting
+    , showFloat
+    , FFFormat(..)
+    , formatRealFloat
+    , formatRealFloatAlt
+    , showSignedFloat
+
+      -- * Operations
+    , log1mexpOrd
+    , roundTo
+    , floatToDigits
+    , integerToBinaryFloat'
+    , fromRat
+    , fromRat'
+    , roundingMode#
+
+      -- * Monomorphic equality operators
+      -- | See GHC.Classes#matching_overloaded_methods_in_rules
+    , eqFloat, eqDouble
+
+      -- * Internal
+      -- | These may vanish in a future release
+    , clamp
+    , expt
+    , expts
+    , expts10
+    , fromRat''
+    , maxExpt
+    , maxExpt10
+    , minExpt
+    , powerDouble
+    , powerFloat
+    , stgDoubleToWord64
+    , stgFloatToWord32
+    , stgWord64ToDouble
+    , stgWord32ToFloat
+    ) where
 
 import Data.Maybe
 
diff --git a/libraries/base/GHC/Float/RealFracMethods.hs b/libraries/base/GHC/Float/RealFracMethods.hs
index 35a961579bc2bf5a6082391577c2f20aa095308e..af5413dbe19dd915103657240db499af1051c479 100644
--- a/libraries/base/GHC/Float/RealFracMethods.hs
+++ b/libraries/base/GHC/Float/RealFracMethods.hs
@@ -15,7 +15,12 @@
 -- Methods for the RealFrac instances for 'Float' and 'Double',
 -- with specialised versions for 'Int'.
 --
--- Moved to their own module to not bloat GHC.Float further.
+-- Moved to their own module to not bloat "GHC.Float" further.
+--
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
 --
 -----------------------------------------------------------------------------
 
diff --git a/libraries/base/GHC/GHCi.hs b/libraries/base/GHC/GHCi.hs
index 0370dfb19eb4029276cd6a6fcfbfa128255e41ea..49fbd2e94ee412b6b66bad11863584b8f132d544 100644
--- a/libraries/base/GHC/GHCi.hs
+++ b/libraries/base/GHC/GHCi.hs
@@ -15,6 +15,11 @@
 --
 -- EXPERIMENTAL! DON'T USE.
 --
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
+--
 -----------------------------------------------------------------------------
 
 module GHC.GHCi {-# WARNING "This is an unstable interface." #-} (
diff --git a/libraries/base/GHC/GHCi/Helpers.hs b/libraries/base/GHC/GHCi/Helpers.hs
index de510f3674ea599571c8fcb4516c2d86771fbbf6..fdf3890c1cf2623f5806a0786937629c4ac60654 100644
--- a/libraries/base/GHC/GHCi/Helpers.hs
+++ b/libraries/base/GHC/GHCi/Helpers.hs
@@ -10,6 +10,11 @@
 --
 -- Various helpers used by the GHCi shell.
 --
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
+--
 -----------------------------------------------------------------------------
 
 module GHC.GHCi.Helpers
diff --git a/libraries/base/GHC/IO.hs b/libraries/base/GHC/IO.hs
index f59727771077af132e93ca182987b766a4caebf6..74eb3bd12a6b824a6d7e8b224027f1ffc5cc1da3 100644
--- a/libraries/base/GHC/IO.hs
+++ b/libraries/base/GHC/IO.hs
@@ -12,7 +12,7 @@
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  GHC.IO
--- Copyright   :  (c) The University of Glasgow 1994-2002
+-- Copyright   :  (c) The University of Glasgow 1994-2023
 -- License     :  see libraries/base/LICENSE
 --
 -- Maintainer  :  cvs-ghc@haskell.org
@@ -21,6 +21,11 @@
 --
 -- Definitions for the 'IO' monad and its friends.
 --
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
+--
 -----------------------------------------------------------------------------
 
 module GHC.IO (
diff --git a/libraries/base/GHC/IO/Buffer.hs b/libraries/base/GHC/IO/Buffer.hs
index 992733d645191181062eca50e557d1510af8c73c..f4646fa913e8c870a7430885df42cf4680b8c9b0 100644
--- a/libraries/base/GHC/IO/Buffer.hs
+++ b/libraries/base/GHC/IO/Buffer.hs
@@ -14,6 +14,11 @@
 --
 -- Buffers used in the IO system
 --
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
+--
 -----------------------------------------------------------------------------
 
 module GHC.IO.Buffer (
diff --git a/libraries/base/GHC/IO/Device.hs b/libraries/base/GHC/IO/Device.hs
index 9f5c6d21a06f37c4f0e33006b16e3157f0aaa1f3..4af789a3aed84bdb3c85ebc7ed654a32dd5c3a2b 100644
--- a/libraries/base/GHC/IO/Device.hs
+++ b/libraries/base/GHC/IO/Device.hs
@@ -13,6 +13,11 @@
 --
 -- Type classes for I/O providers.
 --
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
+--
 -----------------------------------------------------------------------------
 
 module GHC.IO.Device (
diff --git a/libraries/base/GHC/IO/Encoding.hs b/libraries/base/GHC/IO/Encoding.hs
index ab2599559d960d817fa160ccde16b6017a7c8318..01b22e2a31361013f8a5771e5dc038cd26aaf69a 100644
--- a/libraries/base/GHC/IO/Encoding.hs
+++ b/libraries/base/GHC/IO/Encoding.hs
@@ -15,6 +15,11 @@
 --
 -- Text codecs for I/O
 --
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
+--
 -----------------------------------------------------------------------------
 
 module GHC.IO.Encoding (
diff --git a/libraries/base/GHC/IO/Exception.hs b/libraries/base/GHC/IO/Exception.hs
index 5f8a1ca024a1f8433aa631f75c88ea4a297baa0c..a04a19f5a263ecf87c28780cdcec62781a82eec3 100644
--- a/libraries/base/GHC/IO/Exception.hs
+++ b/libraries/base/GHC/IO/Exception.hs
@@ -16,6 +16,11 @@
 --
 -- IO-related Exception types and functions
 --
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
+--
 -----------------------------------------------------------------------------
 
 module GHC.IO.Exception (
diff --git a/libraries/base/GHC/IO/Handle/Internals.hs b/libraries/base/GHC/IO/Handle/Internals.hs
index cd1f6a35ef76a9b5b52d7311d4327bf9bccdec0c..33d825597063a6c39bc2686e5b3db49d94df6118 100644
--- a/libraries/base/GHC/IO/Handle/Internals.hs
+++ b/libraries/base/GHC/IO/Handle/Internals.hs
@@ -24,6 +24,11 @@
 -- of the operations defined here are independent of the underlying
 -- device.
 --
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
+--
 -----------------------------------------------------------------------------
 
 module GHC.IO.Handle.Internals (
diff --git a/libraries/base/GHC/IO/Handle/Text.hs b/libraries/base/GHC/IO/Handle/Text.hs
index 60c2aa7c10c93307d63adf7c7352919e8c778ade..25552f9be20c68ab11a02f6151530cefee2e4124 100644
--- a/libraries/base/GHC/IO/Handle/Text.hs
+++ b/libraries/base/GHC/IO/Handle/Text.hs
@@ -22,6 +22,11 @@
 --
 -- String I\/O functions
 --
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
+--
 -----------------------------------------------------------------------------
 
 module GHC.IO.Handle.Text (
diff --git a/libraries/base/GHC/IO/Handle/Types.hs b/libraries/base/GHC/IO/Handle/Types.hs
index 372dfbf19c6443b1cc9eabdf0c2530df062996a0..a095a57039e9da28875312a0d5b4a663e6397632 100644
--- a/libraries/base/GHC/IO/Handle/Types.hs
+++ b/libraries/base/GHC/IO/Handle/Types.hs
@@ -18,6 +18,11 @@
 --
 -- Basic types for the implementation of IO Handles.
 --
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
+--
 -----------------------------------------------------------------------------
 
 module GHC.IO.Handle.Types (
diff --git a/libraries/base/GHC/IO/SubSystem.hs b/libraries/base/GHC/IO/SubSystem.hs
index a6f06e60e9cd56832a7ead20548c66231476833b..066102741f66e05b5aca24336344d4da5c940a03 100644
--- a/libraries/base/GHC/IO/SubSystem.hs
+++ b/libraries/base/GHC/IO/SubSystem.hs
@@ -12,9 +12,14 @@
 -- Stability   :  internal
 -- Portability :  non-portable
 --
--- The SubSystem control interface.  These methods can be used to disambiguate
+-- The 'IoSubSystem' control interface.  These methods can be used to disambiguate
 -- between the two operations.
 --
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
+--
 -----------------------------------------------------------------------------
 
 module GHC.IO.SubSystem (
diff --git a/libraries/base/GHC/IOPort.hs b/libraries/base/GHC/IOPort.hs
index 101f9b34fafa5ebbe71d1b50cdd6c751a05c71c5..8d5525d49b8bae188b956de4a18526152981700c 100644
--- a/libraries/base/GHC/IOPort.hs
+++ b/libraries/base/GHC/IOPort.hs
@@ -13,7 +13,13 @@
 -- Stability   :  internal
 -- Portability :  non-portable (GHC Extensions)
 --
--- The IOPort type. This is a facility used by the Windows IO subsystem.
+-- The 'IOPort' type. This is a facility used by the Windows IO subsystem.
+--
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
+--
 -- We have strict rules with an I/O Port:
 -- * writing more than once is an error
 -- * reading more than once is an error
diff --git a/libraries/base/GHC/InfoProv.hsc b/libraries/base/GHC/InfoProv.hsc
index 86e2ae8a14bcd61d09f03661b3441c59535ee876..2586a705867c74fc3b98c30ac73cfe1243ce13a4 100644
--- a/libraries/base/GHC/InfoProv.hsc
+++ b/libraries/base/GHC/InfoProv.hsc
@@ -15,6 +15,11 @@
 --
 -- Access to GHC's info-table provenance metadata.
 --
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
+--
 -- @since 4.18.0.0
 -----------------------------------------------------------------------------
 
diff --git a/libraries/base/GHC/Num.hs b/libraries/base/GHC/Num.hs
index 1b76cd1bbc3870fc0493d0f9cc0cf0e321f3e2a6..b6e60b6121bac23e1447121374cea8bce93ec014 100644
--- a/libraries/base/GHC/Num.hs
+++ b/libraries/base/GHC/Num.hs
@@ -18,7 +18,9 @@
 
 
 module GHC.Num
-   ( module GHC.Num
+   ( Num(..)
+   , subtract
+   , quotRemInteger
    , module GHC.Num.Integer
    , module GHC.Num.Natural
     -- reexported for backward compatibility
diff --git a/libraries/base/GHC/RTS/Flags.hsc b/libraries/base/GHC/RTS/Flags.hsc
index 138033758bea514f5bbc334ad5dc77157dbe828a..847c6c13949732730bf1af01a07de230acc13317 100644
--- a/libraries/base/GHC/RTS/Flags.hsc
+++ b/libraries/base/GHC/RTS/Flags.hsc
@@ -1,7 +1,19 @@
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE NoImplicitPrelude #-}
 
--- | Accessors to GHC RTS flags.
+-- |
+-- Module      :  GHC.RTS.Flags
+-- Copyright   :  (c) The University of Glasgow, 1994-2000
+-- License     :  see libraries/base/LICENSE
+--
+-- Maintainer  :  cvs-ghc@haskell.org
+-- Stability   :  internal
+-- Portability :  non-portable (GHC extensions)
+--
+-- /The API of this module is unstable and is tightly coupled to GHC's internals./
+-- If depend on it, make sure to use a tight upper bound, e.g., @base < 4.X@ rather
+-- than @base < 5@, because the interface can change rapidly without much warning.
+--
 -- Descriptions of flags can be seen in
 -- <https://www.haskell.org/ghc/docs/latest/html/users_guide/runtime_control.html GHC User's Guide>,
 -- or by running RTS help message using @+RTS --help@.
diff --git a/libraries/base/GHC/Real.hs b/libraries/base/GHC/Real.hs
index 932cba8fcbc820f841c038249858702b615ce811..7e1ebc8c27a2acc2f247a1da39509bf54e887b96 100644
--- a/libraries/base/GHC/Real.hs
+++ b/libraries/base/GHC/Real.hs
@@ -18,7 +18,72 @@
 --
 -----------------------------------------------------------------------------
 
-module GHC.Real where
+module GHC.Real
+    ( -- * Classes
+      Real(..)
+    , Integral(..)
+    , Fractional(..)
+    , RealFrac(..)
+
+      -- * Conversion
+    , fromIntegral
+    , realToFrac
+
+      -- * Formatting
+    , showSigned
+
+      -- * Predicates
+    , even
+    , odd
+
+      -- * Arithmetic
+    , (^)
+    , (^^)
+    , gcd
+    , lcm
+
+      -- * 'Ratio'
+    , Ratio(..)
+    , Rational
+    , infinity
+    , notANumber
+
+      -- * 'Enum' helpers
+    , numericEnumFrom
+    , numericEnumFromThen
+    , numericEnumFromTo
+    , numericEnumFromThenTo
+    , integralEnumFrom
+    , integralEnumFromThen
+    , integralEnumFromTo
+    , integralEnumFromThenTo
+
+      -- ** Construction
+    , (%)
+
+      -- ** Projection
+    , numerator
+    , denominator
+
+      -- ** Operations
+    , reduce
+
+      -- * Internal
+    , ratioPrec
+    , ratioPrec1
+    , divZeroError
+    , ratioZeroDenominatorError
+    , overflowError
+    , underflowError
+    , mkRationalBase2
+    , mkRationalBase10
+    , FractionalExponentBase(..)
+    , (^%^)
+    , (^^%^^)
+    , mkRationalWithExponentBase
+    , powImpl
+    , powImplAcc
+    ) where
 
 #include "MachDeps.h"
 
diff --git a/libraries/base/GHC/Stack/Types.hs b/libraries/base/GHC/Stack/Types.hs
index 8c729a693fe8090ca795be631855c66b6d843082..f21e096f799066bda6925dbbd8fad439a97c9f95 100644
--- a/libraries/base/GHC/Stack/Types.hs
+++ b/libraries/base/GHC/Stack/Types.hs
@@ -19,10 +19,15 @@
 -- Stability   :  internal
 -- Portability :  non-portable (GHC Extensions)
 --
--- type definitions for implicit call-stacks.
+-- Type definitions for implicit call-stacks.
 -- Use "GHC.Stack" from the base package instead of importing this
 -- module directly.
 --
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
+--
 -----------------------------------------------------------------------------
 
 module GHC.Stack.Types (
diff --git a/libraries/base/GHC/Stats.hsc b/libraries/base/GHC/Stats.hsc
index 27ac5ca8c658afecf199f4d2aced2b79fdfc8373..85eaa25d5b27843a5feecebbcbc1a8a75d2a8897 100644
--- a/libraries/base/GHC/Stats.hsc
+++ b/libraries/base/GHC/Stats.hsc
@@ -5,11 +5,22 @@
 {-# OPTIONS_GHC -funbox-strict-fields #-}
 
 -----------------------------------------------------------------------------
--- | This module provides access to internal garbage collection and
+-- |
+-- Module      :  GHC.RTS.Flags
+-- Copyright   :  (c) The University of Glasgow, 1994-2000
+-- License     :  see libraries/base/LICENSE
+--
+-- Maintainer  :  cvs-ghc@haskell.org
+-- Stability   :  internal
+-- Portability :  non-portable (GHC extensions)
+--
+-- This module provides access to internal garbage collection and
 -- memory usage statistics.  These statistics are not available unless
 -- a program is run with the @-T@ RTS flag.
 --
--- This module is GHC-only and should not be considered portable.
+-- /The API of this module is unstable and is tightly coupled to GHC's internals./
+-- If depend on it, make sure to use a tight upper bound, e.g., @base < 4.X@ rather
+-- than @base < 5@, because the interface can change rapidly without much warning.
 --
 -- @since 4.5.0.0
 -----------------------------------------------------------------------------
diff --git a/libraries/base/GHC/TopHandler.hs b/libraries/base/GHC/TopHandler.hs
index e3206517f224d06b9566970388518b1fe6003473..5a0abd0d1752d9a39ee6b85e3f4c47c9641184d9 100644
--- a/libraries/base/GHC/TopHandler.hs
+++ b/libraries/base/GHC/TopHandler.hs
@@ -19,6 +19,11 @@
 -- Support for catching exceptions raised during top-level computations
 -- (e.g. @Main.main@, 'Control.Concurrent.forkIO', and foreign exports)
 --
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
+--
 -----------------------------------------------------------------------------
 
 module GHC.TopHandler (
diff --git a/libraries/base/GHC/TypeLits/Internal.hs b/libraries/base/GHC/TypeLits/Internal.hs
index c2bb3327e53d7a495bf0c47497279fa1abfa897c..06b4042aa21e11b5d7da5c5581ff471f03b3f5a8 100644
--- a/libraries/base/GHC/TypeLits/Internal.hs
+++ b/libraries/base/GHC/TypeLits/Internal.hs
@@ -4,18 +4,29 @@
 {-# LANGUAGE NoImplicitPrelude #-}
 {-# OPTIONS_HADDOCK not-home #-}
 
-{-|
-DO NOT USE THIS MODULE.  Use "GHC.TypeLits" instead.
-
-This module is internal-only and was exposed by accident.  It may be
-removed without warning in a future version.
-
-(The technical reason for this module's existence is that it is needed
-to prevent module cycles while still allowing these identifiers to be
-imported in 'Data.Type.Ord'.)
-
-@since 4.16.0.0
--}
+-- |
+-- Module      :  GHC.TypeLits.Internal
+-- Copyright   :  (c) The University of Glasgow, 1994-2000
+-- License     :  see libraries/base/LICENSE
+--
+-- Maintainer  :  cvs-ghc@haskell.org
+-- Stability   :  internal
+-- Portability :  non-portable (GHC extensions)
+--
+-- __Do not use this module.__  Use "GHC.TypeLits" instead.
+--
+-- This module is internal-only and was exposed by accident.  It may be
+-- removed without warning in a future version.
+--
+-- /The API of this module is unstable and is tightly coupled to GHC's internals./
+-- If depend on it, make sure to use a tight upper bound, e.g., @base < 4.X@ rather
+-- than @base < 5@, because the interface can change rapidly without much warning.
+--
+-- The technical reason for this module's existence is that it is needed
+-- to prevent module cycles while still allowing these identifiers to be
+-- imported in "Data.Type.Ord".
+--
+-- @since 4.16.0.0
 
 module GHC.TypeLits.Internal
   ( Symbol
diff --git a/libraries/base/GHC/TypeNats/Internal.hs b/libraries/base/GHC/TypeNats/Internal.hs
index b46d53603afebd2cff77847f6c8f69a495396030..ec85fd49c2c30966dc17e143d0b8e1bb1e46925e 100644
--- a/libraries/base/GHC/TypeNats/Internal.hs
+++ b/libraries/base/GHC/TypeNats/Internal.hs
@@ -4,18 +4,28 @@
 {-# LANGUAGE NoImplicitPrelude #-}
 {-# OPTIONS_HADDOCK not-home #-}
 
-{-|
-DO NOT USE THIS MODULE.  Use "GHC.TypeNats" instead.
-
-This module is internal-only and was exposed by accident.  It may be
-removed without warning in a future version.
-
-(The technical reason for this module's existence is that it is needed
-to prevent module cycles while still allowing these identifiers to be
-imported in 'Data.Type.Ord'.)
-
-@since 4.16.0.0
--}
+-- Module      :  GHC.TypeNats.Internal
+-- Copyright   :  (c) The University of Glasgow, 1994-2000
+-- License     :  see libraries/base/LICENSE
+--
+-- Maintainer  :  cvs-ghc@haskell.org
+-- Stability   :  internal
+-- Portability :  non-portable (GHC extensions)
+--
+-- __Do not use this module.__  Use "GHC.TypeNats" instead.
+--
+-- This module is internal-only and was exposed by accident.  It may be
+-- removed without warning in a future version.
+--
+-- /The API of this module is unstable and is tightly coupled to GHC's internals./
+-- If depend on it, make sure to use a tight upper bound, e.g., @base < 4.X@ rather
+-- than @base < 5@, because the interface can change rapidly without much warning.
+--
+-- The technical reason for this module's existence is that it is needed
+-- to prevent module cycles while still allowing these identifiers to be
+-- imported in "Data.Type.Ord".
+--
+-- @since 4.16.0.0
 
 module GHC.TypeNats.Internal
   ( Natural
diff --git a/libraries/base/System/Posix/Internals.hs b/libraries/base/System/Posix/Internals.hs
index 70b8ca0a498dea15a8434016e33e65678fb61c62..37ec373c203b213bcc69055d1513402ec117e01c 100644
--- a/libraries/base/System/Posix/Internals.hs
+++ b/libraries/base/System/Posix/Internals.hs
@@ -17,10 +17,16 @@
 -- Portability :  non-portable (requires POSIX)
 --
 -- POSIX support layer for the standard libraries.
+--
+-- /The API of this module is unstable and not meant to be consumed by the general public./
+-- If you absolutely must depend on it, make sure to use a tight upper
+-- bound, e.g., @base < 4.X@ rather than @base < 5@, because the interface can
+-- change rapidly without much warning.
+--
 -- This library is built on *every* platform, including Win32.
 --
--- Non-posix compliant in order to support the following features:
---      * S_ISSOCK (no sockets in POSIX)
+-- Non-POSIX compliant in order to support the following features:
+--  * S_ISSOCK (no sockets in POSIX)
 --
 -----------------------------------------------------------------------------
 
diff --git a/libraries/base/base.cabal b/libraries/base/base.cabal
index cb25aefd4fb4d9c9f2cb9f510a03b477b3596d2b..661c5d1b0c39cf9345d4de0e7bd08509f2e67672 100644
--- a/libraries/base/base.cabal
+++ b/libraries/base/base.cabal
@@ -128,6 +128,7 @@ Library
         Data.Dynamic
         Data.Either
         Data.Eq
+        Data.Enum
         Data.Fixed
         Data.Foldable
         Data.Foldable1
diff --git a/libraries/ghc-bignum/src/GHC/Num/Integer.hs b/libraries/ghc-bignum/src/GHC/Num/Integer.hs
index 419aecf841d427fdfdd724de53ee0e02fbe2a251..9e651f02bc76d7d7843fcad6380ff0391e934a1d 100644
--- a/libraries/ghc-bignum/src/GHC/Num/Integer.hs
+++ b/libraries/ghc-bignum/src/GHC/Num/Integer.hs
@@ -20,7 +20,131 @@
 --
 -- The 'Integer' type.
 
-module GHC.Num.Integer where
+module GHC.Num.Integer
+    ( Integer(..)
+    , integerCheck
+    , integerCheck#
+
+      -- * Useful constants
+    , integerZero
+    , integerOne
+
+      -- * Conversion with...
+      -- ** 'Int'
+    , integerFromInt#
+    , integerFromInt
+    , integerToInt#
+    , integerToInt
+      -- ** 'BigNat'
+    , integerFromBigNat#
+    , integerFromBigNatNeg#
+    , integerFromBigNatSign#
+    , integerToBigNatSign#
+    , integerToBigNatClamp#
+      -- ** 'Word'
+    , integerFromWord#
+    , integerFromWord
+    , integerFromWordNeg#
+    , integerFromWordSign#
+    , integerToWord#
+    , integerToWord
+      -- ** 'Natural'
+    , integerFromNatural
+    , integerToNaturalClamp
+    , integerToNatural
+    , integerToNaturalThrow
+      -- ** 'Int64'/'Word64'
+    , integerFromInt64#
+    , integerFromWord64#
+    , integerToInt64#
+    , integerToWord64#
+      -- ** Floating-point
+    , integerDecodeDouble#
+    , integerEncodeDouble#
+    , integerEncodeDouble
+    , integerEncodeFloat#
+      -- ** 'Addr#'
+    , integerToAddr#
+    , integerToAddr
+    , integerFromAddr#
+    , integerFromAddr
+      -- ** Limbs
+    , integerFromWordList
+    , integerToMutableByteArray#
+    , integerToMutableByteArray
+    , integerFromByteArray#
+    , integerFromByteArray
+
+      -- * Predicates
+    , integerIsNegative#
+    , integerIsNegative
+    , integerIsZero
+    , integerIsOne
+
+      -- * Comparison
+    , integerNe
+    , integerEq
+    , integerLe
+    , integerLt
+    , integerGt
+    , integerGe
+    , integerEq#
+    , integerNe#
+    , integerGt#
+    , integerLe#
+    , integerLt#
+    , integerGe#
+    , integerCompare
+
+      -- * Arithmetic
+    , integerSub
+    , integerAdd
+    , integerMul
+    , integerNegate
+    , integerAbs
+    , integerSignum
+    , integerSignum#
+    , integerQuotRem#
+    , integerQuotRem
+    , integerQuot
+    , integerRem
+    , integerDivMod#
+    , integerDivMod
+    , integerDiv
+    , integerMod
+    , integerGcd
+    , integerLcm
+    , integerSqr
+    , integerLog2#
+    , integerLog2
+    , integerLogBaseWord#
+    , integerLogBaseWord
+    , integerLogBase#
+    , integerLogBase
+    , integerIsPowerOf2#
+    , integerGcde#
+    , integerGcde
+    , integerRecipMod#
+    , integerPowMod#
+
+      -- * Bit operations
+    , integerPopCount#
+    , integerBit#
+    , integerBit
+    , integerTestBit#
+    , integerTestBit
+    , integerShiftR#
+    , integerShiftR
+    , integerShiftL#
+    , integerShiftL
+    , integerOr
+    , integerXor
+    , integerAnd
+    , integerComplement
+
+      -- * Miscellaneous
+    , integerSizeInBase#
+    ) where
 
 #include "MachDeps.h"
 #include "WordSize.h"
diff --git a/libraries/ghc-bignum/src/GHC/Num/Natural.hs b/libraries/ghc-bignum/src/GHC/Num/Natural.hs
index 3650e7f42b4fe44a02c85afc80aa8b563ee8e7bd..8473e14d44f1499e5a068c312c92db1b5a036a43 100644
--- a/libraries/ghc-bignum/src/GHC/Num/Natural.hs
+++ b/libraries/ghc-bignum/src/GHC/Num/Natural.hs
@@ -8,7 +8,109 @@
 #include "MachDeps.h"
 #include "WordSize.h"
 
-module GHC.Num.Natural where
+module GHC.Num.Natural
+    ( Natural(..)
+    , naturalCheck#
+    , naturalCheck
+
+      -- * Useful constants
+    , naturalZero
+    , naturalOne
+
+      -- * Predicates
+    , naturalIsZero
+    , naturalIsOne
+    , naturalIsPowerOf2#
+
+      -- * Conversion with...
+      -- ** 'BigNat'
+    , naturalFromBigNat#
+    , naturalToBigNat#
+      -- ** 'Word'
+    , naturalFromWord#
+    , naturalFromWord2#
+    , naturalFromWord
+    , naturalToWord#
+    , naturalToWord
+    , naturalToWordClamp#
+    , naturalToWordClamp
+    , naturalToWordMaybe#
+      -- ** Limbs
+    , naturalFromWordList
+    , naturalToMutableByteArray#
+    , naturalFromByteArray#
+      -- ** Floating point
+    , naturalEncodeDouble#
+    , naturalEncodeFloat#
+      -- ** 'Addr#'
+    , naturalToAddr#
+    , naturalToAddr
+    , naturalFromAddr#
+    , naturalFromAddr
+
+      -- * Comparison
+    , naturalEq#
+    , naturalEq
+    , naturalNe#
+    , naturalNe
+    , naturalGe#
+    , naturalGe
+    , naturalLe#
+    , naturalLe
+    , naturalGt#
+    , naturalGt
+    , naturalLt#
+    , naturalLt
+    , naturalCompare
+
+      -- * Bit operations
+    , naturalPopCount#
+    , naturalPopCount
+    , naturalShiftR#
+    , naturalShiftR
+    , naturalShiftL#
+    , naturalShiftL
+    , naturalAnd
+    , naturalAndNot
+    , naturalOr
+    , naturalXor
+    , naturalTestBit#
+    , naturalTestBit
+    , naturalBit#
+    , naturalBit
+    , naturalSetBit#
+    , naturalSetBit
+    , naturalClearBit#
+    , naturalClearBit
+    , naturalComplementBit#
+    , naturalComplementBit
+
+      -- * Arithmetic
+    , naturalAdd
+    , naturalSub
+    , naturalSubThrow
+    , naturalSubUnsafe
+    , naturalMul
+    , naturalSqr
+    , naturalSignum
+    , naturalNegate
+    , naturalQuotRem#
+    , naturalQuotRem
+    , naturalQuot
+    , naturalRem
+    , naturalGcd
+    , naturalLcm
+    , naturalLog2#
+    , naturalLog2
+    , naturalLogBaseWord#
+    , naturalLogBaseWord
+    , naturalLogBase#
+    , naturalLogBase
+    , naturalPowMod
+
+      -- * Miscellaneous
+    , naturalSizeInBase#
+    ) where
 
 import GHC.Prim
 import GHC.Types
diff --git a/testsuite/tests/interface-stability/base-exports.stdout b/testsuite/tests/interface-stability/base-exports.stdout
index 26550cb1edc836394c2a7aa20f55e4ee84e636ad..9d044ee0f69905686d7da8b97d61d9429bd06ae1 100644
--- a/testsuite/tests/interface-stability/base-exports.stdout
+++ b/testsuite/tests/interface-stability/base-exports.stdout
@@ -906,6 +906,25 @@ module Data.Either where
   partitionEithers :: forall a b. [Either a b] -> ([a], [b])
   rights :: forall a b. [Either a b] -> [b]
 
+module Data.Enum where
+  -- Safety: Safe-Inferred
+  type Bounded :: * -> Constraint
+  class Bounded a where
+    minBound :: a
+    maxBound :: a
+    {-# MINIMAL minBound, maxBound #-}
+  type Enum :: * -> Constraint
+  class Enum a where
+    succ :: a -> a
+    pred :: a -> a
+    toEnum :: GHC.Types.Int -> a
+    fromEnum :: a -> GHC.Types.Int
+    enumFrom :: a -> [a]
+    enumFromThen :: a -> a -> [a]
+    enumFromTo :: a -> a -> [a]
+    enumFromThenTo :: a -> a -> a -> [a]
+    {-# MINIMAL toEnum, fromEnum #-}
+
 module Data.Eq where
   -- Safety: Trustworthy
   type Eq :: * -> Constraint
@@ -11311,6 +11330,30 @@ instance GHC.Enum.Bounded GHC.Unicode.GeneralCategory -- Defined in ‘GHC.Unico
 instance forall k (a :: k) (b :: k). (a ~ b) => GHC.Enum.Bounded (a Data.Type.Equality.:~: b) -- Defined in ‘Data.Type.Equality’
 instance forall k1 k2 (a :: k1) (b :: k2). (a ~~ b) => GHC.Enum.Bounded (a Data.Type.Equality.:~~: b) -- Defined in ‘Data.Type.Equality’
 instance forall k (t :: k). GHC.Enum.Bounded (Data.Proxy.Proxy t) -- Defined in ‘Data.Proxy’
+instance GHC.Enum.Bounded GHC.Types.Bool -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.Char -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.Int -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.Levity -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.Ordering -- Defined in ‘GHC.Enum’
+instance forall a. GHC.Enum.Bounded a => GHC.Enum.Bounded (Solo a) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i j. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i j k. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i j k l. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i j k l m. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i j k l m n. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m, GHC.Enum.Bounded n) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i j k l m n o. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m, GHC.Enum.Bounded n, GHC.Enum.Bounded o) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -- Defined in ‘GHC.Enum’
+instance forall a b. (GHC.Enum.Bounded a, GHC.Enum.Bounded b) => GHC.Enum.Bounded (a, b) -- Defined in ‘GHC.Enum’
+instance forall a b c. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c) => GHC.Enum.Bounded (a, b, c) -- Defined in ‘GHC.Enum’
+instance forall a b c d. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d) => GHC.Enum.Bounded (a, b, c, d) -- Defined in ‘GHC.Enum’
+instance forall a b c d e. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e) => GHC.Enum.Bounded (a, b, c, d, e) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f) => GHC.Enum.Bounded (a, b, c, d, e, f) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g) => GHC.Enum.Bounded (a, b, c, d, e, f, g) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i) -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded () -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.VecCount -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.VecElem -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.Word -- Defined in ‘GHC.Enum’
 instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Enum.Bounded (f (g a)) => GHC.Enum.Bounded (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
 instance forall a. GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Functor.Identity.Identity a) -- Defined in ‘Data.Functor.Identity’
 instance GHC.Enum.Bounded GHC.Int.Int16 -- Defined in ‘GHC.Int’
@@ -11336,30 +11379,6 @@ instance GHC.Enum.Bounded GHC.Word.Word8 -- Defined in ‘GHC.Word’
 instance GHC.Enum.Bounded Foreign.Ptr.IntPtr -- Defined in ‘Foreign.Ptr’
 instance GHC.Enum.Bounded Foreign.Ptr.WordPtr -- Defined in ‘Foreign.Ptr’
 instance [safe] GHC.Enum.Bounded GHC.ByteOrder.ByteOrder -- Defined in ‘GHC.ByteOrder’
-instance GHC.Enum.Bounded GHC.Types.Bool -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.Char -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.Int -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.Levity -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.Ordering -- Defined in ‘GHC.Enum’
-instance forall a. GHC.Enum.Bounded a => GHC.Enum.Bounded (Solo a) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i j. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i j k. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i j k l. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i j k l m. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i j k l m n. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m, GHC.Enum.Bounded n) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i j k l m n o. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m, GHC.Enum.Bounded n, GHC.Enum.Bounded o) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -- Defined in ‘GHC.Enum’
-instance forall a b. (GHC.Enum.Bounded a, GHC.Enum.Bounded b) => GHC.Enum.Bounded (a, b) -- Defined in ‘GHC.Enum’
-instance forall a b c. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c) => GHC.Enum.Bounded (a, b, c) -- Defined in ‘GHC.Enum’
-instance forall a b c d. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d) => GHC.Enum.Bounded (a, b, c, d) -- Defined in ‘GHC.Enum’
-instance forall a b c d e. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e) => GHC.Enum.Bounded (a, b, c, d, e) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f) => GHC.Enum.Bounded (a, b, c, d, e, f) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g) => GHC.Enum.Bounded (a, b, c, d, e, f, g) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i) -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded () -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.VecCount -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.VecElem -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.Word -- Defined in ‘GHC.Enum’
 instance GHC.Enum.Bounded GHC.Generics.Associativity -- Defined in ‘GHC.Generics’
 instance GHC.Enum.Bounded GHC.Generics.DecidedStrictness -- Defined in ‘GHC.Generics’
 instance GHC.Enum.Bounded GHC.Generics.SourceStrictness -- Defined in ‘GHC.Generics’
@@ -11373,6 +11392,18 @@ instance GHC.Enum.Enum GHC.Unicode.GeneralCategory -- Defined in ‘GHC.Unicode
 instance forall k (a :: k) (b :: k). (a ~ b) => GHC.Enum.Enum (a Data.Type.Equality.:~: b) -- Defined in ‘Data.Type.Equality’
 instance forall k1 k2 (a :: k1) (b :: k2). (a ~~ b) => GHC.Enum.Enum (a Data.Type.Equality.:~~: b) -- Defined in ‘Data.Type.Equality’
 instance forall k (s :: k). GHC.Enum.Enum (Data.Proxy.Proxy s) -- Defined in ‘Data.Proxy’
+instance GHC.Enum.Enum GHC.Types.Bool -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.Char -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.Int -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Num.Integer.Integer -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.Levity -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Num.Natural.Natural -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.Ordering -- Defined in ‘GHC.Enum’
+instance forall a. GHC.Enum.Enum a => GHC.Enum.Enum (Solo a) -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum () -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.VecCount -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.VecElem -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.Word -- Defined in ‘GHC.Enum’
 instance forall k (a :: k). GHC.Enum.Enum (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
 instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Enum.Enum (f (g a)) => GHC.Enum.Enum (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
 instance forall a. GHC.Enum.Enum a => GHC.Enum.Enum (Data.Functor.Identity.Identity a) -- Defined in ‘Data.Functor.Identity’
@@ -11397,18 +11428,6 @@ instance GHC.Enum.Enum GHC.Word.Word8 -- Defined in ‘GHC.Word’
 instance GHC.Enum.Enum Foreign.Ptr.IntPtr -- Defined in ‘Foreign.Ptr’
 instance GHC.Enum.Enum Foreign.Ptr.WordPtr -- Defined in ‘Foreign.Ptr’
 instance [safe] GHC.Enum.Enum GHC.ByteOrder.ByteOrder -- Defined in ‘GHC.ByteOrder’
-instance GHC.Enum.Enum GHC.Types.Bool -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.Char -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.Int -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Num.Integer.Integer -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.Levity -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Num.Natural.Natural -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.Ordering -- Defined in ‘GHC.Enum’
-instance forall a. GHC.Enum.Enum a => GHC.Enum.Enum (Solo a) -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum () -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.VecCount -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.VecElem -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.Word -- Defined in ‘GHC.Enum’
 instance GHC.Enum.Enum GHC.Types.Double -- Defined in ‘GHC.Float’
 instance GHC.Enum.Enum GHC.Types.Float -- Defined in ‘GHC.Float’
 instance GHC.Enum.Enum GHC.Generics.Associativity -- Defined in ‘GHC.Generics’
diff --git a/testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs b/testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
index 879c391e34d52fe2443f0d86faed91bc72ec361a..db022a72e64174dc08f506d028496df47c2a521c 100644
--- a/testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
+++ b/testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
@@ -906,6 +906,25 @@ module Data.Either where
   partitionEithers :: forall a b. [Either a b] -> ([a], [b])
   rights :: forall a b. [Either a b] -> [b]
 
+module Data.Enum where
+  -- Safety: Safe-Inferred
+  type Bounded :: * -> Constraint
+  class Bounded a where
+    minBound :: a
+    maxBound :: a
+    {-# MINIMAL minBound, maxBound #-}
+  type Enum :: * -> Constraint
+  class Enum a where
+    succ :: a -> a
+    pred :: a -> a
+    toEnum :: GHC.Types.Int -> a
+    fromEnum :: a -> GHC.Types.Int
+    enumFrom :: a -> [a]
+    enumFromThen :: a -> a -> [a]
+    enumFromTo :: a -> a -> [a]
+    enumFromThenTo :: a -> a -> a -> [a]
+    {-# MINIMAL toEnum, fromEnum #-}
+
 module Data.Eq where
   -- Safety: Trustworthy
   type Eq :: * -> Constraint
@@ -14082,6 +14101,30 @@ instance GHC.Enum.Bounded GHC.Unicode.GeneralCategory -- Defined in ‘GHC.Unico
 instance forall k (a :: k) (b :: k). (a ~ b) => GHC.Enum.Bounded (a Data.Type.Equality.:~: b) -- Defined in ‘Data.Type.Equality’
 instance forall k1 k2 (a :: k1) (b :: k2). (a ~~ b) => GHC.Enum.Bounded (a Data.Type.Equality.:~~: b) -- Defined in ‘Data.Type.Equality’
 instance forall k (t :: k). GHC.Enum.Bounded (Data.Proxy.Proxy t) -- Defined in ‘Data.Proxy’
+instance GHC.Enum.Bounded GHC.Types.Bool -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.Char -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.Int -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.Levity -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.Ordering -- Defined in ‘GHC.Enum’
+instance forall a. GHC.Enum.Bounded a => GHC.Enum.Bounded (Solo a) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i j. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i j k. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i j k l. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i j k l m. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i j k l m n. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m, GHC.Enum.Bounded n) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i j k l m n o. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m, GHC.Enum.Bounded n, GHC.Enum.Bounded o) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -- Defined in ‘GHC.Enum’
+instance forall a b. (GHC.Enum.Bounded a, GHC.Enum.Bounded b) => GHC.Enum.Bounded (a, b) -- Defined in ‘GHC.Enum’
+instance forall a b c. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c) => GHC.Enum.Bounded (a, b, c) -- Defined in ‘GHC.Enum’
+instance forall a b c d. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d) => GHC.Enum.Bounded (a, b, c, d) -- Defined in ‘GHC.Enum’
+instance forall a b c d e. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e) => GHC.Enum.Bounded (a, b, c, d, e) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f) => GHC.Enum.Bounded (a, b, c, d, e, f) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g) => GHC.Enum.Bounded (a, b, c, d, e, f, g) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i) -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded () -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.VecCount -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.VecElem -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.Word -- Defined in ‘GHC.Enum’
 instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Enum.Bounded (f (g a)) => GHC.Enum.Bounded (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
 instance forall a. GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Functor.Identity.Identity a) -- Defined in ‘Data.Functor.Identity’
 instance GHC.Enum.Bounded GHC.Int.Int16 -- Defined in ‘GHC.Int’
@@ -14107,30 +14150,6 @@ instance GHC.Enum.Bounded GHC.Word.Word8 -- Defined in ‘GHC.Word’
 instance GHC.Enum.Bounded Foreign.Ptr.IntPtr -- Defined in ‘Foreign.Ptr’
 instance GHC.Enum.Bounded Foreign.Ptr.WordPtr -- Defined in ‘Foreign.Ptr’
 instance [safe] GHC.Enum.Bounded GHC.ByteOrder.ByteOrder -- Defined in ‘GHC.ByteOrder’
-instance GHC.Enum.Bounded GHC.Types.Bool -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.Char -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.Int -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.Levity -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.Ordering -- Defined in ‘GHC.Enum’
-instance forall a. GHC.Enum.Bounded a => GHC.Enum.Bounded (Solo a) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i j. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i j k. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i j k l. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i j k l m. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i j k l m n. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m, GHC.Enum.Bounded n) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i j k l m n o. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m, GHC.Enum.Bounded n, GHC.Enum.Bounded o) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -- Defined in ‘GHC.Enum’
-instance forall a b. (GHC.Enum.Bounded a, GHC.Enum.Bounded b) => GHC.Enum.Bounded (a, b) -- Defined in ‘GHC.Enum’
-instance forall a b c. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c) => GHC.Enum.Bounded (a, b, c) -- Defined in ‘GHC.Enum’
-instance forall a b c d. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d) => GHC.Enum.Bounded (a, b, c, d) -- Defined in ‘GHC.Enum’
-instance forall a b c d e. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e) => GHC.Enum.Bounded (a, b, c, d, e) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f) => GHC.Enum.Bounded (a, b, c, d, e, f) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g) => GHC.Enum.Bounded (a, b, c, d, e, f, g) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i) -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded () -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.VecCount -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.VecElem -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.Word -- Defined in ‘GHC.Enum’
 instance GHC.Enum.Bounded GHC.Generics.Associativity -- Defined in ‘GHC.Generics’
 instance GHC.Enum.Bounded GHC.Generics.DecidedStrictness -- Defined in ‘GHC.Generics’
 instance GHC.Enum.Bounded GHC.Generics.SourceStrictness -- Defined in ‘GHC.Generics’
@@ -14144,6 +14163,18 @@ instance GHC.Enum.Enum GHC.Unicode.GeneralCategory -- Defined in ‘GHC.Unicode
 instance forall k (a :: k) (b :: k). (a ~ b) => GHC.Enum.Enum (a Data.Type.Equality.:~: b) -- Defined in ‘Data.Type.Equality’
 instance forall k1 k2 (a :: k1) (b :: k2). (a ~~ b) => GHC.Enum.Enum (a Data.Type.Equality.:~~: b) -- Defined in ‘Data.Type.Equality’
 instance forall k (s :: k). GHC.Enum.Enum (Data.Proxy.Proxy s) -- Defined in ‘Data.Proxy’
+instance GHC.Enum.Enum GHC.Types.Bool -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.Char -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.Int -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Num.Integer.Integer -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.Levity -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Num.Natural.Natural -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.Ordering -- Defined in ‘GHC.Enum’
+instance forall a. GHC.Enum.Enum a => GHC.Enum.Enum (Solo a) -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum () -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.VecCount -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.VecElem -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.Word -- Defined in ‘GHC.Enum’
 instance forall k (a :: k). GHC.Enum.Enum (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
 instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Enum.Enum (f (g a)) => GHC.Enum.Enum (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
 instance forall a. GHC.Enum.Enum a => GHC.Enum.Enum (Data.Functor.Identity.Identity a) -- Defined in ‘Data.Functor.Identity’
@@ -14168,18 +14199,6 @@ instance GHC.Enum.Enum GHC.Word.Word8 -- Defined in ‘GHC.Word’
 instance GHC.Enum.Enum Foreign.Ptr.IntPtr -- Defined in ‘Foreign.Ptr’
 instance GHC.Enum.Enum Foreign.Ptr.WordPtr -- Defined in ‘Foreign.Ptr’
 instance [safe] GHC.Enum.Enum GHC.ByteOrder.ByteOrder -- Defined in ‘GHC.ByteOrder’
-instance GHC.Enum.Enum GHC.Types.Bool -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.Char -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.Int -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Num.Integer.Integer -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.Levity -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Num.Natural.Natural -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.Ordering -- Defined in ‘GHC.Enum’
-instance forall a. GHC.Enum.Enum a => GHC.Enum.Enum (Solo a) -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum () -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.VecCount -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.VecElem -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.Word -- Defined in ‘GHC.Enum’
 instance GHC.Enum.Enum GHC.Types.Double -- Defined in ‘GHC.Float’
 instance GHC.Enum.Enum GHC.Types.Float -- Defined in ‘GHC.Float’
 instance GHC.Enum.Enum GHC.Generics.Associativity -- Defined in ‘GHC.Generics’
diff --git a/testsuite/tests/interface-stability/base-exports.stdout-mingw32 b/testsuite/tests/interface-stability/base-exports.stdout-mingw32
index 88b5d354ea1aa40f9600d1aacd36423bf6ceeb0c..92785aaa6ab61bcef32f9cd544987fb4f42813d3 100644
--- a/testsuite/tests/interface-stability/base-exports.stdout-mingw32
+++ b/testsuite/tests/interface-stability/base-exports.stdout-mingw32
@@ -906,6 +906,25 @@ module Data.Either where
   partitionEithers :: forall a b. [Either a b] -> ([a], [b])
   rights :: forall a b. [Either a b] -> [b]
 
+module Data.Enum where
+  -- Safety: Safe-Inferred
+  type Bounded :: * -> Constraint
+  class Bounded a where
+    minBound :: a
+    maxBound :: a
+    {-# MINIMAL minBound, maxBound #-}
+  type Enum :: * -> Constraint
+  class Enum a where
+    succ :: a -> a
+    pred :: a -> a
+    toEnum :: GHC.Types.Int -> a
+    fromEnum :: a -> GHC.Types.Int
+    enumFrom :: a -> [a]
+    enumFromThen :: a -> a -> [a]
+    enumFromTo :: a -> a -> [a]
+    enumFromThenTo :: a -> a -> a -> [a]
+    {-# MINIMAL toEnum, fromEnum #-}
+
 module Data.Eq where
   -- Safety: Trustworthy
   type Eq :: * -> Constraint
@@ -11579,6 +11598,30 @@ instance GHC.Enum.Bounded GHC.Unicode.GeneralCategory -- Defined in ‘GHC.Unico
 instance forall k (a :: k) (b :: k). (a ~ b) => GHC.Enum.Bounded (a Data.Type.Equality.:~: b) -- Defined in ‘Data.Type.Equality’
 instance forall k1 k2 (a :: k1) (b :: k2). (a ~~ b) => GHC.Enum.Bounded (a Data.Type.Equality.:~~: b) -- Defined in ‘Data.Type.Equality’
 instance forall k (t :: k). GHC.Enum.Bounded (Data.Proxy.Proxy t) -- Defined in ‘Data.Proxy’
+instance GHC.Enum.Bounded GHC.Types.Bool -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.Char -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.Int -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.Levity -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.Ordering -- Defined in ‘GHC.Enum’
+instance forall a. GHC.Enum.Bounded a => GHC.Enum.Bounded (Solo a) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i j. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i j k. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i j k l. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i j k l m. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i j k l m n. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m, GHC.Enum.Bounded n) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i j k l m n o. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m, GHC.Enum.Bounded n, GHC.Enum.Bounded o) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -- Defined in ‘GHC.Enum’
+instance forall a b. (GHC.Enum.Bounded a, GHC.Enum.Bounded b) => GHC.Enum.Bounded (a, b) -- Defined in ‘GHC.Enum’
+instance forall a b c. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c) => GHC.Enum.Bounded (a, b, c) -- Defined in ‘GHC.Enum’
+instance forall a b c d. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d) => GHC.Enum.Bounded (a, b, c, d) -- Defined in ‘GHC.Enum’
+instance forall a b c d e. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e) => GHC.Enum.Bounded (a, b, c, d, e) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f) => GHC.Enum.Bounded (a, b, c, d, e, f) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g) => GHC.Enum.Bounded (a, b, c, d, e, f, g) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i) -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded () -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.VecCount -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.VecElem -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.Word -- Defined in ‘GHC.Enum’
 instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Enum.Bounded (f (g a)) => GHC.Enum.Bounded (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
 instance forall a. GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Functor.Identity.Identity a) -- Defined in ‘Data.Functor.Identity’
 instance GHC.Enum.Bounded GHC.Int.Int16 -- Defined in ‘GHC.Int’
@@ -11604,30 +11647,6 @@ instance GHC.Enum.Bounded GHC.Word.Word8 -- Defined in ‘GHC.Word’
 instance GHC.Enum.Bounded Foreign.Ptr.IntPtr -- Defined in ‘Foreign.Ptr’
 instance GHC.Enum.Bounded Foreign.Ptr.WordPtr -- Defined in ‘Foreign.Ptr’
 instance [safe] GHC.Enum.Bounded GHC.ByteOrder.ByteOrder -- Defined in ‘GHC.ByteOrder’
-instance GHC.Enum.Bounded GHC.Types.Bool -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.Char -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.Int -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.Levity -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.Ordering -- Defined in ‘GHC.Enum’
-instance forall a. GHC.Enum.Bounded a => GHC.Enum.Bounded (Solo a) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i j. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i j k. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i j k l. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i j k l m. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i j k l m n. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m, GHC.Enum.Bounded n) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i j k l m n o. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m, GHC.Enum.Bounded n, GHC.Enum.Bounded o) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -- Defined in ‘GHC.Enum’
-instance forall a b. (GHC.Enum.Bounded a, GHC.Enum.Bounded b) => GHC.Enum.Bounded (a, b) -- Defined in ‘GHC.Enum’
-instance forall a b c. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c) => GHC.Enum.Bounded (a, b, c) -- Defined in ‘GHC.Enum’
-instance forall a b c d. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d) => GHC.Enum.Bounded (a, b, c, d) -- Defined in ‘GHC.Enum’
-instance forall a b c d e. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e) => GHC.Enum.Bounded (a, b, c, d, e) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f) => GHC.Enum.Bounded (a, b, c, d, e, f) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g) => GHC.Enum.Bounded (a, b, c, d, e, f, g) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i) -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded () -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.VecCount -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.VecElem -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.Word -- Defined in ‘GHC.Enum’
 instance GHC.Enum.Bounded GHC.Generics.Associativity -- Defined in ‘GHC.Generics’
 instance GHC.Enum.Bounded GHC.Generics.DecidedStrictness -- Defined in ‘GHC.Generics’
 instance GHC.Enum.Bounded GHC.Generics.SourceStrictness -- Defined in ‘GHC.Generics’
@@ -11641,6 +11660,18 @@ instance GHC.Enum.Enum GHC.Unicode.GeneralCategory -- Defined in ‘GHC.Unicode
 instance forall k (a :: k) (b :: k). (a ~ b) => GHC.Enum.Enum (a Data.Type.Equality.:~: b) -- Defined in ‘Data.Type.Equality’
 instance forall k1 k2 (a :: k1) (b :: k2). (a ~~ b) => GHC.Enum.Enum (a Data.Type.Equality.:~~: b) -- Defined in ‘Data.Type.Equality’
 instance forall k (s :: k). GHC.Enum.Enum (Data.Proxy.Proxy s) -- Defined in ‘Data.Proxy’
+instance GHC.Enum.Enum GHC.Types.Bool -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.Char -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.Int -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Num.Integer.Integer -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.Levity -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Num.Natural.Natural -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.Ordering -- Defined in ‘GHC.Enum’
+instance forall a. GHC.Enum.Enum a => GHC.Enum.Enum (Solo a) -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum () -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.VecCount -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.VecElem -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.Word -- Defined in ‘GHC.Enum’
 instance forall k (a :: k). GHC.Enum.Enum (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
 instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Enum.Enum (f (g a)) => GHC.Enum.Enum (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
 instance forall a. GHC.Enum.Enum a => GHC.Enum.Enum (Data.Functor.Identity.Identity a) -- Defined in ‘Data.Functor.Identity’
@@ -11666,18 +11697,6 @@ instance GHC.Enum.Enum Foreign.Ptr.IntPtr -- Defined in ‘Foreign.Ptr’
 instance GHC.Enum.Enum Foreign.Ptr.WordPtr -- Defined in ‘Foreign.Ptr’
 instance [safe] GHC.Enum.Enum GHC.ByteOrder.ByteOrder -- Defined in ‘GHC.ByteOrder’
 instance GHC.Enum.Enum GHC.Event.Windows.ConsoleEvent.ConsoleEvent -- Defined in ‘GHC.Event.Windows.ConsoleEvent’
-instance GHC.Enum.Enum GHC.Types.Bool -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.Char -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.Int -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Num.Integer.Integer -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.Levity -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Num.Natural.Natural -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.Ordering -- Defined in ‘GHC.Enum’
-instance forall a. GHC.Enum.Enum a => GHC.Enum.Enum (Solo a) -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum () -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.VecCount -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.VecElem -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.Word -- Defined in ‘GHC.Enum’
 instance GHC.Enum.Enum GHC.Types.Double -- Defined in ‘GHC.Float’
 instance GHC.Enum.Enum GHC.Types.Float -- Defined in ‘GHC.Float’
 instance GHC.Enum.Enum GHC.Generics.Associativity -- Defined in ‘GHC.Generics’
diff --git a/testsuite/tests/interface-stability/base-exports.stdout-ws-32 b/testsuite/tests/interface-stability/base-exports.stdout-ws-32
index 8a5a5c9964b3aa080d9fa066adcca48d4da1bf3c..6ea64b7e2958efd56a069d5cb99b0043708d7497 100644
--- a/testsuite/tests/interface-stability/base-exports.stdout-ws-32
+++ b/testsuite/tests/interface-stability/base-exports.stdout-ws-32
@@ -906,6 +906,25 @@ module Data.Either where
   partitionEithers :: forall a b. [Either a b] -> ([a], [b])
   rights :: forall a b. [Either a b] -> [b]
 
+module Data.Enum where
+  -- Safety: Safe-Inferred
+  type Bounded :: * -> Constraint
+  class Bounded a where
+    minBound :: a
+    maxBound :: a
+    {-# MINIMAL minBound, maxBound #-}
+  type Enum :: * -> Constraint
+  class Enum a where
+    succ :: a -> a
+    pred :: a -> a
+    toEnum :: GHC.Types.Int -> a
+    fromEnum :: a -> GHC.Types.Int
+    enumFrom :: a -> [a]
+    enumFromThen :: a -> a -> [a]
+    enumFromTo :: a -> a -> [a]
+    enumFromThenTo :: a -> a -> a -> [a]
+    {-# MINIMAL toEnum, fromEnum #-}
+
 module Data.Eq where
   -- Safety: Trustworthy
   type Eq :: * -> Constraint
@@ -11315,6 +11334,30 @@ instance GHC.Enum.Bounded GHC.Unicode.GeneralCategory -- Defined in ‘GHC.Unico
 instance forall k (a :: k) (b :: k). (a ~ b) => GHC.Enum.Bounded (a Data.Type.Equality.:~: b) -- Defined in ‘Data.Type.Equality’
 instance forall k1 k2 (a :: k1) (b :: k2). (a ~~ b) => GHC.Enum.Bounded (a Data.Type.Equality.:~~: b) -- Defined in ‘Data.Type.Equality’
 instance forall k (t :: k). GHC.Enum.Bounded (Data.Proxy.Proxy t) -- Defined in ‘Data.Proxy’
+instance GHC.Enum.Bounded GHC.Types.Bool -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.Char -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.Int -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.Levity -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.Ordering -- Defined in ‘GHC.Enum’
+instance forall a. GHC.Enum.Bounded a => GHC.Enum.Bounded (Solo a) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i j. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i j k. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i j k l. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i j k l m. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i j k l m n. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m, GHC.Enum.Bounded n) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i j k l m n o. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m, GHC.Enum.Bounded n, GHC.Enum.Bounded o) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -- Defined in ‘GHC.Enum’
+instance forall a b. (GHC.Enum.Bounded a, GHC.Enum.Bounded b) => GHC.Enum.Bounded (a, b) -- Defined in ‘GHC.Enum’
+instance forall a b c. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c) => GHC.Enum.Bounded (a, b, c) -- Defined in ‘GHC.Enum’
+instance forall a b c d. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d) => GHC.Enum.Bounded (a, b, c, d) -- Defined in ‘GHC.Enum’
+instance forall a b c d e. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e) => GHC.Enum.Bounded (a, b, c, d, e) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f) => GHC.Enum.Bounded (a, b, c, d, e, f) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g) => GHC.Enum.Bounded (a, b, c, d, e, f, g) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h) -- Defined in ‘GHC.Enum’
+instance forall a b c d e f g h i. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i) -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded () -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.VecCount -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.VecElem -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Bounded GHC.Types.Word -- Defined in ‘GHC.Enum’
 instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Enum.Bounded (f (g a)) => GHC.Enum.Bounded (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
 instance forall a. GHC.Enum.Bounded a => GHC.Enum.Bounded (Data.Functor.Identity.Identity a) -- Defined in ‘Data.Functor.Identity’
 instance GHC.Enum.Bounded GHC.Int.Int16 -- Defined in ‘GHC.Int’
@@ -11340,30 +11383,6 @@ instance GHC.Enum.Bounded GHC.Word.Word8 -- Defined in ‘GHC.Word’
 instance GHC.Enum.Bounded Foreign.Ptr.IntPtr -- Defined in ‘Foreign.Ptr’
 instance GHC.Enum.Bounded Foreign.Ptr.WordPtr -- Defined in ‘Foreign.Ptr’
 instance [safe] GHC.Enum.Bounded GHC.ByteOrder.ByteOrder -- Defined in ‘GHC.ByteOrder’
-instance GHC.Enum.Bounded GHC.Types.Bool -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.Char -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.Int -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.Levity -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.Ordering -- Defined in ‘GHC.Enum’
-instance forall a. GHC.Enum.Bounded a => GHC.Enum.Bounded (Solo a) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i j. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i j k. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i j k l. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i j k l m. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i j k l m n. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m, GHC.Enum.Bounded n) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i j k l m n o. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i, GHC.Enum.Bounded j, GHC.Enum.Bounded k, GHC.Enum.Bounded l, GHC.Enum.Bounded m, GHC.Enum.Bounded n, GHC.Enum.Bounded o) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -- Defined in ‘GHC.Enum’
-instance forall a b. (GHC.Enum.Bounded a, GHC.Enum.Bounded b) => GHC.Enum.Bounded (a, b) -- Defined in ‘GHC.Enum’
-instance forall a b c. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c) => GHC.Enum.Bounded (a, b, c) -- Defined in ‘GHC.Enum’
-instance forall a b c d. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d) => GHC.Enum.Bounded (a, b, c, d) -- Defined in ‘GHC.Enum’
-instance forall a b c d e. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e) => GHC.Enum.Bounded (a, b, c, d, e) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f) => GHC.Enum.Bounded (a, b, c, d, e, f) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g) => GHC.Enum.Bounded (a, b, c, d, e, f, g) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h) -- Defined in ‘GHC.Enum’
-instance forall a b c d e f g h i. (GHC.Enum.Bounded a, GHC.Enum.Bounded b, GHC.Enum.Bounded c, GHC.Enum.Bounded d, GHC.Enum.Bounded e, GHC.Enum.Bounded f, GHC.Enum.Bounded g, GHC.Enum.Bounded h, GHC.Enum.Bounded i) => GHC.Enum.Bounded (a, b, c, d, e, f, g, h, i) -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded () -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.VecCount -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.VecElem -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Bounded GHC.Types.Word -- Defined in ‘GHC.Enum’
 instance GHC.Enum.Bounded GHC.Generics.Associativity -- Defined in ‘GHC.Generics’
 instance GHC.Enum.Bounded GHC.Generics.DecidedStrictness -- Defined in ‘GHC.Generics’
 instance GHC.Enum.Bounded GHC.Generics.SourceStrictness -- Defined in ‘GHC.Generics’
@@ -11377,6 +11396,18 @@ instance GHC.Enum.Enum GHC.Unicode.GeneralCategory -- Defined in ‘GHC.Unicode
 instance forall k (a :: k) (b :: k). (a ~ b) => GHC.Enum.Enum (a Data.Type.Equality.:~: b) -- Defined in ‘Data.Type.Equality’
 instance forall k1 k2 (a :: k1) (b :: k2). (a ~~ b) => GHC.Enum.Enum (a Data.Type.Equality.:~~: b) -- Defined in ‘Data.Type.Equality’
 instance forall k (s :: k). GHC.Enum.Enum (Data.Proxy.Proxy s) -- Defined in ‘Data.Proxy’
+instance GHC.Enum.Enum GHC.Types.Bool -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.Char -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.Int -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Num.Integer.Integer -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.Levity -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Num.Natural.Natural -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.Ordering -- Defined in ‘GHC.Enum’
+instance forall a. GHC.Enum.Enum a => GHC.Enum.Enum (Solo a) -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum () -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.VecCount -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.VecElem -- Defined in ‘GHC.Enum’
+instance GHC.Enum.Enum GHC.Types.Word -- Defined in ‘GHC.Enum’
 instance forall k (a :: k). GHC.Enum.Enum (Data.Fixed.Fixed a) -- Defined in ‘Data.Fixed’
 instance forall k1 k2 (f :: k1 -> *) (g :: k2 -> k1) (a :: k2). GHC.Enum.Enum (f (g a)) => GHC.Enum.Enum (Data.Functor.Compose.Compose f g a) -- Defined in ‘Data.Functor.Compose’
 instance forall a. GHC.Enum.Enum a => GHC.Enum.Enum (Data.Functor.Identity.Identity a) -- Defined in ‘Data.Functor.Identity’
@@ -11401,18 +11432,6 @@ instance GHC.Enum.Enum GHC.Word.Word8 -- Defined in ‘GHC.Word’
 instance GHC.Enum.Enum Foreign.Ptr.IntPtr -- Defined in ‘Foreign.Ptr’
 instance GHC.Enum.Enum Foreign.Ptr.WordPtr -- Defined in ‘Foreign.Ptr’
 instance [safe] GHC.Enum.Enum GHC.ByteOrder.ByteOrder -- Defined in ‘GHC.ByteOrder’
-instance GHC.Enum.Enum GHC.Types.Bool -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.Char -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.Int -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Num.Integer.Integer -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.Levity -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Num.Natural.Natural -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.Ordering -- Defined in ‘GHC.Enum’
-instance forall a. GHC.Enum.Enum a => GHC.Enum.Enum (Solo a) -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum () -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.VecCount -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.VecElem -- Defined in ‘GHC.Enum’
-instance GHC.Enum.Enum GHC.Types.Word -- Defined in ‘GHC.Enum’
 instance GHC.Enum.Enum GHC.Types.Double -- Defined in ‘GHC.Float’
 instance GHC.Enum.Enum GHC.Types.Float -- Defined in ‘GHC.Float’
 instance GHC.Enum.Enum GHC.Generics.Associativity -- Defined in ‘GHC.Generics’