[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 2 commits: base: don't expose GHC.Num.{BigNat, Integer, Natural}
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 01be89c2 by Teo Camarasu at 2026-01-19T15:06:30-05:00 base: don't expose GHC.Num.{BigNat, Integer, Natural} We no longer expose GHC.Num.{BigNat, Integer, Natural} from base instead users should get these modules from ghc-bignum. We make this change to insulate end users from changes to GHC's implementation of big numbers. Implements CLC proposal 359: https://github.com/haskell/core-libraries-committee/issues/359 - - - - - 34564f82 by Teo Camarasu at 2026-01-19T15:06:31-05:00 base: deprecate GHC internals in GHC.Num Implements CLC proposal: https://github.com/haskell/core-libraries-committee/issues/360 - - - - - 14 changed files: - libraries/base/base.cabal.in - libraries/base/changelog.md - libraries/base/src/Data/Array/Byte.hs - libraries/base/src/GHC/Num.hs - − libraries/base/src/GHC/Num/BigNat.hs - − libraries/base/src/GHC/Num/Integer.hs - − libraries/base/src/GHC/Num/Natural.hs - libraries/base/src/System/CPUTime/Utils.hs - libraries/ghc-bignum/ghc-bignum.cabal - libraries/ghc-experimental/src/GHC/TypeNats/Experimental.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 Changes: ===================================== libraries/base/base.cabal.in ===================================== @@ -219,9 +219,6 @@ Library , GHC.MVar , GHC.Natural , GHC.Num - , GHC.Num.Integer - , GHC.Num.Natural - , GHC.Num.BigNat , GHC.OldList , GHC.OverloadedLabels , GHC.Profiling ===================================== libraries/base/changelog.md ===================================== @@ -13,8 +13,10 @@ * Add `thenA` and `thenM`. ([CLC proposal #351](https://github.com/haskell/core-libraries-committee/issues/351)) * Fix bug where `naturalAndNot` was incorrectly truncating results ([CLC proposal #350](github.com/haskell/core-libraries-committee/issues/350)) * generalize `deleteBy` and `deleteFirstsBy` ([CLC proposal 372](https://github.com/haskell/core-libraries-committee/issues/372)) + * GHC.Num.{BigNat, Integer, Natural} are no longer exposed. Users should import them from `ghc-bignum` instead. ([CLC proposal #359](github.com/haskell/core-libraries-committee/issues/359)) * Remove extra laziness from `Data.Bifunctor.Bifunctor` instances for all tuples to have the same laziness as their `Data.Functor.Functor` counterparts (i.e. they became more strict than before) ([CLC proposal #339](https://github.com/haskell/core-libraries-committee/issues/339)) * Adjust the strictness of `Data.List.iterate'` to be more reasonable: every element of the output list is forced to WHNF when the `(:)` containing it is forced. ([CLC proposal #335)](https://github.com/haskell/core-libraries-committee/issues/335) + * GHC internals in `GHC.Num` have been deprecated and will be removed after one major release. ((CLC proposal #360)[https://github.com/haskell/core-libraries-committee/issues/360]) * Add `nubOrd` / `nubOrdBy` to `Data.List` and `Data.List.NonEmpty`. ([CLC proposal #336](https://github.com/haskell/core-libraries-committee/issues/336)) * Add `Semigroup` and `Monoid` instances for `Control.Monad.ST.Lazy`. ([CLC proposal #374](https://github.com/haskell/core-libraries-committee/issues/374)) * `GHC.Conc.throwSTM` and `GHC.Conc.Sync.throwSTM` now carry a `HasCallStack` constraint and attach a `Backtrace` annotation to the thrown exception. ([GHC #25365](https://gitlab.haskell.org/ghc/ghc/-/issues/25365)) ===================================== libraries/base/src/Data/Array/Byte.hs ===================================== @@ -27,7 +27,7 @@ import qualified GHC.Internal.Data.Foldable as F import GHC.Internal.Data.Maybe (fromMaybe) import Data.Semigroup import GHC.Internal.Exts -import GHC.Num.Integer (Integer(..)) +import GHC.Internal.Bignum.Integer (Integer(..)) import GHC.Internal.Show (intToDigit) import GHC.Internal.ST (ST(..), runST) import GHC.Internal.Word (Word8(..)) ===================================== libraries/base/src/GHC/Num.hs ===================================== @@ -1,5 +1,7 @@ {-# LANGUAGE MagicHash #-} {-# OPTIONS_HADDOCK not-home #-} +-- don't warn that some but not all of Integer and Natural are deprecated +{-# OPTIONS_GHC -Wno-incomplete-export-warnings -Wno-duplicate-exports #-} -- | -- Module : GHC.Num @@ -15,191 +17,370 @@ module GHC.Num ( Num(..) + , Integer + , Natural , subtract , quotRemInteger - , integerFromNatural - , integerToNaturalClamp - , integerToNaturalThrow - , integerToNatural - , integerToWord# - , integerToInt# - , integerToWord64# - , integerToInt64# - , integerAdd - , integerMul - , integerSub - , integerNegate - , integerAbs - , integerPopCount# - , integerQuot - , integerRem - , integerDiv - , integerMod - , integerDivMod# - , integerQuotRem# - , integerEncodeFloat# - , integerEncodeDouble# - , integerGcd - , integerLcm - , integerAnd - , integerOr - , integerXor - , integerComplement - , integerBit# - , integerTestBit# - , integerShiftL# - , integerShiftR# - , integerFromWord# - , integerFromWord64# - , integerFromInt64# - , Integer(..) - , integerBit - , integerCheck - , integerCheck# - , integerCompare - , integerDecodeDouble# - , integerDivMod - , integerEncodeDouble - , integerEq - , integerEq# - , integerFromAddr - , integerFromAddr# - , integerFromBigNat# - , integerFromBigNatNeg# - , integerFromBigNatSign# - , integerFromByteArray - , integerFromByteArray# - , integerFromInt - , integerFromInt# + , integerToWord , integerFromWord - , integerFromWordList - , integerFromWordNeg# - , integerFromWordSign# - , integerGcde - , integerGcde# - , integerGe - , integerGe# - , integerGt - , integerGt# - , integerIsNegative - , integerIsNegative# - , integerIsOne - , integerIsPowerOf2# - , integerIsZero - , integerLe - , integerLe# - , integerLog2 - , integerLog2# - , integerLogBase - , integerLogBase# - , integerLogBaseWord - , integerLogBaseWord# - , integerLt - , integerLt# - , integerNe - , integerNe# - , integerOne - , integerPowMod# - , integerQuotRem - , integerRecipMod# - , integerShiftL - , integerShiftR - , integerSignum - , integerSignum# - , integerSizeInBase# - , integerSqr - , integerTestBit - , integerToAddr - , integerToAddr# - , integerToBigNatClamp# - , integerToBigNatSign# , integerToInt - , integerToMutableByteArray - , integerToMutableByteArray# - , integerToWord - , integerZero - , naturalToWord# - , naturalPopCount# - , naturalShiftR# - , naturalShiftL# - , naturalAdd - , naturalSub - , naturalSubThrow - , naturalSubUnsafe - , naturalMul - , naturalQuotRem# - , naturalQuot - , naturalRem - , naturalAnd - , naturalAndNot - , naturalOr - , naturalXor - , naturalTestBit# - , naturalBit# - , naturalGcd - , naturalLcm - , naturalLog2# - , naturalLogBaseWord# - , naturalLogBase# - , naturalPowMod - , naturalSizeInBase# - , Natural(..) - , naturalBit - , naturalCheck - , naturalCheck# - , naturalClearBit - , naturalClearBit# - , naturalCompare - , naturalComplementBit - , naturalComplementBit# - , naturalEncodeDouble# - , naturalEncodeFloat# - , naturalEq - , naturalEq# - , naturalFromAddr - , naturalFromAddr# - , naturalFromBigNat# - , naturalFromByteArray# - , naturalFromWord - , naturalFromWord# - , naturalFromWord2# - , naturalFromWordList - , naturalGe - , naturalGe# - , naturalGt - , naturalGt# - , naturalIsOne - , naturalIsPowerOf2# - , naturalIsZero - , naturalLe - , naturalLe# - , naturalLog2 - , naturalLogBase - , naturalLogBaseWord - , naturalLt - , naturalLt# - , naturalNe - , naturalNe# - , naturalNegate - , naturalOne - , naturalPopCount - , naturalQuotRem - , naturalSetBit - , naturalSetBit# - , naturalShiftL - , naturalShiftR - , naturalSignum - , naturalSqr - , naturalTestBit - , naturalToAddr - , naturalToAddr# - , naturalToBigNat# - , naturalToMutableByteArray# - , naturalToWord - , naturalToWordClamp - , naturalToWordClamp# - , naturalToWordMaybe# - , naturalZero + , integerFromInt + , integerToNatural + , integerFromNatural + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + Integer(IN, IP, IS) + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + Natural(NS, NB) + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerToNaturalClamp + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerToNaturalThrow + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerToWord# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerToInt# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerToWord64# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerToInt64# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerAdd + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerMul + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerSub + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerNegate + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerAbs + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerPopCount# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerQuot + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerRem + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerDiv + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerMod + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerDivMod# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerQuotRem# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerEncodeFloat# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerEncodeDouble# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerGcd + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerLcm + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerAnd + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerOr + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerXor + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerComplement + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerBit# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerTestBit# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerShiftL# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerShiftR# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerFromWord# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerFromWord64# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerFromInt64# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerBit + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerCheck + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerCheck# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerCompare + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerDecodeDouble# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerDivMod + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerEncodeDouble + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerEq + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerEq# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerFromAddr + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerFromAddr# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerFromBigNat# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerFromBigNatNeg# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerFromBigNatSign# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerFromByteArray + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerFromByteArray# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerFromInt# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerFromWordList + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerFromWordNeg# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerFromWordSign# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerGcde + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerGcde# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerGe + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerGe# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerGt + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerGt# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerIsNegative + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerIsNegative# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerIsOne + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerIsPowerOf2# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerIsZero + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerLe + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerLe# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerLog2 + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerLog2# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerLogBase + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerLogBase# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerLogBaseWord + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerLogBaseWord# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerLt + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerLt# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerNe + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerNe# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerOne + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerPowMod# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerQuotRem + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerRecipMod# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerShiftL + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerShiftR + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerSignum + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerSignum# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerSizeInBase# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerSqr + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerTestBit + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerToAddr + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerToAddr# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerToBigNatClamp# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerToBigNatSign# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerToMutableByteArray + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerToMutableByteArray# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + integerZero + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalToWord# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalPopCount# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalShiftR# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalShiftL# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalAdd + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalSub + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalSubThrow + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalSubUnsafe + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalMul + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalQuotRem# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalQuot + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalRem + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalAnd + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalAndNot + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalOr + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalXor + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalTestBit# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalBit# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalGcd + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalLcm + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalLog2# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalLogBaseWord# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalLogBase# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalPowMod + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalSizeInBase# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalBit + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalCheck + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalCheck# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalClearBit + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalClearBit# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalCompare + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalComplementBit + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalComplementBit# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalEncodeDouble# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalEncodeFloat# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalEq + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalEq# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalFromAddr + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalFromAddr# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalFromBigNat# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalFromByteArray# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalFromWord + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalFromWord# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalFromWord2# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalFromWordList + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalGe + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalGe# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalGt + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalGt# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalIsOne + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalIsPowerOf2# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalIsZero + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalLe + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalLe# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalLog2 + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalLogBase + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalLogBaseWord + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalLt + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalLt# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalNe + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalNe# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalNegate + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalOne + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalPopCount + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalQuotRem + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalSetBit + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalSetBit# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalShiftL + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalShiftR + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalSignum + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalSqr + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalTestBit + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalToAddr + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalToAddr# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalToBigNat# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalToMutableByteArray# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalToWord + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalToWordClamp + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalToWordClamp# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalToWordMaybe# + , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-} + naturalZero ) where ===================================== libraries/base/src/GHC/Num/BigNat.hs deleted ===================================== @@ -1,6 +0,0 @@ -module GHC.Num.BigNat - ( module GHC.Internal.Bignum.BigNat - ) -where - -import GHC.Internal.Bignum.BigNat ===================================== libraries/base/src/GHC/Num/Integer.hs deleted ===================================== @@ -1,6 +0,0 @@ -module GHC.Num.Integer - ( module GHC.Internal.Bignum.Integer - ) -where - -import GHC.Internal.Bignum.Integer ===================================== libraries/base/src/GHC/Num/Natural.hs deleted ===================================== @@ -1,6 +0,0 @@ -module GHC.Num.Natural - ( module GHC.Internal.Bignum.Natural - ) -where - -import GHC.Internal.Bignum.Natural ===================================== libraries/base/src/System/CPUTime/Utils.hs ===================================== @@ -8,7 +8,7 @@ module System.CPUTime.Utils ) where import GHC.Internal.Foreign.C.Types -import GHC.Num.Integer (Integer) +import GHC.Internal.Bignum.Integer (Integer) import GHC.Internal.Real (fromIntegral) cClockToInteger :: CClock -> Integer ===================================== libraries/ghc-bignum/ghc-bignum.cabal ===================================== @@ -10,10 +10,8 @@ bug-reports: https://gitlab.haskell.org/ghc/ghc/issues/new category: Numeric, Algebra, GHC build-type: Simple description: - This package used to provide the low-level implementation of the standard + This package provides the low-level implementation of the standard 'BigNat', 'Natural' and 'Integer' types. - Use `base:GHC.Num.{Integer,Natural,BigNat}` instead or other modules from - `ghc-internal`. extra-source-files: changelog.md @@ -40,13 +38,6 @@ library , GHC.Internal.Bignum.Backend as GHC.Num.Backend , GHC.Internal.Bignum.Backend.Selected as GHC.Num.Backend.Selected , GHC.Internal.Bignum.Backend.Native as GHC.Num.Backend.Native - -- reexport from base - -- We can't reexport these modules from ghc-internal otherwise we get - -- ambiguity between: - -- ghc-bignum:GHC.Num.X - -- base:GHC.Num.X - -- we should probably just deprecate ghc-bignum and encourage users to use - -- exports from base instead. - , GHC.Num.BigNat - , GHC.Num.Natural - , GHC.Num.Integer + , GHC.Internal.Bignum.BigNat as GHC.Num.BigNat + , GHC.Internal.Bignum.Natural as GHC.Num.Natural + , GHC.Internal.Bignum.Integer as GHC.Num.Integer ===================================== libraries/ghc-experimental/src/GHC/TypeNats/Experimental.hs ===================================== @@ -12,7 +12,7 @@ module GHC.TypeNats.Experimental ( ) where import GHC.Internal.TypeNats -import GHC.Num.Natural (naturalLog2) +import GHC.Internal.Bignum.Natural (naturalLog2) plusSNat :: SNat n -> SNat m -> SNat (n + m) plusSNat (UnsafeSNat n) (UnsafeSNat m) = UnsafeSNat (n + m) ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -8550,340 +8550,6 @@ module GHC.Num where quotRemInteger :: Integer -> Integer -> (# Integer, Integer #) subtract :: forall a. Num a => a -> a -> a -module GHC.Num.BigNat where - -- Safety: None - type BigNat :: * - data BigNat = BN# {unBigNat :: BigNat#} - type BigNat# :: GHC.Internal.Types.UnliftedType - type BigNat# = GHC.Internal.Bignum.WordArray.WordArray# - bigNatAdd :: BigNat# -> BigNat# -> BigNat# - bigNatAddWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat# - bigNatAddWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatAnd :: BigNat# -> BigNat# -> BigNat# - bigNatAndInt# :: BigNat# -> GHC.Internal.Prim.Int# -> BigNat# - bigNatAndNot :: BigNat# -> BigNat# -> BigNat# - bigNatAndNotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatAndWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatBit :: GHC.Internal.Types.Word -> BigNat# - bigNatBit# :: GHC.Internal.Prim.Word# -> BigNat# - bigNatCheck :: BigNat# -> GHC.Internal.Types.Bool - bigNatCheck# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatClearBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatCompare :: BigNat# -> BigNat# -> GHC.Internal.Types.Ordering - bigNatCompareWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Ordering - bigNatCompareWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Types.Ordering - bigNatComplementBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatCtz :: BigNat# -> GHC.Internal.Types.Word - bigNatCtz# :: BigNat# -> GHC.Internal.Prim.Word# - bigNatCtzWord :: BigNat# -> GHC.Internal.Types.Word - bigNatCtzWord# :: BigNat# -> GHC.Internal.Prim.Word# - bigNatEncodeDouble# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double# - bigNatEq :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool - bigNatEq# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatEqWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatFromAbsInt# :: GHC.Internal.Prim.Int# -> BigNat# - bigNatFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) - bigNatFromAddrBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) - bigNatFromAddrLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) - bigNatFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) - bigNatFromByteArrayBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) - bigNatFromByteArrayLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) - bigNatFromWord :: GHC.Internal.Types.Word -> BigNat# - bigNatFromWord# :: GHC.Internal.Prim.Word# -> BigNat# - bigNatFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatFromWord64# :: GHC.Internal.Prim.Word64# -> BigNat# - bigNatFromWordArray :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat - bigNatFromWordArray# :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatFromWordList :: [GHC.Internal.Types.Word] -> BigNat# - bigNatFromWordList# :: [GHC.Internal.Types.Word] -> GHC.Internal.Bignum.WordArray.WordArray# - bigNatFromWordListUnsafe :: [GHC.Internal.Types.Word] -> BigNat# - bigNatGcd :: BigNat# -> BigNat# -> BigNat# - bigNatGcdWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# - bigNatGe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool - bigNatGe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatGt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool - bigNatGt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatGtWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool - bigNatGtWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatIndex :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Types.Word - bigNatIndex# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word# - bigNatIsOne :: BigNat# -> GHC.Internal.Types.Bool - bigNatIsOne# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatIsPowerOf2# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #) - bigNatIsTwo :: BigNat# -> GHC.Internal.Types.Bool - bigNatIsTwo# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatIsZero :: BigNat# -> GHC.Internal.Types.Bool - bigNatIsZero# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatLcm :: BigNat# -> BigNat# -> BigNat# - bigNatLcmWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatLcmWordWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatLe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool - bigNatLe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatLeWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool - bigNatLeWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatLog2 :: BigNat# -> GHC.Internal.Types.Word - bigNatLog2# :: BigNat# -> GHC.Internal.Prim.Word# - bigNatLogBase :: BigNat# -> BigNat# -> GHC.Internal.Types.Word - bigNatLogBase# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word# - bigNatLogBaseWord :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word - bigNatLogBaseWord# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word# - bigNatLt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool - bigNatLt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatMul :: BigNat# -> BigNat# -> BigNat# - bigNatMulWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat# - bigNatMulWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatNe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool - bigNatNe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatOne :: BigNat - bigNatOne# :: (# #) -> BigNat# - bigNatOr :: BigNat# -> BigNat# -> BigNat# - bigNatOrWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatPopCount :: BigNat# -> GHC.Internal.Types.Word - bigNatPopCount# :: BigNat# -> GHC.Internal.Prim.Word# - bigNatPowMod :: BigNat# -> BigNat# -> BigNat# -> BigNat# - bigNatPowModWord# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# - bigNatQuot :: BigNat# -> BigNat# -> BigNat# - bigNatQuotRem# :: BigNat# -> BigNat# -> (# BigNat#, BigNat# #) - bigNatQuotRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# BigNat#, GHC.Internal.Prim.Word# #) - bigNatQuotWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat# - bigNatQuotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatRem :: BigNat# -> BigNat# -> BigNat# - bigNatRemWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word - bigNatRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# - bigNatSetBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatShiftL :: BigNat# -> GHC.Internal.Types.Word -> BigNat# - bigNatShiftL# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatShiftR :: BigNat# -> GHC.Internal.Types.Word -> BigNat# - bigNatShiftR# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatShiftRNeg# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatSize :: BigNat# -> GHC.Internal.Types.Word - bigNatSize# :: BigNat# -> GHC.Internal.Prim.Int# - bigNatSizeInBase :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word - bigNatSizeInBase# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word# - bigNatSqr :: BigNat# -> BigNat# - bigNatSub :: BigNat# -> BigNat# -> (# (# #) | BigNat# #) - bigNatSubUnsafe :: BigNat# -> BigNat# -> BigNat# - bigNatSubWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# (# #) | BigNat# #) - bigNatSubWordUnsafe :: BigNat# -> GHC.Internal.Types.Word -> BigNat# - bigNatSubWordUnsafe# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatTestBit :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool - bigNatTestBit# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatToAddr :: BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word - bigNatToAddr# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - bigNatToAddrBE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - bigNatToAddrLE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - bigNatToInt :: BigNat# -> GHC.Internal.Types.Int - bigNatToInt# :: BigNat# -> GHC.Internal.Prim.Int# - bigNatToMutableByteArray# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - bigNatToMutableByteArrayBE# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - bigNatToMutableByteArrayLE# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - bigNatToWord :: BigNat# -> GHC.Internal.Types.Word - bigNatToWord# :: BigNat# -> GHC.Internal.Prim.Word# - bigNatToWord64# :: BigNat# -> GHC.Internal.Prim.Word64# - bigNatToWordList :: BigNat# -> [GHC.Internal.Types.Word] - bigNatToWordMaybe# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #) - bigNatXor :: BigNat# -> BigNat# -> BigNat# - bigNatXorWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatZero :: BigNat - bigNatZero# :: (# #) -> BigNat# - gcdInt :: GHC.Internal.Types.Int -> GHC.Internal.Types.Int -> GHC.Internal.Types.Int - gcdInt# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# - gcdWord :: GHC.Internal.Types.Word -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word - gcdWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# - powModWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# - raiseDivZero_BigNat :: (# #) -> BigNat# - -module GHC.Num.Integer where - -- Safety: None - type Integer :: * - data Integer = IS GHC.Internal.Prim.Int# | IP GHC.Internal.Prim.ByteArray# | IN GHC.Internal.Prim.ByteArray# - integerAbs :: Integer -> Integer - integerAdd :: Integer -> Integer -> Integer - integerAnd :: Integer -> Integer -> Integer - integerBit :: GHC.Internal.Types.Word -> Integer - integerBit# :: GHC.Internal.Prim.Word# -> Integer - integerCheck :: Integer -> GHC.Internal.Types.Bool - integerCheck# :: Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerCompare :: Integer -> Integer -> GHC.Internal.Types.Ordering - integerComplement :: Integer -> Integer - integerDecodeDouble# :: GHC.Internal.Prim.Double# -> (# Integer, GHC.Internal.Prim.Int# #) - integerDiv :: Integer -> Integer -> Integer - integerDivMod :: Integer -> Integer -> (Integer, Integer) - integerDivMod# :: Integer -> Integer -> (# Integer, Integer #) - integerEncodeDouble :: Integer -> GHC.Internal.Types.Int -> GHC.Internal.Types.Double - integerEncodeDouble# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double# - integerEncodeFloat# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float# - integerEq :: Integer -> Integer -> GHC.Internal.Types.Bool - integerEq# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Integer - integerFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Integer #) - integerFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer - integerFromBigNatNeg# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer - integerFromBigNatSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Bignum.BigNat.BigNat# -> Integer - integerFromByteArray :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> Integer - integerFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Integer #) - integerFromInt :: GHC.Internal.Types.Int -> Integer - integerFromInt# :: GHC.Internal.Prim.Int# -> Integer - integerFromInt64# :: GHC.Internal.Prim.Int64# -> Integer - integerFromNatural :: GHC.Internal.Bignum.Natural.Natural -> Integer - integerFromWord :: GHC.Internal.Types.Word -> Integer - integerFromWord# :: GHC.Internal.Prim.Word# -> Integer - integerFromWord64# :: GHC.Internal.Prim.Word64# -> Integer - integerFromWordList :: GHC.Internal.Types.Bool -> [GHC.Internal.Types.Word] -> Integer - integerFromWordNeg# :: GHC.Internal.Prim.Word# -> Integer - integerFromWordSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word# -> Integer - integerGcd :: Integer -> Integer -> Integer - integerGcde :: Integer -> Integer -> (Integer, Integer, Integer) - integerGcde# :: Integer -> Integer -> (# Integer, Integer, Integer #) - integerGe :: Integer -> Integer -> GHC.Internal.Types.Bool - integerGe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerGt :: Integer -> Integer -> GHC.Internal.Types.Bool - integerGt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerIsNegative :: Integer -> GHC.Internal.Types.Bool - integerIsNegative# :: Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerIsOne :: Integer -> GHC.Internal.Types.Bool - integerIsPowerOf2# :: Integer -> (# (# #) | GHC.Internal.Prim.Word# #) - integerIsZero :: Integer -> GHC.Internal.Types.Bool - integerLcm :: Integer -> Integer -> Integer - integerLe :: Integer -> Integer -> GHC.Internal.Types.Bool - integerLe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerLog2 :: Integer -> GHC.Internal.Types.Word - integerLog2# :: Integer -> GHC.Internal.Prim.Word# - integerLogBase :: Integer -> Integer -> GHC.Internal.Types.Word - integerLogBase# :: Integer -> Integer -> GHC.Internal.Prim.Word# - integerLogBaseWord :: GHC.Internal.Types.Word -> Integer -> GHC.Internal.Types.Word - integerLogBaseWord# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word# - integerLt :: Integer -> Integer -> GHC.Internal.Types.Bool - integerLt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerMod :: Integer -> Integer -> Integer - integerMul :: Integer -> Integer -> Integer - integerNe :: Integer -> Integer -> GHC.Internal.Types.Bool - integerNe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerNegate :: Integer -> Integer - integerOne :: Integer - integerOr :: Integer -> Integer -> Integer - integerPopCount# :: Integer -> GHC.Internal.Prim.Int# - integerPowMod# :: Integer -> Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #) - integerQuot :: Integer -> Integer -> Integer - integerQuotRem :: Integer -> Integer -> (Integer, Integer) - integerQuotRem# :: Integer -> Integer -> (# Integer, Integer #) - integerRecipMod# :: Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #) - integerRem :: Integer -> Integer -> Integer - integerShiftL :: Integer -> GHC.Internal.Types.Word -> Integer - integerShiftL# :: Integer -> GHC.Internal.Prim.Word# -> Integer - integerShiftR :: Integer -> GHC.Internal.Types.Word -> Integer - integerShiftR# :: Integer -> GHC.Internal.Prim.Word# -> Integer - integerSignum :: Integer -> Integer - integerSignum# :: Integer -> GHC.Internal.Prim.Int# - integerSizeInBase# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word# - integerSqr :: Integer -> Integer - integerSub :: Integer -> Integer -> Integer - integerTestBit :: Integer -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool - integerTestBit# :: Integer -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# - integerToAddr :: Integer -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word - integerToAddr# :: forall s. Integer -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - integerToBigNatClamp# :: Integer -> GHC.Internal.Bignum.BigNat.BigNat# - integerToBigNatSign# :: Integer -> (# GHC.Internal.Prim.Int#, GHC.Internal.Bignum.BigNat.BigNat# #) - integerToInt :: Integer -> GHC.Internal.Types.Int - integerToInt# :: Integer -> GHC.Internal.Prim.Int# - integerToInt64# :: Integer -> GHC.Internal.Prim.Int64# - integerToMutableByteArray :: Integer -> GHC.Internal.Prim.MutableByteArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word - integerToMutableByteArray# :: forall s. Integer -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - integerToNatural :: Integer -> GHC.Internal.Bignum.Natural.Natural - integerToNaturalClamp :: Integer -> GHC.Internal.Bignum.Natural.Natural - integerToNaturalThrow :: Integer -> GHC.Internal.Bignum.Natural.Natural - integerToWord :: Integer -> GHC.Internal.Types.Word - integerToWord# :: Integer -> GHC.Internal.Prim.Word# - integerToWord64# :: Integer -> GHC.Internal.Prim.Word64# - integerXor :: Integer -> Integer -> Integer - integerZero :: Integer - -module GHC.Num.Natural where - -- Safety: None - type Natural :: * - data Natural = NS GHC.Internal.Prim.Word# | NB GHC.Internal.Prim.ByteArray# - naturalAdd :: Natural -> Natural -> Natural - naturalAnd :: Natural -> Natural -> Natural - naturalAndNot :: Natural -> Natural -> Natural - naturalBit :: GHC.Internal.Types.Word -> Natural - naturalBit# :: GHC.Internal.Prim.Word# -> Natural - naturalCheck :: Natural -> GHC.Internal.Types.Bool - naturalCheck# :: Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalClearBit :: Natural -> GHC.Internal.Types.Word -> Natural - naturalClearBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural - naturalCompare :: Natural -> Natural -> GHC.Internal.Types.Ordering - naturalComplementBit :: Natural -> GHC.Internal.Types.Word -> Natural - naturalComplementBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural - naturalEncodeDouble# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double# - naturalEncodeFloat# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float# - naturalEq :: Natural -> Natural -> GHC.Internal.Types.Bool - naturalEq# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Natural - naturalFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Natural #) - naturalFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Natural - naturalFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Natural #) - naturalFromWord :: GHC.Internal.Types.Word -> Natural - naturalFromWord# :: GHC.Internal.Prim.Word# -> Natural - naturalFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> Natural - naturalFromWordList :: [GHC.Internal.Types.Word] -> Natural - naturalGcd :: Natural -> Natural -> Natural - naturalGe :: Natural -> Natural -> GHC.Internal.Types.Bool - naturalGe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalGt :: Natural -> Natural -> GHC.Internal.Types.Bool - naturalGt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalIsOne :: Natural -> GHC.Internal.Types.Bool - naturalIsPowerOf2# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #) - naturalIsZero :: Natural -> GHC.Internal.Types.Bool - naturalLcm :: Natural -> Natural -> Natural - naturalLe :: Natural -> Natural -> GHC.Internal.Types.Bool - naturalLe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalLog2 :: Natural -> GHC.Internal.Types.Word - naturalLog2# :: Natural -> GHC.Internal.Prim.Word# - naturalLogBase :: Natural -> Natural -> GHC.Internal.Types.Word - naturalLogBase# :: Natural -> Natural -> GHC.Internal.Prim.Word# - naturalLogBaseWord :: GHC.Internal.Types.Word -> Natural -> GHC.Internal.Types.Word - naturalLogBaseWord# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word# - naturalLt :: Natural -> Natural -> GHC.Internal.Types.Bool - naturalLt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalMul :: Natural -> Natural -> Natural - naturalNe :: Natural -> Natural -> GHC.Internal.Types.Bool - naturalNe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalNegate :: Natural -> Natural - naturalOne :: Natural - naturalOr :: Natural -> Natural -> Natural - naturalPopCount :: Natural -> GHC.Internal.Types.Word - naturalPopCount# :: Natural -> GHC.Internal.Prim.Word# - naturalPowMod :: Natural -> Natural -> Natural -> Natural - naturalQuot :: Natural -> Natural -> Natural - naturalQuotRem :: Natural -> Natural -> (Natural, Natural) - naturalQuotRem# :: Natural -> Natural -> (# Natural, Natural #) - naturalRem :: Natural -> Natural -> Natural - naturalSetBit :: Natural -> GHC.Internal.Types.Word -> Natural - naturalSetBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural - naturalShiftL :: Natural -> GHC.Internal.Types.Word -> Natural - naturalShiftL# :: Natural -> GHC.Internal.Prim.Word# -> Natural - naturalShiftR :: Natural -> GHC.Internal.Types.Word -> Natural - naturalShiftR# :: Natural -> GHC.Internal.Prim.Word# -> Natural - naturalSignum :: Natural -> Natural - naturalSizeInBase# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word# - naturalSqr :: Natural -> Natural - naturalSub :: Natural -> Natural -> (# (# #) | Natural #) - naturalSubThrow :: Natural -> Natural -> Natural - naturalSubUnsafe :: Natural -> Natural -> Natural - naturalTestBit :: Natural -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool - naturalTestBit# :: Natural -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# - naturalToAddr :: Natural -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word - naturalToAddr# :: forall s. Natural -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - naturalToBigNat# :: Natural -> GHC.Internal.Bignum.BigNat.BigNat# - naturalToMutableByteArray# :: forall s. Natural -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - naturalToWord :: Natural -> GHC.Internal.Types.Word - naturalToWord# :: Natural -> GHC.Internal.Prim.Word# - naturalToWordClamp :: Natural -> GHC.Internal.Types.Word - naturalToWordClamp# :: Natural -> GHC.Internal.Prim.Word# - naturalToWordMaybe# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #) - naturalXor :: Natural -> Natural -> Natural - naturalZero :: Natural - module GHC.OldList where -- Safety: Safe (!!) :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> GHC.Internal.Types.Int -> a ===================================== testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs ===================================== @@ -8588,340 +8588,6 @@ module GHC.Num where quotRemInteger :: Integer -> Integer -> (# Integer, Integer #) subtract :: forall a. Num a => a -> a -> a -module GHC.Num.BigNat where - -- Safety: None - type BigNat :: * - data BigNat = BN# {unBigNat :: BigNat#} - type BigNat# :: GHC.Internal.Types.UnliftedType - type BigNat# = GHC.Internal.Bignum.WordArray.WordArray# - bigNatAdd :: BigNat# -> BigNat# -> BigNat# - bigNatAddWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat# - bigNatAddWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatAnd :: BigNat# -> BigNat# -> BigNat# - bigNatAndInt# :: BigNat# -> GHC.Internal.Prim.Int# -> BigNat# - bigNatAndNot :: BigNat# -> BigNat# -> BigNat# - bigNatAndNotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatAndWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatBit :: GHC.Internal.Types.Word -> BigNat# - bigNatBit# :: GHC.Internal.Prim.Word# -> BigNat# - bigNatCheck :: BigNat# -> GHC.Internal.Types.Bool - bigNatCheck# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatClearBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatCompare :: BigNat# -> BigNat# -> GHC.Internal.Types.Ordering - bigNatCompareWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Ordering - bigNatCompareWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Types.Ordering - bigNatComplementBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatCtz :: BigNat# -> GHC.Internal.Types.Word - bigNatCtz# :: BigNat# -> GHC.Internal.Prim.Word# - bigNatCtzWord :: BigNat# -> GHC.Internal.Types.Word - bigNatCtzWord# :: BigNat# -> GHC.Internal.Prim.Word# - bigNatEncodeDouble# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double# - bigNatEq :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool - bigNatEq# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatEqWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatFromAbsInt# :: GHC.Internal.Prim.Int# -> BigNat# - bigNatFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) - bigNatFromAddrBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) - bigNatFromAddrLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) - bigNatFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) - bigNatFromByteArrayBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) - bigNatFromByteArrayLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) - bigNatFromWord :: GHC.Internal.Types.Word -> BigNat# - bigNatFromWord# :: GHC.Internal.Prim.Word# -> BigNat# - bigNatFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatFromWord64# :: GHC.Internal.Prim.Word64# -> BigNat# - bigNatFromWordArray :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat - bigNatFromWordArray# :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatFromWordList :: [GHC.Internal.Types.Word] -> BigNat# - bigNatFromWordList# :: [GHC.Internal.Types.Word] -> GHC.Internal.Bignum.WordArray.WordArray# - bigNatFromWordListUnsafe :: [GHC.Internal.Types.Word] -> BigNat# - bigNatGcd :: BigNat# -> BigNat# -> BigNat# - bigNatGcdWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# - bigNatGe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool - bigNatGe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatGt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool - bigNatGt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatGtWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool - bigNatGtWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatIndex :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Types.Word - bigNatIndex# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word# - bigNatIsOne :: BigNat# -> GHC.Internal.Types.Bool - bigNatIsOne# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatIsPowerOf2# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #) - bigNatIsTwo :: BigNat# -> GHC.Internal.Types.Bool - bigNatIsTwo# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatIsZero :: BigNat# -> GHC.Internal.Types.Bool - bigNatIsZero# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatLcm :: BigNat# -> BigNat# -> BigNat# - bigNatLcmWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatLcmWordWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatLe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool - bigNatLe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatLeWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool - bigNatLeWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatLog2 :: BigNat# -> GHC.Internal.Types.Word - bigNatLog2# :: BigNat# -> GHC.Internal.Prim.Word# - bigNatLogBase :: BigNat# -> BigNat# -> GHC.Internal.Types.Word - bigNatLogBase# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word# - bigNatLogBaseWord :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word - bigNatLogBaseWord# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word# - bigNatLt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool - bigNatLt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatMul :: BigNat# -> BigNat# -> BigNat# - bigNatMulWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat# - bigNatMulWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatNe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool - bigNatNe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatOne :: BigNat - bigNatOne# :: (# #) -> BigNat# - bigNatOr :: BigNat# -> BigNat# -> BigNat# - bigNatOrWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatPopCount :: BigNat# -> GHC.Internal.Types.Word - bigNatPopCount# :: BigNat# -> GHC.Internal.Prim.Word# - bigNatPowMod :: BigNat# -> BigNat# -> BigNat# -> BigNat# - bigNatPowModWord# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# - bigNatQuot :: BigNat# -> BigNat# -> BigNat# - bigNatQuotRem# :: BigNat# -> BigNat# -> (# BigNat#, BigNat# #) - bigNatQuotRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# BigNat#, GHC.Internal.Prim.Word# #) - bigNatQuotWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat# - bigNatQuotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatRem :: BigNat# -> BigNat# -> BigNat# - bigNatRemWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word - bigNatRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# - bigNatSetBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatShiftL :: BigNat# -> GHC.Internal.Types.Word -> BigNat# - bigNatShiftL# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatShiftR :: BigNat# -> GHC.Internal.Types.Word -> BigNat# - bigNatShiftR# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatShiftRNeg# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatSize :: BigNat# -> GHC.Internal.Types.Word - bigNatSize# :: BigNat# -> GHC.Internal.Prim.Int# - bigNatSizeInBase :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word - bigNatSizeInBase# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word# - bigNatSqr :: BigNat# -> BigNat# - bigNatSub :: BigNat# -> BigNat# -> (# (# #) | BigNat# #) - bigNatSubUnsafe :: BigNat# -> BigNat# -> BigNat# - bigNatSubWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# (# #) | BigNat# #) - bigNatSubWordUnsafe :: BigNat# -> GHC.Internal.Types.Word -> BigNat# - bigNatSubWordUnsafe# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatTestBit :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool - bigNatTestBit# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatToAddr :: BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word - bigNatToAddr# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - bigNatToAddrBE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - bigNatToAddrLE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - bigNatToInt :: BigNat# -> GHC.Internal.Types.Int - bigNatToInt# :: BigNat# -> GHC.Internal.Prim.Int# - bigNatToMutableByteArray# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - bigNatToMutableByteArrayBE# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - bigNatToMutableByteArrayLE# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - bigNatToWord :: BigNat# -> GHC.Internal.Types.Word - bigNatToWord# :: BigNat# -> GHC.Internal.Prim.Word# - bigNatToWord64# :: BigNat# -> GHC.Internal.Prim.Word64# - bigNatToWordList :: BigNat# -> [GHC.Internal.Types.Word] - bigNatToWordMaybe# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #) - bigNatXor :: BigNat# -> BigNat# -> BigNat# - bigNatXorWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatZero :: BigNat - bigNatZero# :: (# #) -> BigNat# - gcdInt :: GHC.Internal.Types.Int -> GHC.Internal.Types.Int -> GHC.Internal.Types.Int - gcdInt# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# - gcdWord :: GHC.Internal.Types.Word -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word - gcdWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# - powModWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# - raiseDivZero_BigNat :: (# #) -> BigNat# - -module GHC.Num.Integer where - -- Safety: None - type Integer :: * - data Integer = IS GHC.Internal.Prim.Int# | IP GHC.Internal.Prim.ByteArray# | IN GHC.Internal.Prim.ByteArray# - integerAbs :: Integer -> Integer - integerAdd :: Integer -> Integer -> Integer - integerAnd :: Integer -> Integer -> Integer - integerBit :: GHC.Internal.Types.Word -> Integer - integerBit# :: GHC.Internal.Prim.Word# -> Integer - integerCheck :: Integer -> GHC.Internal.Types.Bool - integerCheck# :: Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerCompare :: Integer -> Integer -> GHC.Internal.Types.Ordering - integerComplement :: Integer -> Integer - integerDecodeDouble# :: GHC.Internal.Prim.Double# -> (# Integer, GHC.Internal.Prim.Int# #) - integerDiv :: Integer -> Integer -> Integer - integerDivMod :: Integer -> Integer -> (Integer, Integer) - integerDivMod# :: Integer -> Integer -> (# Integer, Integer #) - integerEncodeDouble :: Integer -> GHC.Internal.Types.Int -> GHC.Internal.Types.Double - integerEncodeDouble# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double# - integerEncodeFloat# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float# - integerEq :: Integer -> Integer -> GHC.Internal.Types.Bool - integerEq# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Integer - integerFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Integer #) - integerFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer - integerFromBigNatNeg# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer - integerFromBigNatSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Bignum.BigNat.BigNat# -> Integer - integerFromByteArray :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> Integer - integerFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Integer #) - integerFromInt :: GHC.Internal.Types.Int -> Integer - integerFromInt# :: GHC.Internal.Prim.Int# -> Integer - integerFromInt64# :: GHC.Internal.Prim.Int64# -> Integer - integerFromNatural :: GHC.Internal.Bignum.Natural.Natural -> Integer - integerFromWord :: GHC.Internal.Types.Word -> Integer - integerFromWord# :: GHC.Internal.Prim.Word# -> Integer - integerFromWord64# :: GHC.Internal.Prim.Word64# -> Integer - integerFromWordList :: GHC.Internal.Types.Bool -> [GHC.Internal.Types.Word] -> Integer - integerFromWordNeg# :: GHC.Internal.Prim.Word# -> Integer - integerFromWordSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word# -> Integer - integerGcd :: Integer -> Integer -> Integer - integerGcde :: Integer -> Integer -> (Integer, Integer, Integer) - integerGcde# :: Integer -> Integer -> (# Integer, Integer, Integer #) - integerGe :: Integer -> Integer -> GHC.Internal.Types.Bool - integerGe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerGt :: Integer -> Integer -> GHC.Internal.Types.Bool - integerGt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerIsNegative :: Integer -> GHC.Internal.Types.Bool - integerIsNegative# :: Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerIsOne :: Integer -> GHC.Internal.Types.Bool - integerIsPowerOf2# :: Integer -> (# (# #) | GHC.Internal.Prim.Word# #) - integerIsZero :: Integer -> GHC.Internal.Types.Bool - integerLcm :: Integer -> Integer -> Integer - integerLe :: Integer -> Integer -> GHC.Internal.Types.Bool - integerLe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerLog2 :: Integer -> GHC.Internal.Types.Word - integerLog2# :: Integer -> GHC.Internal.Prim.Word# - integerLogBase :: Integer -> Integer -> GHC.Internal.Types.Word - integerLogBase# :: Integer -> Integer -> GHC.Internal.Prim.Word# - integerLogBaseWord :: GHC.Internal.Types.Word -> Integer -> GHC.Internal.Types.Word - integerLogBaseWord# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word# - integerLt :: Integer -> Integer -> GHC.Internal.Types.Bool - integerLt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerMod :: Integer -> Integer -> Integer - integerMul :: Integer -> Integer -> Integer - integerNe :: Integer -> Integer -> GHC.Internal.Types.Bool - integerNe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerNegate :: Integer -> Integer - integerOne :: Integer - integerOr :: Integer -> Integer -> Integer - integerPopCount# :: Integer -> GHC.Internal.Prim.Int# - integerPowMod# :: Integer -> Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #) - integerQuot :: Integer -> Integer -> Integer - integerQuotRem :: Integer -> Integer -> (Integer, Integer) - integerQuotRem# :: Integer -> Integer -> (# Integer, Integer #) - integerRecipMod# :: Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #) - integerRem :: Integer -> Integer -> Integer - integerShiftL :: Integer -> GHC.Internal.Types.Word -> Integer - integerShiftL# :: Integer -> GHC.Internal.Prim.Word# -> Integer - integerShiftR :: Integer -> GHC.Internal.Types.Word -> Integer - integerShiftR# :: Integer -> GHC.Internal.Prim.Word# -> Integer - integerSignum :: Integer -> Integer - integerSignum# :: Integer -> GHC.Internal.Prim.Int# - integerSizeInBase# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word# - integerSqr :: Integer -> Integer - integerSub :: Integer -> Integer -> Integer - integerTestBit :: Integer -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool - integerTestBit# :: Integer -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# - integerToAddr :: Integer -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word - integerToAddr# :: forall s. Integer -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - integerToBigNatClamp# :: Integer -> GHC.Internal.Bignum.BigNat.BigNat# - integerToBigNatSign# :: Integer -> (# GHC.Internal.Prim.Int#, GHC.Internal.Bignum.BigNat.BigNat# #) - integerToInt :: Integer -> GHC.Internal.Types.Int - integerToInt# :: Integer -> GHC.Internal.Prim.Int# - integerToInt64# :: Integer -> GHC.Internal.Prim.Int64# - integerToMutableByteArray :: Integer -> GHC.Internal.Prim.MutableByteArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word - integerToMutableByteArray# :: forall s. Integer -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - integerToNatural :: Integer -> GHC.Internal.Bignum.Natural.Natural - integerToNaturalClamp :: Integer -> GHC.Internal.Bignum.Natural.Natural - integerToNaturalThrow :: Integer -> GHC.Internal.Bignum.Natural.Natural - integerToWord :: Integer -> GHC.Internal.Types.Word - integerToWord# :: Integer -> GHC.Internal.Prim.Word# - integerToWord64# :: Integer -> GHC.Internal.Prim.Word64# - integerXor :: Integer -> Integer -> Integer - integerZero :: Integer - -module GHC.Num.Natural where - -- Safety: None - type Natural :: * - data Natural = NS GHC.Internal.Prim.Word# | NB GHC.Internal.Prim.ByteArray# - naturalAdd :: Natural -> Natural -> Natural - naturalAnd :: Natural -> Natural -> Natural - naturalAndNot :: Natural -> Natural -> Natural - naturalBit :: GHC.Internal.Types.Word -> Natural - naturalBit# :: GHC.Internal.Prim.Word# -> Natural - naturalCheck :: Natural -> GHC.Internal.Types.Bool - naturalCheck# :: Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalClearBit :: Natural -> GHC.Internal.Types.Word -> Natural - naturalClearBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural - naturalCompare :: Natural -> Natural -> GHC.Internal.Types.Ordering - naturalComplementBit :: Natural -> GHC.Internal.Types.Word -> Natural - naturalComplementBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural - naturalEncodeDouble# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double# - naturalEncodeFloat# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float# - naturalEq :: Natural -> Natural -> GHC.Internal.Types.Bool - naturalEq# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Natural - naturalFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Natural #) - naturalFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Natural - naturalFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Natural #) - naturalFromWord :: GHC.Internal.Types.Word -> Natural - naturalFromWord# :: GHC.Internal.Prim.Word# -> Natural - naturalFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> Natural - naturalFromWordList :: [GHC.Internal.Types.Word] -> Natural - naturalGcd :: Natural -> Natural -> Natural - naturalGe :: Natural -> Natural -> GHC.Internal.Types.Bool - naturalGe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalGt :: Natural -> Natural -> GHC.Internal.Types.Bool - naturalGt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalIsOne :: Natural -> GHC.Internal.Types.Bool - naturalIsPowerOf2# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #) - naturalIsZero :: Natural -> GHC.Internal.Types.Bool - naturalLcm :: Natural -> Natural -> Natural - naturalLe :: Natural -> Natural -> GHC.Internal.Types.Bool - naturalLe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalLog2 :: Natural -> GHC.Internal.Types.Word - naturalLog2# :: Natural -> GHC.Internal.Prim.Word# - naturalLogBase :: Natural -> Natural -> GHC.Internal.Types.Word - naturalLogBase# :: Natural -> Natural -> GHC.Internal.Prim.Word# - naturalLogBaseWord :: GHC.Internal.Types.Word -> Natural -> GHC.Internal.Types.Word - naturalLogBaseWord# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word# - naturalLt :: Natural -> Natural -> GHC.Internal.Types.Bool - naturalLt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalMul :: Natural -> Natural -> Natural - naturalNe :: Natural -> Natural -> GHC.Internal.Types.Bool - naturalNe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalNegate :: Natural -> Natural - naturalOne :: Natural - naturalOr :: Natural -> Natural -> Natural - naturalPopCount :: Natural -> GHC.Internal.Types.Word - naturalPopCount# :: Natural -> GHC.Internal.Prim.Word# - naturalPowMod :: Natural -> Natural -> Natural -> Natural - naturalQuot :: Natural -> Natural -> Natural - naturalQuotRem :: Natural -> Natural -> (Natural, Natural) - naturalQuotRem# :: Natural -> Natural -> (# Natural, Natural #) - naturalRem :: Natural -> Natural -> Natural - naturalSetBit :: Natural -> GHC.Internal.Types.Word -> Natural - naturalSetBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural - naturalShiftL :: Natural -> GHC.Internal.Types.Word -> Natural - naturalShiftL# :: Natural -> GHC.Internal.Prim.Word# -> Natural - naturalShiftR :: Natural -> GHC.Internal.Types.Word -> Natural - naturalShiftR# :: Natural -> GHC.Internal.Prim.Word# -> Natural - naturalSignum :: Natural -> Natural - naturalSizeInBase# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word# - naturalSqr :: Natural -> Natural - naturalSub :: Natural -> Natural -> (# (# #) | Natural #) - naturalSubThrow :: Natural -> Natural -> Natural - naturalSubUnsafe :: Natural -> Natural -> Natural - naturalTestBit :: Natural -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool - naturalTestBit# :: Natural -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# - naturalToAddr :: Natural -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word - naturalToAddr# :: forall s. Natural -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - naturalToBigNat# :: Natural -> GHC.Internal.Bignum.BigNat.BigNat# - naturalToMutableByteArray# :: forall s. Natural -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - naturalToWord :: Natural -> GHC.Internal.Types.Word - naturalToWord# :: Natural -> GHC.Internal.Prim.Word# - naturalToWordClamp :: Natural -> GHC.Internal.Types.Word - naturalToWordClamp# :: Natural -> GHC.Internal.Prim.Word# - naturalToWordMaybe# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #) - naturalXor :: Natural -> Natural -> Natural - naturalZero :: Natural - module GHC.OldList where -- Safety: Safe (!!) :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> GHC.Internal.Types.Int -> a ===================================== testsuite/tests/interface-stability/base-exports.stdout-mingw32 ===================================== @@ -8768,340 +8768,6 @@ module GHC.Num where quotRemInteger :: Integer -> Integer -> (# Integer, Integer #) subtract :: forall a. Num a => a -> a -> a -module GHC.Num.BigNat where - -- Safety: None - type BigNat :: * - data BigNat = BN# {unBigNat :: BigNat#} - type BigNat# :: GHC.Internal.Types.UnliftedType - type BigNat# = GHC.Internal.Bignum.WordArray.WordArray# - bigNatAdd :: BigNat# -> BigNat# -> BigNat# - bigNatAddWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat# - bigNatAddWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatAnd :: BigNat# -> BigNat# -> BigNat# - bigNatAndInt# :: BigNat# -> GHC.Internal.Prim.Int# -> BigNat# - bigNatAndNot :: BigNat# -> BigNat# -> BigNat# - bigNatAndNotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatAndWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatBit :: GHC.Internal.Types.Word -> BigNat# - bigNatBit# :: GHC.Internal.Prim.Word# -> BigNat# - bigNatCheck :: BigNat# -> GHC.Internal.Types.Bool - bigNatCheck# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatClearBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatCompare :: BigNat# -> BigNat# -> GHC.Internal.Types.Ordering - bigNatCompareWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Ordering - bigNatCompareWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Types.Ordering - bigNatComplementBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatCtz :: BigNat# -> GHC.Internal.Types.Word - bigNatCtz# :: BigNat# -> GHC.Internal.Prim.Word# - bigNatCtzWord :: BigNat# -> GHC.Internal.Types.Word - bigNatCtzWord# :: BigNat# -> GHC.Internal.Prim.Word# - bigNatEncodeDouble# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double# - bigNatEq :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool - bigNatEq# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatEqWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatFromAbsInt# :: GHC.Internal.Prim.Int# -> BigNat# - bigNatFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) - bigNatFromAddrBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) - bigNatFromAddrLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) - bigNatFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) - bigNatFromByteArrayBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) - bigNatFromByteArrayLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) - bigNatFromWord :: GHC.Internal.Types.Word -> BigNat# - bigNatFromWord# :: GHC.Internal.Prim.Word# -> BigNat# - bigNatFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatFromWord64# :: GHC.Internal.Prim.Word64# -> BigNat# - bigNatFromWordArray :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat - bigNatFromWordArray# :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatFromWordList :: [GHC.Internal.Types.Word] -> BigNat# - bigNatFromWordList# :: [GHC.Internal.Types.Word] -> GHC.Internal.Bignum.WordArray.WordArray# - bigNatFromWordListUnsafe :: [GHC.Internal.Types.Word] -> BigNat# - bigNatGcd :: BigNat# -> BigNat# -> BigNat# - bigNatGcdWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# - bigNatGe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool - bigNatGe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatGt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool - bigNatGt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatGtWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool - bigNatGtWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatIndex :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Types.Word - bigNatIndex# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word# - bigNatIsOne :: BigNat# -> GHC.Internal.Types.Bool - bigNatIsOne# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatIsPowerOf2# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #) - bigNatIsTwo :: BigNat# -> GHC.Internal.Types.Bool - bigNatIsTwo# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatIsZero :: BigNat# -> GHC.Internal.Types.Bool - bigNatIsZero# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatLcm :: BigNat# -> BigNat# -> BigNat# - bigNatLcmWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatLcmWordWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatLe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool - bigNatLe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatLeWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool - bigNatLeWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatLog2 :: BigNat# -> GHC.Internal.Types.Word - bigNatLog2# :: BigNat# -> GHC.Internal.Prim.Word# - bigNatLogBase :: BigNat# -> BigNat# -> GHC.Internal.Types.Word - bigNatLogBase# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word# - bigNatLogBaseWord :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word - bigNatLogBaseWord# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word# - bigNatLt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool - bigNatLt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatMul :: BigNat# -> BigNat# -> BigNat# - bigNatMulWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat# - bigNatMulWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatNe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool - bigNatNe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatOne :: BigNat - bigNatOne# :: (# #) -> BigNat# - bigNatOr :: BigNat# -> BigNat# -> BigNat# - bigNatOrWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatPopCount :: BigNat# -> GHC.Internal.Types.Word - bigNatPopCount# :: BigNat# -> GHC.Internal.Prim.Word# - bigNatPowMod :: BigNat# -> BigNat# -> BigNat# -> BigNat# - bigNatPowModWord# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# - bigNatQuot :: BigNat# -> BigNat# -> BigNat# - bigNatQuotRem# :: BigNat# -> BigNat# -> (# BigNat#, BigNat# #) - bigNatQuotRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# BigNat#, GHC.Internal.Prim.Word# #) - bigNatQuotWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat# - bigNatQuotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatRem :: BigNat# -> BigNat# -> BigNat# - bigNatRemWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word - bigNatRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# - bigNatSetBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatShiftL :: BigNat# -> GHC.Internal.Types.Word -> BigNat# - bigNatShiftL# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatShiftR :: BigNat# -> GHC.Internal.Types.Word -> BigNat# - bigNatShiftR# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatShiftRNeg# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatSize :: BigNat# -> GHC.Internal.Types.Word - bigNatSize# :: BigNat# -> GHC.Internal.Prim.Int# - bigNatSizeInBase :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word - bigNatSizeInBase# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word# - bigNatSqr :: BigNat# -> BigNat# - bigNatSub :: BigNat# -> BigNat# -> (# (# #) | BigNat# #) - bigNatSubUnsafe :: BigNat# -> BigNat# -> BigNat# - bigNatSubWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# (# #) | BigNat# #) - bigNatSubWordUnsafe :: BigNat# -> GHC.Internal.Types.Word -> BigNat# - bigNatSubWordUnsafe# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatTestBit :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool - bigNatTestBit# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatToAddr :: BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word - bigNatToAddr# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - bigNatToAddrBE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - bigNatToAddrLE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - bigNatToInt :: BigNat# -> GHC.Internal.Types.Int - bigNatToInt# :: BigNat# -> GHC.Internal.Prim.Int# - bigNatToMutableByteArray# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - bigNatToMutableByteArrayBE# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - bigNatToMutableByteArrayLE# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - bigNatToWord :: BigNat# -> GHC.Internal.Types.Word - bigNatToWord# :: BigNat# -> GHC.Internal.Prim.Word# - bigNatToWord64# :: BigNat# -> GHC.Internal.Prim.Word64# - bigNatToWordList :: BigNat# -> [GHC.Internal.Types.Word] - bigNatToWordMaybe# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #) - bigNatXor :: BigNat# -> BigNat# -> BigNat# - bigNatXorWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatZero :: BigNat - bigNatZero# :: (# #) -> BigNat# - gcdInt :: GHC.Internal.Types.Int -> GHC.Internal.Types.Int -> GHC.Internal.Types.Int - gcdInt# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# - gcdWord :: GHC.Internal.Types.Word -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word - gcdWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# - powModWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# - raiseDivZero_BigNat :: (# #) -> BigNat# - -module GHC.Num.Integer where - -- Safety: None - type Integer :: * - data Integer = IS GHC.Internal.Prim.Int# | IP GHC.Internal.Prim.ByteArray# | IN GHC.Internal.Prim.ByteArray# - integerAbs :: Integer -> Integer - integerAdd :: Integer -> Integer -> Integer - integerAnd :: Integer -> Integer -> Integer - integerBit :: GHC.Internal.Types.Word -> Integer - integerBit# :: GHC.Internal.Prim.Word# -> Integer - integerCheck :: Integer -> GHC.Internal.Types.Bool - integerCheck# :: Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerCompare :: Integer -> Integer -> GHC.Internal.Types.Ordering - integerComplement :: Integer -> Integer - integerDecodeDouble# :: GHC.Internal.Prim.Double# -> (# Integer, GHC.Internal.Prim.Int# #) - integerDiv :: Integer -> Integer -> Integer - integerDivMod :: Integer -> Integer -> (Integer, Integer) - integerDivMod# :: Integer -> Integer -> (# Integer, Integer #) - integerEncodeDouble :: Integer -> GHC.Internal.Types.Int -> GHC.Internal.Types.Double - integerEncodeDouble# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double# - integerEncodeFloat# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float# - integerEq :: Integer -> Integer -> GHC.Internal.Types.Bool - integerEq# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Integer - integerFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Integer #) - integerFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer - integerFromBigNatNeg# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer - integerFromBigNatSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Bignum.BigNat.BigNat# -> Integer - integerFromByteArray :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> Integer - integerFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Integer #) - integerFromInt :: GHC.Internal.Types.Int -> Integer - integerFromInt# :: GHC.Internal.Prim.Int# -> Integer - integerFromInt64# :: GHC.Internal.Prim.Int64# -> Integer - integerFromNatural :: GHC.Internal.Bignum.Natural.Natural -> Integer - integerFromWord :: GHC.Internal.Types.Word -> Integer - integerFromWord# :: GHC.Internal.Prim.Word# -> Integer - integerFromWord64# :: GHC.Internal.Prim.Word64# -> Integer - integerFromWordList :: GHC.Internal.Types.Bool -> [GHC.Internal.Types.Word] -> Integer - integerFromWordNeg# :: GHC.Internal.Prim.Word# -> Integer - integerFromWordSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word# -> Integer - integerGcd :: Integer -> Integer -> Integer - integerGcde :: Integer -> Integer -> (Integer, Integer, Integer) - integerGcde# :: Integer -> Integer -> (# Integer, Integer, Integer #) - integerGe :: Integer -> Integer -> GHC.Internal.Types.Bool - integerGe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerGt :: Integer -> Integer -> GHC.Internal.Types.Bool - integerGt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerIsNegative :: Integer -> GHC.Internal.Types.Bool - integerIsNegative# :: Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerIsOne :: Integer -> GHC.Internal.Types.Bool - integerIsPowerOf2# :: Integer -> (# (# #) | GHC.Internal.Prim.Word# #) - integerIsZero :: Integer -> GHC.Internal.Types.Bool - integerLcm :: Integer -> Integer -> Integer - integerLe :: Integer -> Integer -> GHC.Internal.Types.Bool - integerLe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerLog2 :: Integer -> GHC.Internal.Types.Word - integerLog2# :: Integer -> GHC.Internal.Prim.Word# - integerLogBase :: Integer -> Integer -> GHC.Internal.Types.Word - integerLogBase# :: Integer -> Integer -> GHC.Internal.Prim.Word# - integerLogBaseWord :: GHC.Internal.Types.Word -> Integer -> GHC.Internal.Types.Word - integerLogBaseWord# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word# - integerLt :: Integer -> Integer -> GHC.Internal.Types.Bool - integerLt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerMod :: Integer -> Integer -> Integer - integerMul :: Integer -> Integer -> Integer - integerNe :: Integer -> Integer -> GHC.Internal.Types.Bool - integerNe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerNegate :: Integer -> Integer - integerOne :: Integer - integerOr :: Integer -> Integer -> Integer - integerPopCount# :: Integer -> GHC.Internal.Prim.Int# - integerPowMod# :: Integer -> Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #) - integerQuot :: Integer -> Integer -> Integer - integerQuotRem :: Integer -> Integer -> (Integer, Integer) - integerQuotRem# :: Integer -> Integer -> (# Integer, Integer #) - integerRecipMod# :: Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #) - integerRem :: Integer -> Integer -> Integer - integerShiftL :: Integer -> GHC.Internal.Types.Word -> Integer - integerShiftL# :: Integer -> GHC.Internal.Prim.Word# -> Integer - integerShiftR :: Integer -> GHC.Internal.Types.Word -> Integer - integerShiftR# :: Integer -> GHC.Internal.Prim.Word# -> Integer - integerSignum :: Integer -> Integer - integerSignum# :: Integer -> GHC.Internal.Prim.Int# - integerSizeInBase# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word# - integerSqr :: Integer -> Integer - integerSub :: Integer -> Integer -> Integer - integerTestBit :: Integer -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool - integerTestBit# :: Integer -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# - integerToAddr :: Integer -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word - integerToAddr# :: forall s. Integer -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - integerToBigNatClamp# :: Integer -> GHC.Internal.Bignum.BigNat.BigNat# - integerToBigNatSign# :: Integer -> (# GHC.Internal.Prim.Int#, GHC.Internal.Bignum.BigNat.BigNat# #) - integerToInt :: Integer -> GHC.Internal.Types.Int - integerToInt# :: Integer -> GHC.Internal.Prim.Int# - integerToInt64# :: Integer -> GHC.Internal.Prim.Int64# - integerToMutableByteArray :: Integer -> GHC.Internal.Prim.MutableByteArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word - integerToMutableByteArray# :: forall s. Integer -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - integerToNatural :: Integer -> GHC.Internal.Bignum.Natural.Natural - integerToNaturalClamp :: Integer -> GHC.Internal.Bignum.Natural.Natural - integerToNaturalThrow :: Integer -> GHC.Internal.Bignum.Natural.Natural - integerToWord :: Integer -> GHC.Internal.Types.Word - integerToWord# :: Integer -> GHC.Internal.Prim.Word# - integerToWord64# :: Integer -> GHC.Internal.Prim.Word64# - integerXor :: Integer -> Integer -> Integer - integerZero :: Integer - -module GHC.Num.Natural where - -- Safety: None - type Natural :: * - data Natural = NS GHC.Internal.Prim.Word# | NB GHC.Internal.Prim.ByteArray# - naturalAdd :: Natural -> Natural -> Natural - naturalAnd :: Natural -> Natural -> Natural - naturalAndNot :: Natural -> Natural -> Natural - naturalBit :: GHC.Internal.Types.Word -> Natural - naturalBit# :: GHC.Internal.Prim.Word# -> Natural - naturalCheck :: Natural -> GHC.Internal.Types.Bool - naturalCheck# :: Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalClearBit :: Natural -> GHC.Internal.Types.Word -> Natural - naturalClearBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural - naturalCompare :: Natural -> Natural -> GHC.Internal.Types.Ordering - naturalComplementBit :: Natural -> GHC.Internal.Types.Word -> Natural - naturalComplementBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural - naturalEncodeDouble# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double# - naturalEncodeFloat# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float# - naturalEq :: Natural -> Natural -> GHC.Internal.Types.Bool - naturalEq# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Natural - naturalFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Natural #) - naturalFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Natural - naturalFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Natural #) - naturalFromWord :: GHC.Internal.Types.Word -> Natural - naturalFromWord# :: GHC.Internal.Prim.Word# -> Natural - naturalFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> Natural - naturalFromWordList :: [GHC.Internal.Types.Word] -> Natural - naturalGcd :: Natural -> Natural -> Natural - naturalGe :: Natural -> Natural -> GHC.Internal.Types.Bool - naturalGe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalGt :: Natural -> Natural -> GHC.Internal.Types.Bool - naturalGt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalIsOne :: Natural -> GHC.Internal.Types.Bool - naturalIsPowerOf2# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #) - naturalIsZero :: Natural -> GHC.Internal.Types.Bool - naturalLcm :: Natural -> Natural -> Natural - naturalLe :: Natural -> Natural -> GHC.Internal.Types.Bool - naturalLe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalLog2 :: Natural -> GHC.Internal.Types.Word - naturalLog2# :: Natural -> GHC.Internal.Prim.Word# - naturalLogBase :: Natural -> Natural -> GHC.Internal.Types.Word - naturalLogBase# :: Natural -> Natural -> GHC.Internal.Prim.Word# - naturalLogBaseWord :: GHC.Internal.Types.Word -> Natural -> GHC.Internal.Types.Word - naturalLogBaseWord# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word# - naturalLt :: Natural -> Natural -> GHC.Internal.Types.Bool - naturalLt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalMul :: Natural -> Natural -> Natural - naturalNe :: Natural -> Natural -> GHC.Internal.Types.Bool - naturalNe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalNegate :: Natural -> Natural - naturalOne :: Natural - naturalOr :: Natural -> Natural -> Natural - naturalPopCount :: Natural -> GHC.Internal.Types.Word - naturalPopCount# :: Natural -> GHC.Internal.Prim.Word# - naturalPowMod :: Natural -> Natural -> Natural -> Natural - naturalQuot :: Natural -> Natural -> Natural - naturalQuotRem :: Natural -> Natural -> (Natural, Natural) - naturalQuotRem# :: Natural -> Natural -> (# Natural, Natural #) - naturalRem :: Natural -> Natural -> Natural - naturalSetBit :: Natural -> GHC.Internal.Types.Word -> Natural - naturalSetBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural - naturalShiftL :: Natural -> GHC.Internal.Types.Word -> Natural - naturalShiftL# :: Natural -> GHC.Internal.Prim.Word# -> Natural - naturalShiftR :: Natural -> GHC.Internal.Types.Word -> Natural - naturalShiftR# :: Natural -> GHC.Internal.Prim.Word# -> Natural - naturalSignum :: Natural -> Natural - naturalSizeInBase# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word# - naturalSqr :: Natural -> Natural - naturalSub :: Natural -> Natural -> (# (# #) | Natural #) - naturalSubThrow :: Natural -> Natural -> Natural - naturalSubUnsafe :: Natural -> Natural -> Natural - naturalTestBit :: Natural -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool - naturalTestBit# :: Natural -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# - naturalToAddr :: Natural -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word - naturalToAddr# :: forall s. Natural -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - naturalToBigNat# :: Natural -> GHC.Internal.Bignum.BigNat.BigNat# - naturalToMutableByteArray# :: forall s. Natural -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - naturalToWord :: Natural -> GHC.Internal.Types.Word - naturalToWord# :: Natural -> GHC.Internal.Prim.Word# - naturalToWordClamp :: Natural -> GHC.Internal.Types.Word - naturalToWordClamp# :: Natural -> GHC.Internal.Prim.Word# - naturalToWordMaybe# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #) - naturalXor :: Natural -> Natural -> Natural - naturalZero :: Natural - module GHC.OldList where -- Safety: Safe (!!) :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> GHC.Internal.Types.Int -> a ===================================== testsuite/tests/interface-stability/base-exports.stdout-ws-32 ===================================== @@ -8550,340 +8550,6 @@ module GHC.Num where quotRemInteger :: Integer -> Integer -> (# Integer, Integer #) subtract :: forall a. Num a => a -> a -> a -module GHC.Num.BigNat where - -- Safety: None - type BigNat :: * - data BigNat = BN# {unBigNat :: BigNat#} - type BigNat# :: GHC.Internal.Types.UnliftedType - type BigNat# = GHC.Internal.Bignum.WordArray.WordArray# - bigNatAdd :: BigNat# -> BigNat# -> BigNat# - bigNatAddWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat# - bigNatAddWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatAnd :: BigNat# -> BigNat# -> BigNat# - bigNatAndInt# :: BigNat# -> GHC.Internal.Prim.Int# -> BigNat# - bigNatAndNot :: BigNat# -> BigNat# -> BigNat# - bigNatAndNotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatAndWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatBit :: GHC.Internal.Types.Word -> BigNat# - bigNatBit# :: GHC.Internal.Prim.Word# -> BigNat# - bigNatCheck :: BigNat# -> GHC.Internal.Types.Bool - bigNatCheck# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatClearBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatCompare :: BigNat# -> BigNat# -> GHC.Internal.Types.Ordering - bigNatCompareWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Ordering - bigNatCompareWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Types.Ordering - bigNatComplementBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatCtz :: BigNat# -> GHC.Internal.Types.Word - bigNatCtz# :: BigNat# -> GHC.Internal.Prim.Word# - bigNatCtzWord :: BigNat# -> GHC.Internal.Types.Word - bigNatCtzWord# :: BigNat# -> GHC.Internal.Prim.Word# - bigNatEncodeDouble# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double# - bigNatEq :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool - bigNatEq# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatEqWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatFromAbsInt# :: GHC.Internal.Prim.Int# -> BigNat# - bigNatFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) - bigNatFromAddrBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) - bigNatFromAddrLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) - bigNatFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) - bigNatFromByteArrayBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) - bigNatFromByteArrayLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #) - bigNatFromWord :: GHC.Internal.Types.Word -> BigNat# - bigNatFromWord# :: GHC.Internal.Prim.Word# -> BigNat# - bigNatFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatFromWord64# :: GHC.Internal.Prim.Word64# -> BigNat# - bigNatFromWordArray :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat - bigNatFromWordArray# :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatFromWordList :: [GHC.Internal.Types.Word] -> BigNat# - bigNatFromWordList# :: [GHC.Internal.Types.Word] -> GHC.Internal.Bignum.WordArray.WordArray# - bigNatFromWordListUnsafe :: [GHC.Internal.Types.Word] -> BigNat# - bigNatGcd :: BigNat# -> BigNat# -> BigNat# - bigNatGcdWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# - bigNatGe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool - bigNatGe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatGt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool - bigNatGt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatGtWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool - bigNatGtWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatIndex :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Types.Word - bigNatIndex# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word# - bigNatIsOne :: BigNat# -> GHC.Internal.Types.Bool - bigNatIsOne# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatIsPowerOf2# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #) - bigNatIsTwo :: BigNat# -> GHC.Internal.Types.Bool - bigNatIsTwo# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatIsZero :: BigNat# -> GHC.Internal.Types.Bool - bigNatIsZero# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatLcm :: BigNat# -> BigNat# -> BigNat# - bigNatLcmWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatLcmWordWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatLe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool - bigNatLe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatLeWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool - bigNatLeWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatLog2 :: BigNat# -> GHC.Internal.Types.Word - bigNatLog2# :: BigNat# -> GHC.Internal.Prim.Word# - bigNatLogBase :: BigNat# -> BigNat# -> GHC.Internal.Types.Word - bigNatLogBase# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word# - bigNatLogBaseWord :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word - bigNatLogBaseWord# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word# - bigNatLt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool - bigNatLt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatMul :: BigNat# -> BigNat# -> BigNat# - bigNatMulWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat# - bigNatMulWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatNe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool - bigNatNe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatOne :: BigNat - bigNatOne# :: (# #) -> BigNat# - bigNatOr :: BigNat# -> BigNat# -> BigNat# - bigNatOrWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatPopCount :: BigNat# -> GHC.Internal.Types.Word - bigNatPopCount# :: BigNat# -> GHC.Internal.Prim.Word# - bigNatPowMod :: BigNat# -> BigNat# -> BigNat# -> BigNat# - bigNatPowModWord# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# - bigNatQuot :: BigNat# -> BigNat# -> BigNat# - bigNatQuotRem# :: BigNat# -> BigNat# -> (# BigNat#, BigNat# #) - bigNatQuotRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# BigNat#, GHC.Internal.Prim.Word# #) - bigNatQuotWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat# - bigNatQuotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatRem :: BigNat# -> BigNat# -> BigNat# - bigNatRemWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word - bigNatRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# - bigNatSetBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatShiftL :: BigNat# -> GHC.Internal.Types.Word -> BigNat# - bigNatShiftL# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatShiftR :: BigNat# -> GHC.Internal.Types.Word -> BigNat# - bigNatShiftR# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatShiftRNeg# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatSize :: BigNat# -> GHC.Internal.Types.Word - bigNatSize# :: BigNat# -> GHC.Internal.Prim.Int# - bigNatSizeInBase :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word - bigNatSizeInBase# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word# - bigNatSqr :: BigNat# -> BigNat# - bigNatSub :: BigNat# -> BigNat# -> (# (# #) | BigNat# #) - bigNatSubUnsafe :: BigNat# -> BigNat# -> BigNat# - bigNatSubWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# (# #) | BigNat# #) - bigNatSubWordUnsafe :: BigNat# -> GHC.Internal.Types.Word -> BigNat# - bigNatSubWordUnsafe# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatTestBit :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool - bigNatTestBit# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# - bigNatToAddr :: BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word - bigNatToAddr# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - bigNatToAddrBE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - bigNatToAddrLE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - bigNatToInt :: BigNat# -> GHC.Internal.Types.Int - bigNatToInt# :: BigNat# -> GHC.Internal.Prim.Int# - bigNatToMutableByteArray# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - bigNatToMutableByteArrayBE# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - bigNatToMutableByteArrayLE# :: forall s. BigNat# -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - bigNatToWord :: BigNat# -> GHC.Internal.Types.Word - bigNatToWord# :: BigNat# -> GHC.Internal.Prim.Word# - bigNatToWord64# :: BigNat# -> GHC.Internal.Prim.Word64# - bigNatToWordList :: BigNat# -> [GHC.Internal.Types.Word] - bigNatToWordMaybe# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #) - bigNatXor :: BigNat# -> BigNat# -> BigNat# - bigNatXorWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat# - bigNatZero :: BigNat - bigNatZero# :: (# #) -> BigNat# - gcdInt :: GHC.Internal.Types.Int -> GHC.Internal.Types.Int -> GHC.Internal.Types.Int - gcdInt# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# - gcdWord :: GHC.Internal.Types.Word -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word - gcdWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# - powModWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# - raiseDivZero_BigNat :: (# #) -> BigNat# - -module GHC.Num.Integer where - -- Safety: None - type Integer :: * - data Integer = IS GHC.Internal.Prim.Int# | IP GHC.Internal.Prim.ByteArray# | IN GHC.Internal.Prim.ByteArray# - integerAbs :: Integer -> Integer - integerAdd :: Integer -> Integer -> Integer - integerAnd :: Integer -> Integer -> Integer - integerBit :: GHC.Internal.Types.Word -> Integer - integerBit# :: GHC.Internal.Prim.Word# -> Integer - integerCheck :: Integer -> GHC.Internal.Types.Bool - integerCheck# :: Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerCompare :: Integer -> Integer -> GHC.Internal.Types.Ordering - integerComplement :: Integer -> Integer - integerDecodeDouble# :: GHC.Internal.Prim.Double# -> (# Integer, GHC.Internal.Prim.Int# #) - integerDiv :: Integer -> Integer -> Integer - integerDivMod :: Integer -> Integer -> (Integer, Integer) - integerDivMod# :: Integer -> Integer -> (# Integer, Integer #) - integerEncodeDouble :: Integer -> GHC.Internal.Types.Int -> GHC.Internal.Types.Double - integerEncodeDouble# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double# - integerEncodeFloat# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float# - integerEq :: Integer -> Integer -> GHC.Internal.Types.Bool - integerEq# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Integer - integerFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Integer #) - integerFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer - integerFromBigNatNeg# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer - integerFromBigNatSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Bignum.BigNat.BigNat# -> Integer - integerFromByteArray :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> Integer - integerFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Integer #) - integerFromInt :: GHC.Internal.Types.Int -> Integer - integerFromInt# :: GHC.Internal.Prim.Int# -> Integer - integerFromInt64# :: GHC.Internal.Prim.Int64# -> Integer - integerFromNatural :: GHC.Internal.Bignum.Natural.Natural -> Integer - integerFromWord :: GHC.Internal.Types.Word -> Integer - integerFromWord# :: GHC.Internal.Prim.Word# -> Integer - integerFromWord64# :: GHC.Internal.Prim.Word64# -> Integer - integerFromWordList :: GHC.Internal.Types.Bool -> [GHC.Internal.Types.Word] -> Integer - integerFromWordNeg# :: GHC.Internal.Prim.Word# -> Integer - integerFromWordSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word# -> Integer - integerGcd :: Integer -> Integer -> Integer - integerGcde :: Integer -> Integer -> (Integer, Integer, Integer) - integerGcde# :: Integer -> Integer -> (# Integer, Integer, Integer #) - integerGe :: Integer -> Integer -> GHC.Internal.Types.Bool - integerGe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerGt :: Integer -> Integer -> GHC.Internal.Types.Bool - integerGt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerIsNegative :: Integer -> GHC.Internal.Types.Bool - integerIsNegative# :: Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerIsOne :: Integer -> GHC.Internal.Types.Bool - integerIsPowerOf2# :: Integer -> (# (# #) | GHC.Internal.Prim.Word# #) - integerIsZero :: Integer -> GHC.Internal.Types.Bool - integerLcm :: Integer -> Integer -> Integer - integerLe :: Integer -> Integer -> GHC.Internal.Types.Bool - integerLe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerLog2 :: Integer -> GHC.Internal.Types.Word - integerLog2# :: Integer -> GHC.Internal.Prim.Word# - integerLogBase :: Integer -> Integer -> GHC.Internal.Types.Word - integerLogBase# :: Integer -> Integer -> GHC.Internal.Prim.Word# - integerLogBaseWord :: GHC.Internal.Types.Word -> Integer -> GHC.Internal.Types.Word - integerLogBaseWord# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word# - integerLt :: Integer -> Integer -> GHC.Internal.Types.Bool - integerLt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerMod :: Integer -> Integer -> Integer - integerMul :: Integer -> Integer -> Integer - integerNe :: Integer -> Integer -> GHC.Internal.Types.Bool - integerNe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool# - integerNegate :: Integer -> Integer - integerOne :: Integer - integerOr :: Integer -> Integer -> Integer - integerPopCount# :: Integer -> GHC.Internal.Prim.Int# - integerPowMod# :: Integer -> Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #) - integerQuot :: Integer -> Integer -> Integer - integerQuotRem :: Integer -> Integer -> (Integer, Integer) - integerQuotRem# :: Integer -> Integer -> (# Integer, Integer #) - integerRecipMod# :: Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #) - integerRem :: Integer -> Integer -> Integer - integerShiftL :: Integer -> GHC.Internal.Types.Word -> Integer - integerShiftL# :: Integer -> GHC.Internal.Prim.Word# -> Integer - integerShiftR :: Integer -> GHC.Internal.Types.Word -> Integer - integerShiftR# :: Integer -> GHC.Internal.Prim.Word# -> Integer - integerSignum :: Integer -> Integer - integerSignum# :: Integer -> GHC.Internal.Prim.Int# - integerSizeInBase# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word# - integerSqr :: Integer -> Integer - integerSub :: Integer -> Integer -> Integer - integerTestBit :: Integer -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool - integerTestBit# :: Integer -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# - integerToAddr :: Integer -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word - integerToAddr# :: forall s. Integer -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - integerToBigNatClamp# :: Integer -> GHC.Internal.Bignum.BigNat.BigNat# - integerToBigNatSign# :: Integer -> (# GHC.Internal.Prim.Int#, GHC.Internal.Bignum.BigNat.BigNat# #) - integerToInt :: Integer -> GHC.Internal.Types.Int - integerToInt# :: Integer -> GHC.Internal.Prim.Int# - integerToInt64# :: Integer -> GHC.Internal.Prim.Int64# - integerToMutableByteArray :: Integer -> GHC.Internal.Prim.MutableByteArray# GHC.Internal.Prim.RealWorld -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word - integerToMutableByteArray# :: forall s. Integer -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - integerToNatural :: Integer -> GHC.Internal.Bignum.Natural.Natural - integerToNaturalClamp :: Integer -> GHC.Internal.Bignum.Natural.Natural - integerToNaturalThrow :: Integer -> GHC.Internal.Bignum.Natural.Natural - integerToWord :: Integer -> GHC.Internal.Types.Word - integerToWord# :: Integer -> GHC.Internal.Prim.Word# - integerToWord64# :: Integer -> GHC.Internal.Prim.Word64# - integerXor :: Integer -> Integer -> Integer - integerZero :: Integer - -module GHC.Num.Natural where - -- Safety: None - type Natural :: * - data Natural = NS GHC.Internal.Prim.Word# | NB GHC.Internal.Prim.ByteArray# - naturalAdd :: Natural -> Natural -> Natural - naturalAnd :: Natural -> Natural -> Natural - naturalAndNot :: Natural -> Natural -> Natural - naturalBit :: GHC.Internal.Types.Word -> Natural - naturalBit# :: GHC.Internal.Prim.Word# -> Natural - naturalCheck :: Natural -> GHC.Internal.Types.Bool - naturalCheck# :: Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalClearBit :: Natural -> GHC.Internal.Types.Word -> Natural - naturalClearBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural - naturalCompare :: Natural -> Natural -> GHC.Internal.Types.Ordering - naturalComplementBit :: Natural -> GHC.Internal.Types.Word -> Natural - naturalComplementBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural - naturalEncodeDouble# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double# - naturalEncodeFloat# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float# - naturalEq :: Natural -> Natural -> GHC.Internal.Types.Bool - naturalEq# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Natural - naturalFromAddr# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Natural #) - naturalFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Natural - naturalFromByteArray# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, Natural #) - naturalFromWord :: GHC.Internal.Types.Word -> Natural - naturalFromWord# :: GHC.Internal.Prim.Word# -> Natural - naturalFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> Natural - naturalFromWordList :: [GHC.Internal.Types.Word] -> Natural - naturalGcd :: Natural -> Natural -> Natural - naturalGe :: Natural -> Natural -> GHC.Internal.Types.Bool - naturalGe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalGt :: Natural -> Natural -> GHC.Internal.Types.Bool - naturalGt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalIsOne :: Natural -> GHC.Internal.Types.Bool - naturalIsPowerOf2# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #) - naturalIsZero :: Natural -> GHC.Internal.Types.Bool - naturalLcm :: Natural -> Natural -> Natural - naturalLe :: Natural -> Natural -> GHC.Internal.Types.Bool - naturalLe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalLog2 :: Natural -> GHC.Internal.Types.Word - naturalLog2# :: Natural -> GHC.Internal.Prim.Word# - naturalLogBase :: Natural -> Natural -> GHC.Internal.Types.Word - naturalLogBase# :: Natural -> Natural -> GHC.Internal.Prim.Word# - naturalLogBaseWord :: GHC.Internal.Types.Word -> Natural -> GHC.Internal.Types.Word - naturalLogBaseWord# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word# - naturalLt :: Natural -> Natural -> GHC.Internal.Types.Bool - naturalLt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalMul :: Natural -> Natural -> Natural - naturalNe :: Natural -> Natural -> GHC.Internal.Types.Bool - naturalNe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool# - naturalNegate :: Natural -> Natural - naturalOne :: Natural - naturalOr :: Natural -> Natural -> Natural - naturalPopCount :: Natural -> GHC.Internal.Types.Word - naturalPopCount# :: Natural -> GHC.Internal.Prim.Word# - naturalPowMod :: Natural -> Natural -> Natural -> Natural - naturalQuot :: Natural -> Natural -> Natural - naturalQuotRem :: Natural -> Natural -> (Natural, Natural) - naturalQuotRem# :: Natural -> Natural -> (# Natural, Natural #) - naturalRem :: Natural -> Natural -> Natural - naturalSetBit :: Natural -> GHC.Internal.Types.Word -> Natural - naturalSetBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural - naturalShiftL :: Natural -> GHC.Internal.Types.Word -> Natural - naturalShiftL# :: Natural -> GHC.Internal.Prim.Word# -> Natural - naturalShiftR :: Natural -> GHC.Internal.Types.Word -> Natural - naturalShiftR# :: Natural -> GHC.Internal.Prim.Word# -> Natural - naturalSignum :: Natural -> Natural - naturalSizeInBase# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word# - naturalSqr :: Natural -> Natural - naturalSub :: Natural -> Natural -> (# (# #) | Natural #) - naturalSubThrow :: Natural -> Natural -> Natural - naturalSubUnsafe :: Natural -> Natural -> Natural - naturalTestBit :: Natural -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool - naturalTestBit# :: Natural -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# - naturalToAddr :: Natural -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word - naturalToAddr# :: forall s. Natural -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - naturalToBigNat# :: Natural -> GHC.Internal.Bignum.BigNat.BigNat# - naturalToMutableByteArray# :: forall s. Natural -> GHC.Internal.Prim.MutableByteArray# s -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #) - naturalToWord :: Natural -> GHC.Internal.Types.Word - naturalToWord# :: Natural -> GHC.Internal.Prim.Word# - naturalToWordClamp :: Natural -> GHC.Internal.Types.Word - naturalToWordClamp# :: Natural -> GHC.Internal.Prim.Word# - naturalToWordMaybe# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #) - naturalXor :: Natural -> Natural -> Natural - naturalZero :: Natural - module GHC.OldList where -- Safety: Safe (!!) :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> GHC.Internal.Types.Int -> a View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8524ec749269a9a040a38db4d25d41f... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8524ec749269a9a040a38db4d25d41f... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Marge Bot (@marge-bot)