[Git][ghc/ghc][wip/base-stability] 10 commits: nativeGen: Explicitly set flags of text sections on Windows

Ben Gamari (@bgamari) gitlab at gitlab.haskell.org
Fri Jul 21 15:49:25 UTC 2023



Ben Gamari pushed to branch wip/base-stability at Glasgow Haskell Compiler / GHC


Commits:
3ece9856 by Ben Gamari at 2023-07-21T07:30:45-04:00
nativeGen: Explicitly set flags of text sections on Windows

The binutils documentation (for COFF) claims,

> If no flags are specified, the default flags depend upon the section
> name. If the section name is not recognized, the default will be for the
> section to be loaded and writable.

We previously assumed that this would do the right thing for split
sections (e.g. a section named `.text$foo` would be correctly inferred
to be a text section). However, we have observed that this is not the
case (at least under the clang toolchain used on Windows): when
split-sections is enabled, text sections are treated by the assembler as
data (matching the "default" behavior specified by the documentation).

Avoid this by setting section flags explicitly. This should fix split
sections on Windows.

Fixes #22834.

- - - - -
db7f7240 by Ben Gamari at 2023-07-21T07:30:45-04:00
nativeGen: Set explicit section types on all platforms

- - - - -
b444c16f by Finley McIlwaine at 2023-07-21T07:31:28-04:00
Insert documentation into parsed signature modules

Causes haddock comments in signature modules to be properly
inserted into the AST (just as they are for regular modules)
if the `-haddock` flag is given.

Also adds a test that compares `-ddump-parsed-ast` output
for a signature module to prevent further regressions.

Fixes #23315

- - - - -
f7ce8a63 by Ben Gamari at 2023-07-21T11:49:00-04:00
base: Introduce Data.Enum

- - - - -
e2c6430d by Ben Gamari at 2023-07-21T11:49:00-04:00
base: Add export list to GHC.Num.Integer

- - - - -
d03cd0ce by Ben Gamari at 2023-07-21T11:49:00-04:00
base: Add export list to GHC.Num

- - - - -
d31b53ef by Ben Gamari at 2023-07-21T11:49:00-04:00
base: Add export list to GHC.Num.Natural

- - - - -
85b7225c by Ben Gamari at 2023-07-21T11:49:00-04:00
base: Add export list to GHC.Float

- - - - -
22d1f46c by Ben Gamari at 2023-07-21T11:49:00-04:00
base: Add export list to GHC.Real

- - - - -
dd16a902 by Ben Gamari at 2023-07-21T11:49:00-04:00
base: Eliminate module reexport in GHC.Exception

The metric increase here isn't strictly due to this commit but it's a
rather small, incidental change.

Metric Increase:
    T13386

Metric Decrease:
    T13386
    T8095

- - - - -


23 changed files:

- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/CmmToAsm/Ppr.hs
- compiler/GHC/Parser.y
- + libraries/base/Data/Enum.hs
- libraries/base/GHC/Exception.hs
- libraries/base/GHC/Float.hs
- libraries/base/GHC/Num.hs
- libraries/base/GHC/Real.hs
- libraries/base/base.cabal
- libraries/ghc-bignum/src/GHC/Num/Integer.hs
- libraries/ghc-bignum/src/GHC/Num/Natural.hs
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- + testsuite/tests/parser/should_compile/T23315/Makefile
- + testsuite/tests/parser/should_compile/T23315/Setup.hs
- + testsuite/tests/parser/should_compile/T23315/T23315.cabal
- + testsuite/tests/parser/should_compile/T23315/T23315.hsig
- + testsuite/tests/parser/should_compile/T23315/T23315.stderr
- + testsuite/tests/parser/should_compile/T23315/all.T


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -511,7 +511,7 @@ doc-tarball:
       optional: true
     - job: nightly-x86_64-windows-validate
       optional: true
-    - job: release-x86_64-windows-release+no_split_sections
+    - job: release-x86_64-windows-release
       optional: true
 
   tags:
@@ -535,7 +535,7 @@ doc-tarball:
         || mv "ghc-x86_64-linux-deb10-release.tar.xz" "$LINUX_BINDIST" \
         || true
       mv "ghc-x86_64-windows-validate.tar.xz" "$WINDOWS_BINDIST" \
-        || mv "ghc-x86_64-windows-release+no_split_sections.tar.xz" "$WINDOWS_BINDIST" \
+        || mv "ghc-x86_64-windows-release.tar.xz" "$WINDOWS_BINDIST" \
         || true
       if [ ! -f "$LINUX_BINDIST" ]; then
         echo "Error: $LINUX_BINDIST does not exist. Did the Debian 9 job fail?"


=====================================
.gitlab/generate-ci/gen_ci.hs
=====================================
@@ -921,8 +921,8 @@ job_groups =
      -- This job is only for generating head.hackage docs
      , hackage_doc_job (disableValidate (standardBuildsWithConfig Amd64 (Linux Fedora33) releaseConfig))
      , disableValidate (standardBuildsWithConfig Amd64 (Linux Fedora33) dwarf)
-     , fastCI (standardBuildsWithConfig Amd64 Windows (splitSectionsBroken vanilla))
-     , disableValidate (standardBuildsWithConfig Amd64 Windows (splitSectionsBroken nativeInt))
+     , fastCI (standardBuildsWithConfig Amd64 Windows vanilla)
+     , disableValidate (standardBuildsWithConfig Amd64 Windows nativeInt)
      , standardBuilds Amd64 Darwin
      , allowFailureGroup (addValidateRule FreeBSDLabel (validateBuilds Amd64 FreeBSD13 vanilla))
      , fastCI (standardBuilds AArch64 Darwin)


=====================================
.gitlab/jobs.yaml
=====================================
@@ -3577,7 +3577,7 @@
       "XZ_OPT": "-9"
     }
   },
-  "release-x86_64-windows-int_native-release+no_split_sections": {
+  "release-x86_64-windows-int_native-release": {
     "after_script": [
       "bash .gitlab/ci.sh save_cache",
       "bash .gitlab/ci.sh save_test_output",
@@ -3587,7 +3587,7 @@
     "artifacts": {
       "expire_in": "1 year",
       "paths": [
-        "ghc-x86_64-windows-int_native-release+no_split_sections.tar.xz",
+        "ghc-x86_64-windows-int_native-release.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -3626,8 +3626,8 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "native",
-      "BIN_DIST_NAME": "ghc-x86_64-windows-int_native-release+no_split_sections",
-      "BUILD_FLAVOUR": "release+no_split_sections",
+      "BIN_DIST_NAME": "ghc-x86_64-windows-int_native-release",
+      "BUILD_FLAVOUR": "release",
       "CABAL_INSTALL_VERSION": "3.8.1.0",
       "CONFIGURE_ARGS": "",
       "GHC_VERSION": "9.4.3",
@@ -3636,11 +3636,11 @@
       "LANG": "en_US.UTF-8",
       "MSYSTEM": "CLANG64",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-windows-int_native-release+no_split_sections",
+      "TEST_ENV": "x86_64-windows-int_native-release",
       "XZ_OPT": "-9"
     }
   },
-  "release-x86_64-windows-release+no_split_sections": {
+  "release-x86_64-windows-release": {
     "after_script": [
       "bash .gitlab/ci.sh save_cache",
       "bash .gitlab/ci.sh save_test_output",
@@ -3650,7 +3650,7 @@
     "artifacts": {
       "expire_in": "1 year",
       "paths": [
-        "ghc-x86_64-windows-release+no_split_sections.tar.xz",
+        "ghc-x86_64-windows-release.tar.xz",
         "junit.xml",
         "unexpected-test-output.tar.gz"
       ],
@@ -3689,8 +3689,8 @@
     ],
     "variables": {
       "BIGNUM_BACKEND": "gmp",
-      "BIN_DIST_NAME": "ghc-x86_64-windows-release+no_split_sections",
-      "BUILD_FLAVOUR": "release+no_split_sections",
+      "BIN_DIST_NAME": "ghc-x86_64-windows-release",
+      "BUILD_FLAVOUR": "release",
       "CABAL_INSTALL_VERSION": "3.8.1.0",
       "CONFIGURE_ARGS": "",
       "GHC_VERSION": "9.4.3",
@@ -3699,7 +3699,7 @@
       "LANG": "en_US.UTF-8",
       "MSYSTEM": "CLANG64",
       "RUNTEST_ARGS": "",
-      "TEST_ENV": "x86_64-windows-release+no_split_sections",
+      "TEST_ENV": "x86_64-windows-release",
       "XZ_OPT": "-9"
     }
   },


=====================================
compiler/GHC/CmmToAsm/Ppr.hs
=====================================
@@ -245,6 +245,10 @@ pprGNUSectionHeader config t suffix =
       OtherSection _ ->
         panic "PprBase.pprGNUSectionHeader: unknown section type"
     flags = case t of
+      Text
+        | OSMinGW32 <- platformOS platform
+                    -> text ",\"xr\""
+        | otherwise -> text ",\"ax\"," <> sectionType platform "progbits"
       CString
         | OSMinGW32 <- platformOS platform
                     -> empty


=====================================
compiler/GHC/Parser.y
=====================================
@@ -751,7 +751,7 @@ TH_QQUASIQUOTE  { L _ (ITqQuasiQuote _) }
 
 -- Exported parsers
 %name parseModuleNoHaddock module
-%name parseSignature signature
+%name parseSignatureNoHaddock signature
 %name parseImport importdecl
 %name parseStatement e_stmt
 %name parseDeclaration topdecl
@@ -4416,18 +4416,29 @@ pvL :: MonadP m => m (LocatedAn t a) -> m (Located a)
 pvL a = do { av <- a
            ; return (reLoc av) }
 
--- | Parse a Haskell module with Haddock comments.
--- This is done in two steps:
+-- | Parse a Haskell module with Haddock comments. This is done in two steps:
 --
 -- * 'parseModuleNoHaddock' to build the AST
 -- * 'addHaddockToModule' to insert Haddock comments into it
 --
--- This is the only parser entry point that deals with Haddock comments.
--- The other entry points ('parseDeclaration', 'parseExpression', etc) do
--- not insert them into the AST.
+-- This and the signature module parser are the only parser entry points that
+-- deal with Haddock comments. The other entry points ('parseDeclaration',
+-- 'parseExpression', etc) do not insert them into the AST.
 parseModule :: P (Located (HsModule GhcPs))
 parseModule = parseModuleNoHaddock >>= addHaddockToModule
 
+-- | Parse a Haskell signature module with Haddock comments. This is done in two
+-- steps:
+--
+-- * 'parseSignatureNoHaddock' to build the AST
+-- * 'addHaddockToModule' to insert Haddock comments into it
+--
+-- This and the module parser are the only parser entry points that deal with
+-- Haddock comments. The other entry points ('parseDeclaration',
+-- 'parseExpression', etc) do not insert them into the AST.
+parseSignature :: P (Located (HsModule GhcPs))
+parseSignature = parseSignatureNoHaddock >>= addHaddockToModule
+
 commentsA :: (Monoid ann) => SrcSpan -> EpAnnComments -> SrcSpanAnn' (EpAnn ann)
 commentsA loc cs = SrcSpanAnn (EpAnn (Anchor (rs loc) UnchangedAnchor) mempty cs) loc
 


=====================================
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 at haskell.org
+-- Stability   :  stable
+-- Portability :  non-portable (GHC extensions)
+--
+-- The 'Enum' and 'Bounded' classes.
+--
+-----------------------------------------------------------------------------
+
+module Data.Enum
+    ( Bounded(..)
+    , Enum(..)
+    ) where
+
+import GHC.Enum


=====================================
libraries/base/GHC/Exception.hs
=====================================
@@ -23,16 +23,33 @@
 -----------------------------------------------------------------------------
 
 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


=====================================
libraries/base/GHC/Float.hs
=====================================
@@ -45,14 +45,102 @@
 
 
 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
+    , 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
+    ) where
 
 import Data.Maybe
 


=====================================
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


=====================================
libraries/base/GHC/Real.hs
=====================================
@@ -18,7 +18,66 @@
 --
 -----------------------------------------------------------------------------
 
-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
+    ) where
 
 #include "MachDeps.h"
 


=====================================
libraries/base/base.cabal
=====================================
@@ -127,6 +127,7 @@ Library
         Data.Dynamic
         Data.Either
         Data.Eq
+        Data.Enum
         Data.Fixed
         Data.Foldable
         Data.Foldable1


=====================================
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"


=====================================
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


=====================================
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
@@ -6999,7 +7018,6 @@ module GHC.Float where
   castWord64ToDouble :: GHC.Word.Word64 -> Double
   ceilingDouble :: forall b. GHC.Real.Integral b => Double -> b
   ceilingFloat :: forall b. GHC.Real.Integral b => Float -> b
-  clamp :: GHC.Types.Int -> GHC.Types.Int -> GHC.Types.Int
   cosDouble :: Double -> Double
   cosFloat :: Float -> Float
   coshDouble :: Double -> Double
@@ -7014,9 +7032,6 @@ module GHC.Float where
   expFloat :: Float -> Float
   expm1Double :: Double -> Double
   expm1Float :: Float -> Float
-  expt :: GHC.Num.Integer.Integer -> GHC.Types.Int -> GHC.Num.Integer.Integer
-  expts :: GHC.Arr.Array GHC.Types.Int GHC.Num.Integer.Integer
-  expts10 :: GHC.Arr.Array GHC.Types.Int GHC.Num.Integer.Integer
   fabsDouble :: Double -> Double
   fabsFloat :: Float -> Float
   float2Double :: Float -> Double
@@ -7028,7 +7043,6 @@ module GHC.Float where
   formatRealFloatAlt :: forall a. RealFloat a => FFFormat -> GHC.Maybe.Maybe GHC.Types.Int -> GHC.Types.Bool -> a -> GHC.Base.String
   fromRat :: forall a. RealFloat a => GHC.Real.Rational -> a
   fromRat' :: forall a. RealFloat a => GHC.Real.Rational -> a
-  fromRat'' :: forall a. RealFloat a => GHC.Types.Int -> GHC.Types.Int -> GHC.Num.Integer.Integer -> GHC.Num.Integer.Integer -> a
   geDouble :: Double -> Double -> GHC.Types.Bool
   geFloat :: Float -> Float -> GHC.Types.Bool
   gtDouble :: Double -> Double -> GHC.Types.Bool
@@ -7057,9 +7071,6 @@ module GHC.Float where
   logFloat :: Float -> Float
   ltDouble :: Double -> Double -> GHC.Types.Bool
   ltFloat :: Float -> Float -> GHC.Types.Bool
-  maxExpt :: GHC.Types.Int
-  maxExpt10 :: GHC.Types.Int
-  minExpt :: GHC.Types.Int
   minusDouble :: Double -> Double -> Double
   minusFloat :: Float -> Float -> Float
   naturalToDouble# :: GHC.Num.Natural.Natural -> Double#
@@ -7068,8 +7079,6 @@ module GHC.Float where
   negateFloat :: Float -> Float
   plusDouble :: Double -> Double -> Double
   plusFloat :: Float -> Float -> Float
-  powerDouble :: Double -> Double -> Double
-  powerFloat :: Float -> Float -> Float
   properFractionDouble :: forall b. GHC.Real.Integral b => Double -> (b, Double)
   properFractionFloat :: forall b. GHC.Real.Integral b => Float -> (b, Float)
   rationalToDouble :: GHC.Num.Integer.Integer -> GHC.Num.Integer.Integer -> Double
@@ -7086,10 +7095,6 @@ module GHC.Float where
   sinhFloat :: Float -> Float
   sqrtDouble :: Double -> Double
   sqrtFloat :: Float -> Float
-  stgDoubleToWord64 :: Double# -> GHC.Prim.Word64#
-  stgFloatToWord32 :: Float# -> GHC.Prim.Word32#
-  stgWord32ToFloat :: GHC.Prim.Word32# -> Float#
-  stgWord64ToDouble :: GHC.Prim.Word64# -> Double#
   tanDouble :: Double -> Double
   tanFloat :: Float -> Float
   tanhDouble :: Double -> Double
@@ -7097,7 +7102,6 @@ module GHC.Float where
   timesDouble :: Double -> Double -> Double
   timesFloat :: Float -> Float -> Float
   truncateDouble :: forall b. GHC.Real.Integral b => Double -> b
-  truncateFloat :: forall b. GHC.Real.Integral b => Float -> b
   word2Double :: GHC.Types.Word -> Double
   word2Float :: GHC.Types.Word -> Float
 
@@ -9002,8 +9006,6 @@ module GHC.Real where
     recip :: a -> a
     fromRational :: Rational -> a
     {-# MINIMAL fromRational, (recip | (/)) #-}
-  type FractionalExponentBase :: *
-  data FractionalExponentBase = Base2 | Base10
   type Integral :: * -> Constraint
   class (Real a, GHC.Enum.Enum a) => Integral a where
     quot :: a -> a -> a
@@ -9031,9 +9033,7 @@ module GHC.Real where
     floor :: forall b. Integral b => a -> b
     {-# MINIMAL properFraction #-}
   (^) :: forall a b. (GHC.Num.Num a, Integral b) => a -> b -> a
-  (^%^) :: forall a. Integral a => Rational -> a -> Rational
   (^^) :: forall a b. (Fractional a, Integral b) => a -> b -> a
-  (^^%^^) :: forall a. Integral a => Rational -> a -> Rational
   denominator :: forall a. Ratio a -> a
   divZeroError :: forall a. a
   even :: forall a. Integral a => a -> GHC.Types.Bool
@@ -9047,7 +9047,6 @@ module GHC.Real where
   lcm :: forall a. Integral a => a -> a -> a
   mkRationalBase10 :: Rational -> GHC.Num.Integer.Integer -> Rational
   mkRationalBase2 :: Rational -> GHC.Num.Integer.Integer -> Rational
-  mkRationalWithExponentBase :: Rational -> GHC.Num.Integer.Integer -> FractionalExponentBase -> Rational
   notANumber :: Rational
   numerator :: forall a. Ratio a -> a
   numericEnumFrom :: forall a. Fractional a => a -> [a]
@@ -9056,8 +9055,6 @@ module GHC.Real where
   numericEnumFromTo :: forall a. (GHC.Classes.Ord a, Fractional a) => a -> a -> [a]
   odd :: forall a. Integral a => a -> GHC.Types.Bool
   overflowError :: forall a. a
-  powImpl :: forall a b. (GHC.Num.Num a, Integral b) => a -> b -> a
-  powImplAcc :: forall a b. (GHC.Num.Num a, Integral b) => a -> b -> a -> a
   ratioPrec :: GHC.Types.Int
   ratioPrec1 :: GHC.Types.Int
   ratioZeroDenominatorError :: forall a. a
@@ -11309,6 +11306,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’
@@ -11334,30 +11355,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’
@@ -11371,6 +11368,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’
@@ -11395,18 +11404,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’


=====================================
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
@@ -6968,7 +6987,6 @@ module GHC.Float where
   castWord64ToDouble :: GHC.Word.Word64 -> Double
   ceilingDouble :: forall b. GHC.Real.Integral b => Double -> b
   ceilingFloat :: forall b. GHC.Real.Integral b => Float -> b
-  clamp :: GHC.Types.Int -> GHC.Types.Int -> GHC.Types.Int
   cosDouble :: Double -> Double
   cosFloat :: Float -> Float
   coshDouble :: Double -> Double
@@ -6983,9 +7001,6 @@ module GHC.Float where
   expFloat :: Float -> Float
   expm1Double :: Double -> Double
   expm1Float :: Float -> Float
-  expt :: GHC.Num.Integer.Integer -> GHC.Types.Int -> GHC.Num.Integer.Integer
-  expts :: GHC.Arr.Array GHC.Types.Int GHC.Num.Integer.Integer
-  expts10 :: GHC.Arr.Array GHC.Types.Int GHC.Num.Integer.Integer
   fabsDouble :: Double -> Double
   fabsFloat :: Float -> Float
   float2Double :: Float -> Double
@@ -6997,7 +7012,6 @@ module GHC.Float where
   formatRealFloatAlt :: forall a. RealFloat a => FFFormat -> GHC.Maybe.Maybe GHC.Types.Int -> GHC.Types.Bool -> a -> GHC.Base.String
   fromRat :: forall a. RealFloat a => GHC.Real.Rational -> a
   fromRat' :: forall a. RealFloat a => GHC.Real.Rational -> a
-  fromRat'' :: forall a. RealFloat a => GHC.Types.Int -> GHC.Types.Int -> GHC.Num.Integer.Integer -> GHC.Num.Integer.Integer -> a
   geDouble :: Double -> Double -> GHC.Types.Bool
   geFloat :: Float -> Float -> GHC.Types.Bool
   gtDouble :: Double -> Double -> GHC.Types.Bool
@@ -7026,9 +7040,6 @@ module GHC.Float where
   logFloat :: Float -> Float
   ltDouble :: Double -> Double -> GHC.Types.Bool
   ltFloat :: Float -> Float -> GHC.Types.Bool
-  maxExpt :: GHC.Types.Int
-  maxExpt10 :: GHC.Types.Int
-  minExpt :: GHC.Types.Int
   minusDouble :: Double -> Double -> Double
   minusFloat :: Float -> Float -> Float
   naturalToDouble# :: GHC.Num.Natural.Natural -> Double#
@@ -7037,8 +7048,6 @@ module GHC.Float where
   negateFloat :: Float -> Float
   plusDouble :: Double -> Double -> Double
   plusFloat :: Float -> Float -> Float
-  powerDouble :: Double -> Double -> Double
-  powerFloat :: Float -> Float -> Float
   properFractionDouble :: forall b. GHC.Real.Integral b => Double -> (b, Double)
   properFractionFloat :: forall b. GHC.Real.Integral b => Float -> (b, Float)
   rationalToDouble :: GHC.Num.Integer.Integer -> GHC.Num.Integer.Integer -> Double
@@ -7055,10 +7064,6 @@ module GHC.Float where
   sinhFloat :: Float -> Float
   sqrtDouble :: Double -> Double
   sqrtFloat :: Float -> Float
-  stgDoubleToWord64 :: Double# -> GHC.Prim.Word64#
-  stgFloatToWord32 :: Float# -> GHC.Prim.Word32#
-  stgWord32ToFloat :: GHC.Prim.Word32# -> Float#
-  stgWord64ToDouble :: GHC.Prim.Word64# -> Double#
   tanDouble :: Double -> Double
   tanFloat :: Float -> Float
   tanhDouble :: Double -> Double
@@ -7066,7 +7071,6 @@ module GHC.Float where
   timesDouble :: Double -> Double -> Double
   timesFloat :: Float -> Float -> Float
   truncateDouble :: forall b. GHC.Real.Integral b => Double -> b
-  truncateFloat :: forall b. GHC.Real.Integral b => Float -> b
   word2Double :: GHC.Types.Word -> Double
   word2Float :: GHC.Types.Word -> Float
 
@@ -11780,8 +11784,6 @@ module GHC.Real where
     recip :: a -> a
     fromRational :: Rational -> a
     {-# MINIMAL fromRational, (recip | (/)) #-}
-  type FractionalExponentBase :: *
-  data FractionalExponentBase = Base2 | Base10
   type Integral :: * -> Constraint
   class (Real a, GHC.Enum.Enum a) => Integral a where
     quot :: a -> a -> a
@@ -11809,9 +11811,7 @@ module GHC.Real where
     floor :: forall b. Integral b => a -> b
     {-# MINIMAL properFraction #-}
   (^) :: forall a b. (GHC.Num.Num a, Integral b) => a -> b -> a
-  (^%^) :: forall a. Integral a => Rational -> a -> Rational
   (^^) :: forall a b. (Fractional a, Integral b) => a -> b -> a
-  (^^%^^) :: forall a. Integral a => Rational -> a -> Rational
   denominator :: forall a. Ratio a -> a
   divZeroError :: forall a. a
   even :: forall a. Integral a => a -> GHC.Types.Bool
@@ -11825,7 +11825,6 @@ module GHC.Real where
   lcm :: forall a. Integral a => a -> a -> a
   mkRationalBase10 :: Rational -> GHC.Num.Integer.Integer -> Rational
   mkRationalBase2 :: Rational -> GHC.Num.Integer.Integer -> Rational
-  mkRationalWithExponentBase :: Rational -> GHC.Num.Integer.Integer -> FractionalExponentBase -> Rational
   notANumber :: Rational
   numerator :: forall a. Ratio a -> a
   numericEnumFrom :: forall a. Fractional a => a -> [a]
@@ -11834,8 +11833,6 @@ module GHC.Real where
   numericEnumFromTo :: forall a. (GHC.Classes.Ord a, Fractional a) => a -> a -> [a]
   odd :: forall a. Integral a => a -> GHC.Types.Bool
   overflowError :: forall a. a
-  powImpl :: forall a b. (GHC.Num.Num a, Integral b) => a -> b -> a
-  powImplAcc :: forall a b. (GHC.Num.Num a, Integral b) => a -> b -> a -> a
   ratioPrec :: GHC.Types.Int
   ratioPrec1 :: GHC.Types.Int
   ratioZeroDenominatorError :: forall a. a
@@ -14080,6 +14077,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’
@@ -14105,30 +14126,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’
@@ -14142,6 +14139,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’
@@ -14166,18 +14175,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’


=====================================
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
@@ -7148,7 +7167,6 @@ module GHC.Float where
   castWord64ToDouble :: GHC.Word.Word64 -> Double
   ceilingDouble :: forall b. GHC.Real.Integral b => Double -> b
   ceilingFloat :: forall b. GHC.Real.Integral b => Float -> b
-  clamp :: GHC.Types.Int -> GHC.Types.Int -> GHC.Types.Int
   cosDouble :: Double -> Double
   cosFloat :: Float -> Float
   coshDouble :: Double -> Double
@@ -7163,9 +7181,6 @@ module GHC.Float where
   expFloat :: Float -> Float
   expm1Double :: Double -> Double
   expm1Float :: Float -> Float
-  expt :: GHC.Num.Integer.Integer -> GHC.Types.Int -> GHC.Num.Integer.Integer
-  expts :: GHC.Arr.Array GHC.Types.Int GHC.Num.Integer.Integer
-  expts10 :: GHC.Arr.Array GHC.Types.Int GHC.Num.Integer.Integer
   fabsDouble :: Double -> Double
   fabsFloat :: Float -> Float
   float2Double :: Float -> Double
@@ -7177,7 +7192,6 @@ module GHC.Float where
   formatRealFloatAlt :: forall a. RealFloat a => FFFormat -> GHC.Maybe.Maybe GHC.Types.Int -> GHC.Types.Bool -> a -> GHC.Base.String
   fromRat :: forall a. RealFloat a => GHC.Real.Rational -> a
   fromRat' :: forall a. RealFloat a => GHC.Real.Rational -> a
-  fromRat'' :: forall a. RealFloat a => GHC.Types.Int -> GHC.Types.Int -> GHC.Num.Integer.Integer -> GHC.Num.Integer.Integer -> a
   geDouble :: Double -> Double -> GHC.Types.Bool
   geFloat :: Float -> Float -> GHC.Types.Bool
   gtDouble :: Double -> Double -> GHC.Types.Bool
@@ -7206,9 +7220,6 @@ module GHC.Float where
   logFloat :: Float -> Float
   ltDouble :: Double -> Double -> GHC.Types.Bool
   ltFloat :: Float -> Float -> GHC.Types.Bool
-  maxExpt :: GHC.Types.Int
-  maxExpt10 :: GHC.Types.Int
-  minExpt :: GHC.Types.Int
   minusDouble :: Double -> Double -> Double
   minusFloat :: Float -> Float -> Float
   naturalToDouble# :: GHC.Num.Natural.Natural -> Double#
@@ -7217,8 +7228,6 @@ module GHC.Float where
   negateFloat :: Float -> Float
   plusDouble :: Double -> Double -> Double
   plusFloat :: Float -> Float -> Float
-  powerDouble :: Double -> Double -> Double
-  powerFloat :: Float -> Float -> Float
   properFractionDouble :: forall b. GHC.Real.Integral b => Double -> (b, Double)
   properFractionFloat :: forall b. GHC.Real.Integral b => Float -> (b, Float)
   rationalToDouble :: GHC.Num.Integer.Integer -> GHC.Num.Integer.Integer -> Double
@@ -7235,10 +7244,6 @@ module GHC.Float where
   sinhFloat :: Float -> Float
   sqrtDouble :: Double -> Double
   sqrtFloat :: Float -> Float
-  stgDoubleToWord64 :: Double# -> GHC.Prim.Word64#
-  stgFloatToWord32 :: Float# -> GHC.Prim.Word32#
-  stgWord32ToFloat :: GHC.Prim.Word32# -> Float#
-  stgWord64ToDouble :: GHC.Prim.Word64# -> Double#
   tanDouble :: Double -> Double
   tanFloat :: Float -> Float
   tanhDouble :: Double -> Double
@@ -7246,7 +7251,6 @@ module GHC.Float where
   timesDouble :: Double -> Double -> Double
   timesFloat :: Float -> Float -> Float
   truncateDouble :: forall b. GHC.Real.Integral b => Double -> b
-  truncateFloat :: forall b. GHC.Real.Integral b => Float -> b
   word2Double :: GHC.Types.Word -> Double
   word2Float :: GHC.Types.Word -> Float
 
@@ -9226,8 +9230,6 @@ module GHC.Real where
     recip :: a -> a
     fromRational :: Rational -> a
     {-# MINIMAL fromRational, (recip | (/)) #-}
-  type FractionalExponentBase :: *
-  data FractionalExponentBase = Base2 | Base10
   type Integral :: * -> Constraint
   class (Real a, GHC.Enum.Enum a) => Integral a where
     quot :: a -> a -> a
@@ -9255,9 +9257,7 @@ module GHC.Real where
     floor :: forall b. Integral b => a -> b
     {-# MINIMAL properFraction #-}
   (^) :: forall a b. (GHC.Num.Num a, Integral b) => a -> b -> a
-  (^%^) :: forall a. Integral a => Rational -> a -> Rational
   (^^) :: forall a b. (Fractional a, Integral b) => a -> b -> a
-  (^^%^^) :: forall a. Integral a => Rational -> a -> Rational
   denominator :: forall a. Ratio a -> a
   divZeroError :: forall a. a
   even :: forall a. Integral a => a -> GHC.Types.Bool
@@ -9271,7 +9271,6 @@ module GHC.Real where
   lcm :: forall a. Integral a => a -> a -> a
   mkRationalBase10 :: Rational -> GHC.Num.Integer.Integer -> Rational
   mkRationalBase2 :: Rational -> GHC.Num.Integer.Integer -> Rational
-  mkRationalWithExponentBase :: Rational -> GHC.Num.Integer.Integer -> FractionalExponentBase -> Rational
   notANumber :: Rational
   numerator :: forall a. Ratio a -> a
   numericEnumFrom :: forall a. Fractional a => a -> [a]
@@ -9280,8 +9279,6 @@ module GHC.Real where
   numericEnumFromTo :: forall a. (GHC.Classes.Ord a, Fractional a) => a -> a -> [a]
   odd :: forall a. Integral a => a -> GHC.Types.Bool
   overflowError :: forall a. a
-  powImpl :: forall a b. (GHC.Num.Num a, Integral b) => a -> b -> a
-  powImplAcc :: forall a b. (GHC.Num.Num a, Integral b) => a -> b -> a -> a
   ratioPrec :: GHC.Types.Int
   ratioPrec1 :: GHC.Types.Int
   ratioZeroDenominatorError :: forall a. a
@@ -11577,6 +11574,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’
@@ -11602,30 +11623,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’
@@ -11639,6 +11636,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’
@@ -11664,18 +11673,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’


=====================================
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
@@ -6999,7 +7018,6 @@ module GHC.Float where
   castWord64ToDouble :: GHC.Word.Word64 -> Double
   ceilingDouble :: forall b. GHC.Real.Integral b => Double -> b
   ceilingFloat :: forall b. GHC.Real.Integral b => Float -> b
-  clamp :: GHC.Types.Int -> GHC.Types.Int -> GHC.Types.Int
   cosDouble :: Double -> Double
   cosFloat :: Float -> Float
   coshDouble :: Double -> Double
@@ -7014,9 +7032,6 @@ module GHC.Float where
   expFloat :: Float -> Float
   expm1Double :: Double -> Double
   expm1Float :: Float -> Float
-  expt :: GHC.Num.Integer.Integer -> GHC.Types.Int -> GHC.Num.Integer.Integer
-  expts :: GHC.Arr.Array GHC.Types.Int GHC.Num.Integer.Integer
-  expts10 :: GHC.Arr.Array GHC.Types.Int GHC.Num.Integer.Integer
   fabsDouble :: Double -> Double
   fabsFloat :: Float -> Float
   float2Double :: Float -> Double
@@ -7028,7 +7043,6 @@ module GHC.Float where
   formatRealFloatAlt :: forall a. RealFloat a => FFFormat -> GHC.Maybe.Maybe GHC.Types.Int -> GHC.Types.Bool -> a -> GHC.Base.String
   fromRat :: forall a. RealFloat a => GHC.Real.Rational -> a
   fromRat' :: forall a. RealFloat a => GHC.Real.Rational -> a
-  fromRat'' :: forall a. RealFloat a => GHC.Types.Int -> GHC.Types.Int -> GHC.Num.Integer.Integer -> GHC.Num.Integer.Integer -> a
   geDouble :: Double -> Double -> GHC.Types.Bool
   geFloat :: Float -> Float -> GHC.Types.Bool
   gtDouble :: Double -> Double -> GHC.Types.Bool
@@ -7057,9 +7071,6 @@ module GHC.Float where
   logFloat :: Float -> Float
   ltDouble :: Double -> Double -> GHC.Types.Bool
   ltFloat :: Float -> Float -> GHC.Types.Bool
-  maxExpt :: GHC.Types.Int
-  maxExpt10 :: GHC.Types.Int
-  minExpt :: GHC.Types.Int
   minusDouble :: Double -> Double -> Double
   minusFloat :: Float -> Float -> Float
   naturalToDouble# :: GHC.Num.Natural.Natural -> Double#
@@ -7068,8 +7079,6 @@ module GHC.Float where
   negateFloat :: Float -> Float
   plusDouble :: Double -> Double -> Double
   plusFloat :: Float -> Float -> Float
-  powerDouble :: Double -> Double -> Double
-  powerFloat :: Float -> Float -> Float
   properFractionDouble :: forall b. GHC.Real.Integral b => Double -> (b, Double)
   properFractionFloat :: forall b. GHC.Real.Integral b => Float -> (b, Float)
   rationalToDouble :: GHC.Num.Integer.Integer -> GHC.Num.Integer.Integer -> Double
@@ -7086,10 +7095,6 @@ module GHC.Float where
   sinhFloat :: Float -> Float
   sqrtDouble :: Double -> Double
   sqrtFloat :: Float -> Float
-  stgDoubleToWord64 :: Double# -> GHC.Prim.Word64#
-  stgFloatToWord32 :: Float# -> GHC.Prim.Word32#
-  stgWord32ToFloat :: GHC.Prim.Word32# -> Float#
-  stgWord64ToDouble :: GHC.Prim.Word64# -> Double#
   tanDouble :: Double -> Double
   tanFloat :: Float -> Float
   tanhDouble :: Double -> Double
@@ -7097,7 +7102,6 @@ module GHC.Float where
   timesDouble :: Double -> Double -> Double
   timesFloat :: Float -> Float -> Float
   truncateDouble :: forall b. GHC.Real.Integral b => Double -> b
-  truncateFloat :: forall b. GHC.Real.Integral b => Float -> b
   word2Double :: GHC.Types.Word -> Double
   word2Float :: GHC.Types.Word -> Float
 
@@ -9006,8 +9010,6 @@ module GHC.Real where
     recip :: a -> a
     fromRational :: Rational -> a
     {-# MINIMAL fromRational, (recip | (/)) #-}
-  type FractionalExponentBase :: *
-  data FractionalExponentBase = Base2 | Base10
   type Integral :: * -> Constraint
   class (Real a, GHC.Enum.Enum a) => Integral a where
     quot :: a -> a -> a
@@ -9035,9 +9037,7 @@ module GHC.Real where
     floor :: forall b. Integral b => a -> b
     {-# MINIMAL properFraction #-}
   (^) :: forall a b. (GHC.Num.Num a, Integral b) => a -> b -> a
-  (^%^) :: forall a. Integral a => Rational -> a -> Rational
   (^^) :: forall a b. (Fractional a, Integral b) => a -> b -> a
-  (^^%^^) :: forall a. Integral a => Rational -> a -> Rational
   denominator :: forall a. Ratio a -> a
   divZeroError :: forall a. a
   even :: forall a. Integral a => a -> GHC.Types.Bool
@@ -9051,7 +9051,6 @@ module GHC.Real where
   lcm :: forall a. Integral a => a -> a -> a
   mkRationalBase10 :: Rational -> GHC.Num.Integer.Integer -> Rational
   mkRationalBase2 :: Rational -> GHC.Num.Integer.Integer -> Rational
-  mkRationalWithExponentBase :: Rational -> GHC.Num.Integer.Integer -> FractionalExponentBase -> Rational
   notANumber :: Rational
   numerator :: forall a. Ratio a -> a
   numericEnumFrom :: forall a. Fractional a => a -> [a]
@@ -9060,8 +9059,6 @@ module GHC.Real where
   numericEnumFromTo :: forall a. (GHC.Classes.Ord a, Fractional a) => a -> a -> [a]
   odd :: forall a. Integral a => a -> GHC.Types.Bool
   overflowError :: forall a. a
-  powImpl :: forall a b. (GHC.Num.Num a, Integral b) => a -> b -> a
-  powImplAcc :: forall a b. (GHC.Num.Num a, Integral b) => a -> b -> a -> a
   ratioPrec :: GHC.Types.Int
   ratioPrec1 :: GHC.Types.Int
   ratioZeroDenominatorError :: forall a. a
@@ -11313,6 +11310,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’
@@ -11338,30 +11359,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’
@@ -11375,6 +11372,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’
@@ -11399,18 +11408,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’


=====================================
testsuite/tests/parser/should_compile/T23315/Makefile
=====================================
@@ -0,0 +1,18 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
+
+SETUP = ./Setup -v0
+
+T23315: clean
+	$(MAKE) clean
+	'$(TEST_HC)' $(TEST_HC_OPTS) -v0 --make Setup
+	$(SETUP) clean
+	$(SETUP) configure $(CABAL_MINIMAL_BUILD) --with-ghc='$(TEST_HC)' --ghc-options='$(TEST_HC_OPTS)'
+	$(SETUP) build 1>&2
+ifneq "$(CLEANUP)" ""
+	$(MAKE) clean
+endif
+
+clean :
+	$(RM) -r */dist Setup$(exeext) *.o *.hi


=====================================
testsuite/tests/parser/should_compile/T23315/Setup.hs
=====================================
@@ -0,0 +1,2 @@
+import Distribution.Simple
+main = defaultMain
\ No newline at end of file


=====================================
testsuite/tests/parser/should_compile/T23315/T23315.cabal
=====================================
@@ -0,0 +1,10 @@
+name:                T23315
+version:             0.1.0.0
+build-type:          Simple
+cabal-version:       2.0
+
+library
+  signatures:          T23315
+  build-depends:       base >= 4.3 && < 5
+  default-language:    Haskell2010
+  ghc-options:         -Wall -haddock -ddump-parsed-ast


=====================================
testsuite/tests/parser/should_compile/T23315/T23315.hsig
=====================================
@@ -0,0 +1,4 @@
+signature T23315 where
+-- | My unit
+a :: ()
+-- ^ More docs


=====================================
testsuite/tests/parser/should_compile/T23315/T23315.stderr
=====================================
@@ -0,0 +1,112 @@
+
+==================== Parser AST ====================
+
+(L
+ { T23315.hsig:1:1 }
+ (HsModule
+  (XModulePs
+   (EpAnn
+    (Anchor
+     { T23315.hsig:1:1 }
+     (UnchangedAnchor))
+    (AnnsModule
+     [(AddEpAnn AnnSignature (EpaSpan { T23315.hsig:1:1-9 }))
+     ,(AddEpAnn AnnWhere (EpaSpan { T23315.hsig:1:18-22 }))]
+      []
+     (Nothing))
+    (EpaComments
+     []))
+   (VirtualBraces
+    (1))
+   (Nothing)
+   (Nothing))
+  (Just
+   (L
+    (SrcSpanAnn (EpAnnNotUsed) { T23315.hsig:1:11-16 })
+    {ModuleName: T23315}))
+  (Nothing)
+  []
+  [(L
+    (SrcSpanAnn (EpAnnNotUsed) { T23315.hsig:2:1-12 })
+    (DocD
+     (NoExtField)
+     (DocCommentNext
+      (L
+       { T23315.hsig:2:1-12 }
+       (WithHsDocIdentifiers
+        (MultiLineDocString
+         (HsDocStringNext)
+         (:|
+          (L
+           { T23315.hsig:2:5-12 }
+           (HsDocStringChunk
+            " My unit"))
+          []))
+        [])))))
+  ,(L
+    (SrcSpanAnn (EpAnn
+                 (Anchor
+                  { T23315.hsig:3:1-7 }
+                  (UnchangedAnchor))
+                 (AnnListItem
+                  [])
+                 (EpaComments
+                  [])) { T23315.hsig:3:1-7 })
+    (SigD
+     (NoExtField)
+     (TypeSig
+      (EpAnn
+       (Anchor
+        { T23315.hsig:3:1 }
+        (UnchangedAnchor))
+       (AnnSig
+        (AddEpAnn AnnDcolon (EpaSpan { T23315.hsig:3:3-4 }))
+        [])
+       (EpaComments
+        []))
+      [(L
+        (SrcSpanAnn (EpAnnNotUsed) { T23315.hsig:3:1 })
+        (Unqual
+         {OccName: a}))]
+      (HsWC
+       (NoExtField)
+       (L
+        (SrcSpanAnn (EpAnnNotUsed) { T23315.hsig:3:6-7 })
+        (HsSig
+         (NoExtField)
+         (HsOuterImplicit
+          (NoExtField))
+         (L
+          (SrcSpanAnn (EpAnnNotUsed) { T23315.hsig:3:6-7 })
+          (HsTupleTy
+           (EpAnn
+            (Anchor
+             { T23315.hsig:3:6 }
+             (UnchangedAnchor))
+            (AnnParen
+             (AnnParens)
+             (EpaSpan { T23315.hsig:3:6 })
+             (EpaSpan { T23315.hsig:3:7 }))
+            (EpaComments
+             []))
+           (HsBoxedOrConstraintTuple)
+           []))))))))
+  ,(L
+    (SrcSpanAnn (EpAnnNotUsed) { T23315.hsig:4:1-14 })
+    (DocD
+     (NoExtField)
+     (DocCommentPrev
+      (L
+       { T23315.hsig:4:1-14 }
+       (WithHsDocIdentifiers
+        (MultiLineDocString
+         (HsDocStringPrevious)
+         (:|
+          (L
+           { T23315.hsig:4:5-14 }
+           (HsDocStringChunk
+            " More docs"))
+          []))
+        [])))))]))
+
+


=====================================
testsuite/tests/parser/should_compile/T23315/all.T
=====================================
@@ -0,0 +1,3 @@
+test('T23315',
+     [extra_files(['Setup.hs']), js_broken(22352)],
+     makefile_test, [])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9be9b7e4d03c3de7bcb81597ac2a0fb93a58c040...dd16a902160a42d293c4399291bc5ab372dc3117

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9be9b7e4d03c3de7bcb81597ac2a0fb93a58c040...dd16a902160a42d293c4399291bc5ab372dc3117
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230721/23c5f650/attachment-0001.html>


More information about the ghc-commits mailing list