Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC

Commits:

14 changed files:

Changes:

  • libraries/base/base.cabal.in
    ... ... @@ -219,9 +219,6 @@ Library
    219 219
             , GHC.MVar
    
    220 220
             , GHC.Natural
    
    221 221
             , GHC.Num
    
    222
    -        , GHC.Num.Integer
    
    223
    -        , GHC.Num.Natural
    
    224
    -        , GHC.Num.BigNat
    
    225 222
             , GHC.OldList
    
    226 223
             , GHC.OverloadedLabels
    
    227 224
             , GHC.Profiling
    

  • libraries/base/changelog.md
    ... ... @@ -13,8 +13,10 @@
    13 13
       * Add `thenA` and `thenM`. ([CLC proposal #351](https://github.com/haskell/core-libraries-committee/issues/351))
    
    14 14
       * Fix bug where `naturalAndNot` was incorrectly truncating results ([CLC proposal #350](github.com/haskell/core-libraries-committee/issues/350))
    
    15 15
       * generalize `deleteBy` and `deleteFirstsBy` ([CLC proposal 372](https://github.com/haskell/core-libraries-committee/issues/372))
    
    16
    +  * 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))
    
    16 17
       * 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))
    
    17 18
       * 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)
    
    19
    +  * 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])
    
    18 20
       * Add `nubOrd` / `nubOrdBy` to `Data.List` and `Data.List.NonEmpty`. ([CLC proposal #336](https://github.com/haskell/core-libraries-committee/issues/336))
    
    19 21
       * Add `Semigroup` and `Monoid` instances for `Control.Monad.ST.Lazy`. ([CLC proposal #374](https://github.com/haskell/core-libraries-committee/issues/374))
    
    20 22
       * `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
    27 27
     import GHC.Internal.Data.Maybe (fromMaybe)
    
    28 28
     import Data.Semigroup
    
    29 29
     import GHC.Internal.Exts
    
    30
    -import GHC.Num.Integer (Integer(..))
    
    30
    +import GHC.Internal.Bignum.Integer (Integer(..))
    
    31 31
     import GHC.Internal.Show (intToDigit)
    
    32 32
     import GHC.Internal.ST (ST(..), runST)
    
    33 33
     import GHC.Internal.Word (Word8(..))
    

  • libraries/base/src/GHC/Num.hs
    1 1
     {-# LANGUAGE MagicHash #-}
    
    2 2
     {-# OPTIONS_HADDOCK not-home #-}
    
    3
    +-- don't warn that some but not all of Integer and Natural are deprecated
    
    4
    +{-# OPTIONS_GHC -Wno-incomplete-export-warnings -Wno-duplicate-exports #-}
    
    3 5
     
    
    4 6
     -- |
    
    5 7
     -- Module      :  GHC.Num
    
    ... ... @@ -15,191 +17,370 @@
    15 17
     
    
    16 18
     module GHC.Num
    
    17 19
        ( Num(..)
    
    20
    +   , Integer
    
    21
    +   , Natural
    
    18 22
        , subtract
    
    19 23
        , quotRemInteger
    
    20
    -   , integerFromNatural
    
    21
    -   , integerToNaturalClamp
    
    22
    -   , integerToNaturalThrow
    
    23
    -   , integerToNatural
    
    24
    -   , integerToWord#
    
    25
    -   , integerToInt#
    
    26
    -   , integerToWord64#
    
    27
    -   , integerToInt64#
    
    28
    -   , integerAdd
    
    29
    -   , integerMul
    
    30
    -   , integerSub
    
    31
    -   , integerNegate
    
    32
    -   , integerAbs
    
    33
    -   , integerPopCount#
    
    34
    -   , integerQuot
    
    35
    -   , integerRem
    
    36
    -   , integerDiv
    
    37
    -   , integerMod
    
    38
    -   , integerDivMod#
    
    39
    -   , integerQuotRem#
    
    40
    -   , integerEncodeFloat#
    
    41
    -   , integerEncodeDouble#
    
    42
    -   , integerGcd
    
    43
    -   , integerLcm
    
    44
    -   , integerAnd
    
    45
    -   , integerOr
    
    46
    -   , integerXor
    
    47
    -   , integerComplement
    
    48
    -   , integerBit#
    
    49
    -   , integerTestBit#
    
    50
    -   , integerShiftL#
    
    51
    -   , integerShiftR#
    
    52
    -   , integerFromWord#
    
    53
    -   , integerFromWord64#
    
    54
    -   , integerFromInt64#
    
    55
    -   , Integer(..)
    
    56
    -   , integerBit
    
    57
    -   , integerCheck
    
    58
    -   , integerCheck#
    
    59
    -   , integerCompare
    
    60
    -   , integerDecodeDouble#
    
    61
    -   , integerDivMod
    
    62
    -   , integerEncodeDouble
    
    63
    -   , integerEq
    
    64
    -   , integerEq#
    
    65
    -   , integerFromAddr
    
    66
    -   , integerFromAddr#
    
    67
    -   , integerFromBigNat#
    
    68
    -   , integerFromBigNatNeg#
    
    69
    -   , integerFromBigNatSign#
    
    70
    -   , integerFromByteArray
    
    71
    -   , integerFromByteArray#
    
    72
    -   , integerFromInt
    
    73
    -   , integerFromInt#
    
    24
    +   , integerToWord
    
    74 25
        , integerFromWord
    
    75
    -   , integerFromWordList
    
    76
    -   , integerFromWordNeg#
    
    77
    -   , integerFromWordSign#
    
    78
    -   , integerGcde
    
    79
    -   , integerGcde#
    
    80
    -   , integerGe
    
    81
    -   , integerGe#
    
    82
    -   , integerGt
    
    83
    -   , integerGt#
    
    84
    -   , integerIsNegative
    
    85
    -   , integerIsNegative#
    
    86
    -   , integerIsOne
    
    87
    -   , integerIsPowerOf2#
    
    88
    -   , integerIsZero
    
    89
    -   , integerLe
    
    90
    -   , integerLe#
    
    91
    -   , integerLog2
    
    92
    -   , integerLog2#
    
    93
    -   , integerLogBase
    
    94
    -   , integerLogBase#
    
    95
    -   , integerLogBaseWord
    
    96
    -   , integerLogBaseWord#
    
    97
    -   , integerLt
    
    98
    -   , integerLt#
    
    99
    -   , integerNe
    
    100
    -   , integerNe#
    
    101
    -   , integerOne
    
    102
    -   , integerPowMod#
    
    103
    -   , integerQuotRem
    
    104
    -   , integerRecipMod#
    
    105
    -   , integerShiftL
    
    106
    -   , integerShiftR
    
    107
    -   , integerSignum
    
    108
    -   , integerSignum#
    
    109
    -   , integerSizeInBase#
    
    110
    -   , integerSqr
    
    111
    -   , integerTestBit
    
    112
    -   , integerToAddr
    
    113
    -   , integerToAddr#
    
    114
    -   , integerToBigNatClamp#
    
    115
    -   , integerToBigNatSign#
    
    116 26
        , integerToInt
    
    117
    -   , integerToMutableByteArray
    
    118
    -   , integerToMutableByteArray#
    
    119
    -   , integerToWord
    
    120
    -   , integerZero
    
    121
    -   , naturalToWord#
    
    122
    -   , naturalPopCount#
    
    123
    -   , naturalShiftR#
    
    124
    -   , naturalShiftL#
    
    125
    -   , naturalAdd
    
    126
    -   , naturalSub
    
    127
    -   , naturalSubThrow
    
    128
    -   , naturalSubUnsafe
    
    129
    -   , naturalMul
    
    130
    -   , naturalQuotRem#
    
    131
    -   , naturalQuot
    
    132
    -   , naturalRem
    
    133
    -   , naturalAnd
    
    134
    -   , naturalAndNot
    
    135
    -   , naturalOr
    
    136
    -   , naturalXor
    
    137
    -   , naturalTestBit#
    
    138
    -   , naturalBit#
    
    139
    -   , naturalGcd
    
    140
    -   , naturalLcm
    
    141
    -   , naturalLog2#
    
    142
    -   , naturalLogBaseWord#
    
    143
    -   , naturalLogBase#
    
    144
    -   , naturalPowMod
    
    145
    -   , naturalSizeInBase#
    
    146
    -   , Natural(..)
    
    147
    -   , naturalBit
    
    148
    -   , naturalCheck
    
    149
    -   , naturalCheck#
    
    150
    -   , naturalClearBit
    
    151
    -   , naturalClearBit#
    
    152
    -   , naturalCompare
    
    153
    -   , naturalComplementBit
    
    154
    -   , naturalComplementBit#
    
    155
    -   , naturalEncodeDouble#
    
    156
    -   , naturalEncodeFloat#
    
    157
    -   , naturalEq
    
    158
    -   , naturalEq#
    
    159
    -   , naturalFromAddr
    
    160
    -   , naturalFromAddr#
    
    161
    -   , naturalFromBigNat#
    
    162
    -   , naturalFromByteArray#
    
    163
    -   , naturalFromWord
    
    164
    -   , naturalFromWord#
    
    165
    -   , naturalFromWord2#
    
    166
    -   , naturalFromWordList
    
    167
    -   , naturalGe
    
    168
    -   , naturalGe#
    
    169
    -   , naturalGt
    
    170
    -   , naturalGt#
    
    171
    -   , naturalIsOne
    
    172
    -   , naturalIsPowerOf2#
    
    173
    -   , naturalIsZero
    
    174
    -   , naturalLe
    
    175
    -   , naturalLe#
    
    176
    -   , naturalLog2
    
    177
    -   , naturalLogBase
    
    178
    -   , naturalLogBaseWord
    
    179
    -   , naturalLt
    
    180
    -   , naturalLt#
    
    181
    -   , naturalNe
    
    182
    -   , naturalNe#
    
    183
    -   , naturalNegate
    
    184
    -   , naturalOne
    
    185
    -   , naturalPopCount
    
    186
    -   , naturalQuotRem
    
    187
    -   , naturalSetBit
    
    188
    -   , naturalSetBit#
    
    189
    -   , naturalShiftL
    
    190
    -   , naturalShiftR
    
    191
    -   , naturalSignum
    
    192
    -   , naturalSqr
    
    193
    -   , naturalTestBit
    
    194
    -   , naturalToAddr
    
    195
    -   , naturalToAddr#
    
    196
    -   , naturalToBigNat#
    
    197
    -   , naturalToMutableByteArray#
    
    198
    -   , naturalToWord
    
    199
    -   , naturalToWordClamp
    
    200
    -   , naturalToWordClamp#
    
    201
    -   , naturalToWordMaybe#
    
    202
    -   , naturalZero
    
    27
    +   , integerFromInt
    
    28
    +   , integerToNatural
    
    29
    +   , integerFromNatural
    
    30
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    31
    +     Integer(IN, IP, IS)
    
    32
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    33
    +     Natural(NS, NB)
    
    34
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    35
    +     integerToNaturalClamp
    
    36
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    37
    +     integerToNaturalThrow
    
    38
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    39
    +     integerToWord#
    
    40
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    41
    +     integerToInt#
    
    42
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    43
    +     integerToWord64#
    
    44
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    45
    +     integerToInt64#
    
    46
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    47
    +     integerAdd
    
    48
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    49
    +     integerMul
    
    50
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    51
    +     integerSub
    
    52
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    53
    +     integerNegate
    
    54
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    55
    +     integerAbs
    
    56
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    57
    +     integerPopCount#
    
    58
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    59
    +     integerQuot
    
    60
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    61
    +     integerRem
    
    62
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    63
    +     integerDiv
    
    64
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    65
    +     integerMod
    
    66
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    67
    +     integerDivMod#
    
    68
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    69
    +     integerQuotRem#
    
    70
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    71
    +     integerEncodeFloat#
    
    72
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    73
    +     integerEncodeDouble#
    
    74
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    75
    +     integerGcd
    
    76
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    77
    +     integerLcm
    
    78
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    79
    +     integerAnd
    
    80
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    81
    +     integerOr
    
    82
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    83
    +     integerXor
    
    84
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    85
    +     integerComplement
    
    86
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    87
    +     integerBit#
    
    88
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    89
    +     integerTestBit#
    
    90
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    91
    +     integerShiftL#
    
    92
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    93
    +     integerShiftR#
    
    94
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    95
    +     integerFromWord#
    
    96
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    97
    +     integerFromWord64#
    
    98
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    99
    +     integerFromInt64#
    
    100
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    101
    +     integerBit
    
    102
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    103
    +     integerCheck
    
    104
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    105
    +     integerCheck#
    
    106
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    107
    +     integerCompare
    
    108
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    109
    +     integerDecodeDouble#
    
    110
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    111
    +     integerDivMod
    
    112
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    113
    +     integerEncodeDouble
    
    114
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    115
    +     integerEq
    
    116
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    117
    +     integerEq#
    
    118
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    119
    +     integerFromAddr
    
    120
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    121
    +     integerFromAddr#
    
    122
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    123
    +     integerFromBigNat#
    
    124
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    125
    +     integerFromBigNatNeg#
    
    126
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    127
    +     integerFromBigNatSign#
    
    128
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    129
    +     integerFromByteArray
    
    130
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    131
    +     integerFromByteArray#
    
    132
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    133
    +     integerFromInt#
    
    134
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    135
    +     integerFromWordList
    
    136
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    137
    +     integerFromWordNeg#
    
    138
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    139
    +     integerFromWordSign#
    
    140
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    141
    +     integerGcde
    
    142
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    143
    +     integerGcde#
    
    144
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    145
    +     integerGe
    
    146
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    147
    +     integerGe#
    
    148
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    149
    +     integerGt
    
    150
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    151
    +     integerGt#
    
    152
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    153
    +     integerIsNegative
    
    154
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    155
    +     integerIsNegative#
    
    156
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    157
    +     integerIsOne
    
    158
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    159
    +     integerIsPowerOf2#
    
    160
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    161
    +     integerIsZero
    
    162
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    163
    +     integerLe
    
    164
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    165
    +     integerLe#
    
    166
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    167
    +     integerLog2
    
    168
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    169
    +     integerLog2#
    
    170
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    171
    +     integerLogBase
    
    172
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    173
    +     integerLogBase#
    
    174
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    175
    +     integerLogBaseWord
    
    176
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    177
    +     integerLogBaseWord#
    
    178
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    179
    +     integerLt
    
    180
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    181
    +     integerLt#
    
    182
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    183
    +     integerNe
    
    184
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    185
    +     integerNe#
    
    186
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    187
    +     integerOne
    
    188
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    189
    +     integerPowMod#
    
    190
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    191
    +     integerQuotRem
    
    192
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    193
    +     integerRecipMod#
    
    194
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    195
    +     integerShiftL
    
    196
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    197
    +     integerShiftR
    
    198
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    199
    +     integerSignum
    
    200
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    201
    +     integerSignum#
    
    202
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    203
    +     integerSizeInBase#
    
    204
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    205
    +     integerSqr
    
    206
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    207
    +     integerTestBit
    
    208
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    209
    +     integerToAddr
    
    210
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    211
    +     integerToAddr#
    
    212
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    213
    +     integerToBigNatClamp#
    
    214
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    215
    +     integerToBigNatSign#
    
    216
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    217
    +     integerToMutableByteArray
    
    218
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    219
    +     integerToMutableByteArray#
    
    220
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    221
    +     integerZero
    
    222
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    223
    +     naturalToWord#
    
    224
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    225
    +     naturalPopCount#
    
    226
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    227
    +     naturalShiftR#
    
    228
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    229
    +     naturalShiftL#
    
    230
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    231
    +     naturalAdd
    
    232
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    233
    +     naturalSub
    
    234
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    235
    +     naturalSubThrow
    
    236
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    237
    +     naturalSubUnsafe
    
    238
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    239
    +     naturalMul
    
    240
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    241
    +     naturalQuotRem#
    
    242
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    243
    +     naturalQuot
    
    244
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    245
    +     naturalRem
    
    246
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    247
    +     naturalAnd
    
    248
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    249
    +     naturalAndNot
    
    250
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    251
    +     naturalOr
    
    252
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    253
    +     naturalXor
    
    254
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    255
    +     naturalTestBit#
    
    256
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    257
    +     naturalBit#
    
    258
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    259
    +     naturalGcd
    
    260
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    261
    +     naturalLcm
    
    262
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    263
    +     naturalLog2#
    
    264
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    265
    +     naturalLogBaseWord#
    
    266
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    267
    +     naturalLogBase#
    
    268
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    269
    +     naturalPowMod
    
    270
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    271
    +     naturalSizeInBase#
    
    272
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    273
    +     naturalBit
    
    274
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    275
    +     naturalCheck
    
    276
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    277
    +     naturalCheck#
    
    278
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    279
    +     naturalClearBit
    
    280
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    281
    +     naturalClearBit#
    
    282
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    283
    +     naturalCompare
    
    284
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    285
    +     naturalComplementBit
    
    286
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    287
    +     naturalComplementBit#
    
    288
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    289
    +     naturalEncodeDouble#
    
    290
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    291
    +     naturalEncodeFloat#
    
    292
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    293
    +     naturalEq
    
    294
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    295
    +     naturalEq#
    
    296
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    297
    +     naturalFromAddr
    
    298
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    299
    +     naturalFromAddr#
    
    300
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    301
    +     naturalFromBigNat#
    
    302
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    303
    +     naturalFromByteArray#
    
    304
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    305
    +     naturalFromWord
    
    306
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    307
    +     naturalFromWord#
    
    308
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    309
    +     naturalFromWord2#
    
    310
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    311
    +     naturalFromWordList
    
    312
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    313
    +     naturalGe
    
    314
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    315
    +     naturalGe#
    
    316
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    317
    +     naturalGt
    
    318
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    319
    +     naturalGt#
    
    320
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    321
    +     naturalIsOne
    
    322
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    323
    +     naturalIsPowerOf2#
    
    324
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    325
    +     naturalIsZero
    
    326
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    327
    +     naturalLe
    
    328
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    329
    +     naturalLe#
    
    330
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    331
    +     naturalLog2
    
    332
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    333
    +     naturalLogBase
    
    334
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    335
    +     naturalLogBaseWord
    
    336
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    337
    +     naturalLt
    
    338
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    339
    +     naturalLt#
    
    340
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    341
    +     naturalNe
    
    342
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    343
    +     naturalNe#
    
    344
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    345
    +     naturalNegate
    
    346
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    347
    +     naturalOne
    
    348
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    349
    +     naturalPopCount
    
    350
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    351
    +     naturalQuotRem
    
    352
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    353
    +     naturalSetBit
    
    354
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    355
    +     naturalSetBit#
    
    356
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    357
    +     naturalShiftL
    
    358
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    359
    +     naturalShiftR
    
    360
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    361
    +     naturalSignum
    
    362
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    363
    +     naturalSqr
    
    364
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    365
    +     naturalTestBit
    
    366
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    367
    +     naturalToAddr
    
    368
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    369
    +     naturalToAddr#
    
    370
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    371
    +     naturalToBigNat#
    
    372
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    373
    +     naturalToMutableByteArray#
    
    374
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    375
    +     naturalToWord
    
    376
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    377
    +     naturalToWordClamp
    
    378
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    379
    +     naturalToWordClamp#
    
    380
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    381
    +     naturalToWordMaybe#
    
    382
    +   , {-# DEPRECATED ["The internals of big numbers will be removed in 4.24.", "Use ghc-bignum instead."] #-}
    
    383
    +     naturalZero
    
    203 384
        )
    
    204 385
     where
    
    205 386
     
    

  • libraries/base/src/GHC/Num/BigNat.hs deleted
    1
    -module GHC.Num.BigNat
    
    2
    -  ( module GHC.Internal.Bignum.BigNat
    
    3
    -  )
    
    4
    -where
    
    5
    -
    
    6
    -import GHC.Internal.Bignum.BigNat

  • libraries/base/src/GHC/Num/Integer.hs deleted
    1
    -module GHC.Num.Integer
    
    2
    -  ( module GHC.Internal.Bignum.Integer
    
    3
    -  )
    
    4
    -where
    
    5
    -
    
    6
    -import GHC.Internal.Bignum.Integer

  • libraries/base/src/GHC/Num/Natural.hs deleted
    1
    -module GHC.Num.Natural
    
    2
    -  ( module GHC.Internal.Bignum.Natural
    
    3
    -  )
    
    4
    -where
    
    5
    -
    
    6
    -import GHC.Internal.Bignum.Natural

  • libraries/base/src/System/CPUTime/Utils.hs
    ... ... @@ -8,7 +8,7 @@ module System.CPUTime.Utils
    8 8
         ) where
    
    9 9
     
    
    10 10
     import GHC.Internal.Foreign.C.Types
    
    11
    -import GHC.Num.Integer (Integer)
    
    11
    +import GHC.Internal.Bignum.Integer (Integer)
    
    12 12
     import GHC.Internal.Real (fromIntegral)
    
    13 13
     
    
    14 14
     cClockToInteger :: CClock -> Integer
    

  • libraries/ghc-bignum/ghc-bignum.cabal
    ... ... @@ -10,10 +10,8 @@ bug-reports: https://gitlab.haskell.org/ghc/ghc/issues/new
    10 10
     category:            Numeric, Algebra, GHC
    
    11 11
     build-type:          Simple
    
    12 12
     description:
    
    13
    -    This package used to provide the low-level implementation of the standard
    
    13
    +    This package provides the low-level implementation of the standard
    
    14 14
         'BigNat', 'Natural' and 'Integer' types.
    
    15
    -    Use `base:GHC.Num.{Integer,Natural,BigNat}` instead or other modules from
    
    16
    -    `ghc-internal`.
    
    17 15
     
    
    18 16
     extra-source-files:
    
    19 17
         changelog.md
    
    ... ... @@ -40,13 +38,6 @@ library
    40 38
         , GHC.Internal.Bignum.Backend          as GHC.Num.Backend
    
    41 39
         , GHC.Internal.Bignum.Backend.Selected as GHC.Num.Backend.Selected
    
    42 40
         , GHC.Internal.Bignum.Backend.Native   as GHC.Num.Backend.Native
    
    43
    -    -- reexport from base
    
    44
    -    -- We can't reexport these modules from ghc-internal otherwise we get
    
    45
    -    -- ambiguity between:
    
    46
    -    --   ghc-bignum:GHC.Num.X
    
    47
    -    --   base:GHC.Num.X
    
    48
    -    -- we should probably just deprecate ghc-bignum and encourage users to use
    
    49
    -    -- exports from base instead.
    
    50
    -    , GHC.Num.BigNat
    
    51
    -    , GHC.Num.Natural
    
    52
    -    , GHC.Num.Integer
    41
    +    , GHC.Internal.Bignum.BigNat           as GHC.Num.BigNat
    
    42
    +    , GHC.Internal.Bignum.Natural          as GHC.Num.Natural
    
    43
    +    , GHC.Internal.Bignum.Integer          as GHC.Num.Integer

  • libraries/ghc-experimental/src/GHC/TypeNats/Experimental.hs
    ... ... @@ -12,7 +12,7 @@ module GHC.TypeNats.Experimental (
    12 12
     ) where
    
    13 13
     
    
    14 14
     import GHC.Internal.TypeNats
    
    15
    -import GHC.Num.Natural (naturalLog2)
    
    15
    +import GHC.Internal.Bignum.Natural (naturalLog2)
    
    16 16
     
    
    17 17
     plusSNat :: SNat n -> SNat m -> SNat (n + m)
    
    18 18
     plusSNat (UnsafeSNat n) (UnsafeSNat m) = UnsafeSNat (n + m)
    

  • testsuite/tests/interface-stability/base-exports.stdout
    ... ... @@ -8550,340 +8550,6 @@ module GHC.Num where
    8550 8550
       quotRemInteger :: Integer -> Integer -> (# Integer, Integer #)
    
    8551 8551
       subtract :: forall a. Num a => a -> a -> a
    
    8552 8552
     
    
    8553
    -module GHC.Num.BigNat where
    
    8554
    -  -- Safety: None
    
    8555
    -  type BigNat :: *
    
    8556
    -  data BigNat = BN# {unBigNat :: BigNat#}
    
    8557
    -  type BigNat# :: GHC.Internal.Types.UnliftedType
    
    8558
    -  type BigNat# = GHC.Internal.Bignum.WordArray.WordArray#
    
    8559
    -  bigNatAdd :: BigNat# -> BigNat# -> BigNat#
    
    8560
    -  bigNatAddWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
    
    8561
    -  bigNatAddWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8562
    -  bigNatAnd :: BigNat# -> BigNat# -> BigNat#
    
    8563
    -  bigNatAndInt# :: BigNat# -> GHC.Internal.Prim.Int# -> BigNat#
    
    8564
    -  bigNatAndNot :: BigNat# -> BigNat# -> BigNat#
    
    8565
    -  bigNatAndNotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8566
    -  bigNatAndWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8567
    -  bigNatBit :: GHC.Internal.Types.Word -> BigNat#
    
    8568
    -  bigNatBit# :: GHC.Internal.Prim.Word# -> BigNat#
    
    8569
    -  bigNatCheck :: BigNat# -> GHC.Internal.Types.Bool
    
    8570
    -  bigNatCheck# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8571
    -  bigNatClearBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8572
    -  bigNatCompare :: BigNat# -> BigNat# -> GHC.Internal.Types.Ordering
    
    8573
    -  bigNatCompareWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Ordering
    
    8574
    -  bigNatCompareWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Types.Ordering
    
    8575
    -  bigNatComplementBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8576
    -  bigNatCtz :: BigNat# -> GHC.Internal.Types.Word
    
    8577
    -  bigNatCtz# :: BigNat# -> GHC.Internal.Prim.Word#
    
    8578
    -  bigNatCtzWord :: BigNat# -> GHC.Internal.Types.Word
    
    8579
    -  bigNatCtzWord# :: BigNat# -> GHC.Internal.Prim.Word#
    
    8580
    -  bigNatEncodeDouble# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double#
    
    8581
    -  bigNatEq :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
    
    8582
    -  bigNatEq# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8583
    -  bigNatEqWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8584
    -  bigNatFromAbsInt# :: GHC.Internal.Prim.Int# -> BigNat#
    
    8585
    -  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# #)
    
    8586
    -  bigNatFromAddrBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
    
    8587
    -  bigNatFromAddrLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
    
    8588
    -  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# #)
    
    8589
    -  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# #)
    
    8590
    -  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# #)
    
    8591
    -  bigNatFromWord :: GHC.Internal.Types.Word -> BigNat#
    
    8592
    -  bigNatFromWord# :: GHC.Internal.Prim.Word# -> BigNat#
    
    8593
    -  bigNatFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8594
    -  bigNatFromWord64# :: GHC.Internal.Prim.Word64# -> BigNat#
    
    8595
    -  bigNatFromWordArray :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat
    
    8596
    -  bigNatFromWordArray# :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8597
    -  bigNatFromWordList :: [GHC.Internal.Types.Word] -> BigNat#
    
    8598
    -  bigNatFromWordList# :: [GHC.Internal.Types.Word] -> GHC.Internal.Bignum.WordArray.WordArray#
    
    8599
    -  bigNatFromWordListUnsafe :: [GHC.Internal.Types.Word] -> BigNat#
    
    8600
    -  bigNatGcd :: BigNat# -> BigNat# -> BigNat#
    
    8601
    -  bigNatGcdWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
    
    8602
    -  bigNatGe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
    
    8603
    -  bigNatGe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8604
    -  bigNatGt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
    
    8605
    -  bigNatGt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8606
    -  bigNatGtWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
    
    8607
    -  bigNatGtWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8608
    -  bigNatIndex :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Types.Word
    
    8609
    -  bigNatIndex# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word#
    
    8610
    -  bigNatIsOne :: BigNat# -> GHC.Internal.Types.Bool
    
    8611
    -  bigNatIsOne# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8612
    -  bigNatIsPowerOf2# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #)
    
    8613
    -  bigNatIsTwo :: BigNat# -> GHC.Internal.Types.Bool
    
    8614
    -  bigNatIsTwo# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8615
    -  bigNatIsZero :: BigNat# -> GHC.Internal.Types.Bool
    
    8616
    -  bigNatIsZero# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8617
    -  bigNatLcm :: BigNat# -> BigNat# -> BigNat#
    
    8618
    -  bigNatLcmWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8619
    -  bigNatLcmWordWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8620
    -  bigNatLe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
    
    8621
    -  bigNatLe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8622
    -  bigNatLeWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
    
    8623
    -  bigNatLeWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8624
    -  bigNatLog2 :: BigNat# -> GHC.Internal.Types.Word
    
    8625
    -  bigNatLog2# :: BigNat# -> GHC.Internal.Prim.Word#
    
    8626
    -  bigNatLogBase :: BigNat# -> BigNat# -> GHC.Internal.Types.Word
    
    8627
    -  bigNatLogBase# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word#
    
    8628
    -  bigNatLogBaseWord :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word
    
    8629
    -  bigNatLogBaseWord# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word#
    
    8630
    -  bigNatLt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
    
    8631
    -  bigNatLt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8632
    -  bigNatMul :: BigNat# -> BigNat# -> BigNat#
    
    8633
    -  bigNatMulWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
    
    8634
    -  bigNatMulWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8635
    -  bigNatNe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
    
    8636
    -  bigNatNe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8637
    -  bigNatOne :: BigNat
    
    8638
    -  bigNatOne# :: (# #) -> BigNat#
    
    8639
    -  bigNatOr :: BigNat# -> BigNat# -> BigNat#
    
    8640
    -  bigNatOrWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8641
    -  bigNatPopCount :: BigNat# -> GHC.Internal.Types.Word
    
    8642
    -  bigNatPopCount# :: BigNat# -> GHC.Internal.Prim.Word#
    
    8643
    -  bigNatPowMod :: BigNat# -> BigNat# -> BigNat# -> BigNat#
    
    8644
    -  bigNatPowModWord# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
    
    8645
    -  bigNatQuot :: BigNat# -> BigNat# -> BigNat#
    
    8646
    -  bigNatQuotRem# :: BigNat# -> BigNat# -> (# BigNat#, BigNat# #)
    
    8647
    -  bigNatQuotRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# BigNat#, GHC.Internal.Prim.Word# #)
    
    8648
    -  bigNatQuotWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
    
    8649
    -  bigNatQuotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8650
    -  bigNatRem :: BigNat# -> BigNat# -> BigNat#
    
    8651
    -  bigNatRemWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word
    
    8652
    -  bigNatRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
    
    8653
    -  bigNatSetBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8654
    -  bigNatShiftL :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
    
    8655
    -  bigNatShiftL# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8656
    -  bigNatShiftR :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
    
    8657
    -  bigNatShiftR# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8658
    -  bigNatShiftRNeg# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8659
    -  bigNatSize :: BigNat# -> GHC.Internal.Types.Word
    
    8660
    -  bigNatSize# :: BigNat# -> GHC.Internal.Prim.Int#
    
    8661
    -  bigNatSizeInBase :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word
    
    8662
    -  bigNatSizeInBase# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word#
    
    8663
    -  bigNatSqr :: BigNat# -> BigNat#
    
    8664
    -  bigNatSub :: BigNat# -> BigNat# -> (# (# #) | BigNat# #)
    
    8665
    -  bigNatSubUnsafe :: BigNat# -> BigNat# -> BigNat#
    
    8666
    -  bigNatSubWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# (# #) | BigNat# #)
    
    8667
    -  bigNatSubWordUnsafe :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
    
    8668
    -  bigNatSubWordUnsafe# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8669
    -  bigNatTestBit :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
    
    8670
    -  bigNatTestBit# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8671
    -  bigNatToAddr :: BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
    
    8672
    -  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# #)
    
    8673
    -  bigNatToAddrBE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
    
    8674
    -  bigNatToAddrLE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
    
    8675
    -  bigNatToInt :: BigNat# -> GHC.Internal.Types.Int
    
    8676
    -  bigNatToInt# :: BigNat# -> GHC.Internal.Prim.Int#
    
    8677
    -  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# #)
    
    8678
    -  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# #)
    
    8679
    -  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# #)
    
    8680
    -  bigNatToWord :: BigNat# -> GHC.Internal.Types.Word
    
    8681
    -  bigNatToWord# :: BigNat# -> GHC.Internal.Prim.Word#
    
    8682
    -  bigNatToWord64# :: BigNat# -> GHC.Internal.Prim.Word64#
    
    8683
    -  bigNatToWordList :: BigNat# -> [GHC.Internal.Types.Word]
    
    8684
    -  bigNatToWordMaybe# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #)
    
    8685
    -  bigNatXor :: BigNat# -> BigNat# -> BigNat#
    
    8686
    -  bigNatXorWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8687
    -  bigNatZero :: BigNat
    
    8688
    -  bigNatZero# :: (# #) -> BigNat#
    
    8689
    -  gcdInt :: GHC.Internal.Types.Int -> GHC.Internal.Types.Int -> GHC.Internal.Types.Int
    
    8690
    -  gcdInt# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int#
    
    8691
    -  gcdWord :: GHC.Internal.Types.Word -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word
    
    8692
    -  gcdWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
    
    8693
    -  powModWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
    
    8694
    -  raiseDivZero_BigNat :: (# #) -> BigNat#
    
    8695
    -
    
    8696
    -module GHC.Num.Integer where
    
    8697
    -  -- Safety: None
    
    8698
    -  type Integer :: *
    
    8699
    -  data Integer = IS GHC.Internal.Prim.Int# | IP GHC.Internal.Prim.ByteArray# | IN GHC.Internal.Prim.ByteArray#
    
    8700
    -  integerAbs :: Integer -> Integer
    
    8701
    -  integerAdd :: Integer -> Integer -> Integer
    
    8702
    -  integerAnd :: Integer -> Integer -> Integer
    
    8703
    -  integerBit :: GHC.Internal.Types.Word -> Integer
    
    8704
    -  integerBit# :: GHC.Internal.Prim.Word# -> Integer
    
    8705
    -  integerCheck :: Integer -> GHC.Internal.Types.Bool
    
    8706
    -  integerCheck# :: Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8707
    -  integerCompare :: Integer -> Integer -> GHC.Internal.Types.Ordering
    
    8708
    -  integerComplement :: Integer -> Integer
    
    8709
    -  integerDecodeDouble# :: GHC.Internal.Prim.Double# -> (# Integer, GHC.Internal.Prim.Int# #)
    
    8710
    -  integerDiv :: Integer -> Integer -> Integer
    
    8711
    -  integerDivMod :: Integer -> Integer -> (Integer, Integer)
    
    8712
    -  integerDivMod# :: Integer -> Integer -> (# Integer, Integer #)
    
    8713
    -  integerEncodeDouble :: Integer -> GHC.Internal.Types.Int -> GHC.Internal.Types.Double
    
    8714
    -  integerEncodeDouble# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double#
    
    8715
    -  integerEncodeFloat# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float#
    
    8716
    -  integerEq :: Integer -> Integer -> GHC.Internal.Types.Bool
    
    8717
    -  integerEq# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8718
    -  integerFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Integer
    
    8719
    -  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 #)
    
    8720
    -  integerFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer
    
    8721
    -  integerFromBigNatNeg# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer
    
    8722
    -  integerFromBigNatSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Bignum.BigNat.BigNat# -> Integer
    
    8723
    -  integerFromByteArray :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> Integer
    
    8724
    -  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 #)
    
    8725
    -  integerFromInt :: GHC.Internal.Types.Int -> Integer
    
    8726
    -  integerFromInt# :: GHC.Internal.Prim.Int# -> Integer
    
    8727
    -  integerFromInt64# :: GHC.Internal.Prim.Int64# -> Integer
    
    8728
    -  integerFromNatural :: GHC.Internal.Bignum.Natural.Natural -> Integer
    
    8729
    -  integerFromWord :: GHC.Internal.Types.Word -> Integer
    
    8730
    -  integerFromWord# :: GHC.Internal.Prim.Word# -> Integer
    
    8731
    -  integerFromWord64# :: GHC.Internal.Prim.Word64# -> Integer
    
    8732
    -  integerFromWordList :: GHC.Internal.Types.Bool -> [GHC.Internal.Types.Word] -> Integer
    
    8733
    -  integerFromWordNeg# :: GHC.Internal.Prim.Word# -> Integer
    
    8734
    -  integerFromWordSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word# -> Integer
    
    8735
    -  integerGcd :: Integer -> Integer -> Integer
    
    8736
    -  integerGcde :: Integer -> Integer -> (Integer, Integer, Integer)
    
    8737
    -  integerGcde# :: Integer -> Integer -> (# Integer, Integer, Integer #)
    
    8738
    -  integerGe :: Integer -> Integer -> GHC.Internal.Types.Bool
    
    8739
    -  integerGe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8740
    -  integerGt :: Integer -> Integer -> GHC.Internal.Types.Bool
    
    8741
    -  integerGt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8742
    -  integerIsNegative :: Integer -> GHC.Internal.Types.Bool
    
    8743
    -  integerIsNegative# :: Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8744
    -  integerIsOne :: Integer -> GHC.Internal.Types.Bool
    
    8745
    -  integerIsPowerOf2# :: Integer -> (# (# #) | GHC.Internal.Prim.Word# #)
    
    8746
    -  integerIsZero :: Integer -> GHC.Internal.Types.Bool
    
    8747
    -  integerLcm :: Integer -> Integer -> Integer
    
    8748
    -  integerLe :: Integer -> Integer -> GHC.Internal.Types.Bool
    
    8749
    -  integerLe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8750
    -  integerLog2 :: Integer -> GHC.Internal.Types.Word
    
    8751
    -  integerLog2# :: Integer -> GHC.Internal.Prim.Word#
    
    8752
    -  integerLogBase :: Integer -> Integer -> GHC.Internal.Types.Word
    
    8753
    -  integerLogBase# :: Integer -> Integer -> GHC.Internal.Prim.Word#
    
    8754
    -  integerLogBaseWord :: GHC.Internal.Types.Word -> Integer -> GHC.Internal.Types.Word
    
    8755
    -  integerLogBaseWord# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word#
    
    8756
    -  integerLt :: Integer -> Integer -> GHC.Internal.Types.Bool
    
    8757
    -  integerLt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8758
    -  integerMod :: Integer -> Integer -> Integer
    
    8759
    -  integerMul :: Integer -> Integer -> Integer
    
    8760
    -  integerNe :: Integer -> Integer -> GHC.Internal.Types.Bool
    
    8761
    -  integerNe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8762
    -  integerNegate :: Integer -> Integer
    
    8763
    -  integerOne :: Integer
    
    8764
    -  integerOr :: Integer -> Integer -> Integer
    
    8765
    -  integerPopCount# :: Integer -> GHC.Internal.Prim.Int#
    
    8766
    -  integerPowMod# :: Integer -> Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #)
    
    8767
    -  integerQuot :: Integer -> Integer -> Integer
    
    8768
    -  integerQuotRem :: Integer -> Integer -> (Integer, Integer)
    
    8769
    -  integerQuotRem# :: Integer -> Integer -> (# Integer, Integer #)
    
    8770
    -  integerRecipMod# :: Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #)
    
    8771
    -  integerRem :: Integer -> Integer -> Integer
    
    8772
    -  integerShiftL :: Integer -> GHC.Internal.Types.Word -> Integer
    
    8773
    -  integerShiftL# :: Integer -> GHC.Internal.Prim.Word# -> Integer
    
    8774
    -  integerShiftR :: Integer -> GHC.Internal.Types.Word -> Integer
    
    8775
    -  integerShiftR# :: Integer -> GHC.Internal.Prim.Word# -> Integer
    
    8776
    -  integerSignum :: Integer -> Integer
    
    8777
    -  integerSignum# :: Integer -> GHC.Internal.Prim.Int#
    
    8778
    -  integerSizeInBase# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word#
    
    8779
    -  integerSqr :: Integer -> Integer
    
    8780
    -  integerSub :: Integer -> Integer -> Integer
    
    8781
    -  integerTestBit :: Integer -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
    
    8782
    -  integerTestBit# :: Integer -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8783
    -  integerToAddr :: Integer -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
    
    8784
    -  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# #)
    
    8785
    -  integerToBigNatClamp# :: Integer -> GHC.Internal.Bignum.BigNat.BigNat#
    
    8786
    -  integerToBigNatSign# :: Integer -> (# GHC.Internal.Prim.Int#, GHC.Internal.Bignum.BigNat.BigNat# #)
    
    8787
    -  integerToInt :: Integer -> GHC.Internal.Types.Int
    
    8788
    -  integerToInt# :: Integer -> GHC.Internal.Prim.Int#
    
    8789
    -  integerToInt64# :: Integer -> GHC.Internal.Prim.Int64#
    
    8790
    -  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
    
    8791
    -  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# #)
    
    8792
    -  integerToNatural :: Integer -> GHC.Internal.Bignum.Natural.Natural
    
    8793
    -  integerToNaturalClamp :: Integer -> GHC.Internal.Bignum.Natural.Natural
    
    8794
    -  integerToNaturalThrow :: Integer -> GHC.Internal.Bignum.Natural.Natural
    
    8795
    -  integerToWord :: Integer -> GHC.Internal.Types.Word
    
    8796
    -  integerToWord# :: Integer -> GHC.Internal.Prim.Word#
    
    8797
    -  integerToWord64# :: Integer -> GHC.Internal.Prim.Word64#
    
    8798
    -  integerXor :: Integer -> Integer -> Integer
    
    8799
    -  integerZero :: Integer
    
    8800
    -
    
    8801
    -module GHC.Num.Natural where
    
    8802
    -  -- Safety: None
    
    8803
    -  type Natural :: *
    
    8804
    -  data Natural = NS GHC.Internal.Prim.Word# | NB GHC.Internal.Prim.ByteArray#
    
    8805
    -  naturalAdd :: Natural -> Natural -> Natural
    
    8806
    -  naturalAnd :: Natural -> Natural -> Natural
    
    8807
    -  naturalAndNot :: Natural -> Natural -> Natural
    
    8808
    -  naturalBit :: GHC.Internal.Types.Word -> Natural
    
    8809
    -  naturalBit# :: GHC.Internal.Prim.Word# -> Natural
    
    8810
    -  naturalCheck :: Natural -> GHC.Internal.Types.Bool
    
    8811
    -  naturalCheck# :: Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    8812
    -  naturalClearBit :: Natural -> GHC.Internal.Types.Word -> Natural
    
    8813
    -  naturalClearBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural
    
    8814
    -  naturalCompare :: Natural -> Natural -> GHC.Internal.Types.Ordering
    
    8815
    -  naturalComplementBit :: Natural -> GHC.Internal.Types.Word -> Natural
    
    8816
    -  naturalComplementBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural
    
    8817
    -  naturalEncodeDouble# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double#
    
    8818
    -  naturalEncodeFloat# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float#
    
    8819
    -  naturalEq :: Natural -> Natural -> GHC.Internal.Types.Bool
    
    8820
    -  naturalEq# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    8821
    -  naturalFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Natural
    
    8822
    -  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 #)
    
    8823
    -  naturalFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Natural
    
    8824
    -  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 #)
    
    8825
    -  naturalFromWord :: GHC.Internal.Types.Word -> Natural
    
    8826
    -  naturalFromWord# :: GHC.Internal.Prim.Word# -> Natural
    
    8827
    -  naturalFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> Natural
    
    8828
    -  naturalFromWordList :: [GHC.Internal.Types.Word] -> Natural
    
    8829
    -  naturalGcd :: Natural -> Natural -> Natural
    
    8830
    -  naturalGe :: Natural -> Natural -> GHC.Internal.Types.Bool
    
    8831
    -  naturalGe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    8832
    -  naturalGt :: Natural -> Natural -> GHC.Internal.Types.Bool
    
    8833
    -  naturalGt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    8834
    -  naturalIsOne :: Natural -> GHC.Internal.Types.Bool
    
    8835
    -  naturalIsPowerOf2# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #)
    
    8836
    -  naturalIsZero :: Natural -> GHC.Internal.Types.Bool
    
    8837
    -  naturalLcm :: Natural -> Natural -> Natural
    
    8838
    -  naturalLe :: Natural -> Natural -> GHC.Internal.Types.Bool
    
    8839
    -  naturalLe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    8840
    -  naturalLog2 :: Natural -> GHC.Internal.Types.Word
    
    8841
    -  naturalLog2# :: Natural -> GHC.Internal.Prim.Word#
    
    8842
    -  naturalLogBase :: Natural -> Natural -> GHC.Internal.Types.Word
    
    8843
    -  naturalLogBase# :: Natural -> Natural -> GHC.Internal.Prim.Word#
    
    8844
    -  naturalLogBaseWord :: GHC.Internal.Types.Word -> Natural -> GHC.Internal.Types.Word
    
    8845
    -  naturalLogBaseWord# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word#
    
    8846
    -  naturalLt :: Natural -> Natural -> GHC.Internal.Types.Bool
    
    8847
    -  naturalLt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    8848
    -  naturalMul :: Natural -> Natural -> Natural
    
    8849
    -  naturalNe :: Natural -> Natural -> GHC.Internal.Types.Bool
    
    8850
    -  naturalNe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    8851
    -  naturalNegate :: Natural -> Natural
    
    8852
    -  naturalOne :: Natural
    
    8853
    -  naturalOr :: Natural -> Natural -> Natural
    
    8854
    -  naturalPopCount :: Natural -> GHC.Internal.Types.Word
    
    8855
    -  naturalPopCount# :: Natural -> GHC.Internal.Prim.Word#
    
    8856
    -  naturalPowMod :: Natural -> Natural -> Natural -> Natural
    
    8857
    -  naturalQuot :: Natural -> Natural -> Natural
    
    8858
    -  naturalQuotRem :: Natural -> Natural -> (Natural, Natural)
    
    8859
    -  naturalQuotRem# :: Natural -> Natural -> (# Natural, Natural #)
    
    8860
    -  naturalRem :: Natural -> Natural -> Natural
    
    8861
    -  naturalSetBit :: Natural -> GHC.Internal.Types.Word -> Natural
    
    8862
    -  naturalSetBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural
    
    8863
    -  naturalShiftL :: Natural -> GHC.Internal.Types.Word -> Natural
    
    8864
    -  naturalShiftL# :: Natural -> GHC.Internal.Prim.Word# -> Natural
    
    8865
    -  naturalShiftR :: Natural -> GHC.Internal.Types.Word -> Natural
    
    8866
    -  naturalShiftR# :: Natural -> GHC.Internal.Prim.Word# -> Natural
    
    8867
    -  naturalSignum :: Natural -> Natural
    
    8868
    -  naturalSizeInBase# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word#
    
    8869
    -  naturalSqr :: Natural -> Natural
    
    8870
    -  naturalSub :: Natural -> Natural -> (# (# #) | Natural #)
    
    8871
    -  naturalSubThrow :: Natural -> Natural -> Natural
    
    8872
    -  naturalSubUnsafe :: Natural -> Natural -> Natural
    
    8873
    -  naturalTestBit :: Natural -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
    
    8874
    -  naturalTestBit# :: Natural -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8875
    -  naturalToAddr :: Natural -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
    
    8876
    -  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# #)
    
    8877
    -  naturalToBigNat# :: Natural -> GHC.Internal.Bignum.BigNat.BigNat#
    
    8878
    -  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# #)
    
    8879
    -  naturalToWord :: Natural -> GHC.Internal.Types.Word
    
    8880
    -  naturalToWord# :: Natural -> GHC.Internal.Prim.Word#
    
    8881
    -  naturalToWordClamp :: Natural -> GHC.Internal.Types.Word
    
    8882
    -  naturalToWordClamp# :: Natural -> GHC.Internal.Prim.Word#
    
    8883
    -  naturalToWordMaybe# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #)
    
    8884
    -  naturalXor :: Natural -> Natural -> Natural
    
    8885
    -  naturalZero :: Natural
    
    8886
    -
    
    8887 8553
     module GHC.OldList where
    
    8888 8554
       -- Safety: Safe
    
    8889 8555
       (!!) :: 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
    8588 8588
       quotRemInteger :: Integer -> Integer -> (# Integer, Integer #)
    
    8589 8589
       subtract :: forall a. Num a => a -> a -> a
    
    8590 8590
     
    
    8591
    -module GHC.Num.BigNat where
    
    8592
    -  -- Safety: None
    
    8593
    -  type BigNat :: *
    
    8594
    -  data BigNat = BN# {unBigNat :: BigNat#}
    
    8595
    -  type BigNat# :: GHC.Internal.Types.UnliftedType
    
    8596
    -  type BigNat# = GHC.Internal.Bignum.WordArray.WordArray#
    
    8597
    -  bigNatAdd :: BigNat# -> BigNat# -> BigNat#
    
    8598
    -  bigNatAddWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
    
    8599
    -  bigNatAddWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8600
    -  bigNatAnd :: BigNat# -> BigNat# -> BigNat#
    
    8601
    -  bigNatAndInt# :: BigNat# -> GHC.Internal.Prim.Int# -> BigNat#
    
    8602
    -  bigNatAndNot :: BigNat# -> BigNat# -> BigNat#
    
    8603
    -  bigNatAndNotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8604
    -  bigNatAndWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8605
    -  bigNatBit :: GHC.Internal.Types.Word -> BigNat#
    
    8606
    -  bigNatBit# :: GHC.Internal.Prim.Word# -> BigNat#
    
    8607
    -  bigNatCheck :: BigNat# -> GHC.Internal.Types.Bool
    
    8608
    -  bigNatCheck# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8609
    -  bigNatClearBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8610
    -  bigNatCompare :: BigNat# -> BigNat# -> GHC.Internal.Types.Ordering
    
    8611
    -  bigNatCompareWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Ordering
    
    8612
    -  bigNatCompareWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Types.Ordering
    
    8613
    -  bigNatComplementBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8614
    -  bigNatCtz :: BigNat# -> GHC.Internal.Types.Word
    
    8615
    -  bigNatCtz# :: BigNat# -> GHC.Internal.Prim.Word#
    
    8616
    -  bigNatCtzWord :: BigNat# -> GHC.Internal.Types.Word
    
    8617
    -  bigNatCtzWord# :: BigNat# -> GHC.Internal.Prim.Word#
    
    8618
    -  bigNatEncodeDouble# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double#
    
    8619
    -  bigNatEq :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
    
    8620
    -  bigNatEq# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8621
    -  bigNatEqWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8622
    -  bigNatFromAbsInt# :: GHC.Internal.Prim.Int# -> BigNat#
    
    8623
    -  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# #)
    
    8624
    -  bigNatFromAddrBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
    
    8625
    -  bigNatFromAddrLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
    
    8626
    -  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# #)
    
    8627
    -  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# #)
    
    8628
    -  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# #)
    
    8629
    -  bigNatFromWord :: GHC.Internal.Types.Word -> BigNat#
    
    8630
    -  bigNatFromWord# :: GHC.Internal.Prim.Word# -> BigNat#
    
    8631
    -  bigNatFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8632
    -  bigNatFromWord64# :: GHC.Internal.Prim.Word64# -> BigNat#
    
    8633
    -  bigNatFromWordArray :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat
    
    8634
    -  bigNatFromWordArray# :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8635
    -  bigNatFromWordList :: [GHC.Internal.Types.Word] -> BigNat#
    
    8636
    -  bigNatFromWordList# :: [GHC.Internal.Types.Word] -> GHC.Internal.Bignum.WordArray.WordArray#
    
    8637
    -  bigNatFromWordListUnsafe :: [GHC.Internal.Types.Word] -> BigNat#
    
    8638
    -  bigNatGcd :: BigNat# -> BigNat# -> BigNat#
    
    8639
    -  bigNatGcdWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
    
    8640
    -  bigNatGe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
    
    8641
    -  bigNatGe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8642
    -  bigNatGt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
    
    8643
    -  bigNatGt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8644
    -  bigNatGtWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
    
    8645
    -  bigNatGtWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8646
    -  bigNatIndex :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Types.Word
    
    8647
    -  bigNatIndex# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word#
    
    8648
    -  bigNatIsOne :: BigNat# -> GHC.Internal.Types.Bool
    
    8649
    -  bigNatIsOne# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8650
    -  bigNatIsPowerOf2# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #)
    
    8651
    -  bigNatIsTwo :: BigNat# -> GHC.Internal.Types.Bool
    
    8652
    -  bigNatIsTwo# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8653
    -  bigNatIsZero :: BigNat# -> GHC.Internal.Types.Bool
    
    8654
    -  bigNatIsZero# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8655
    -  bigNatLcm :: BigNat# -> BigNat# -> BigNat#
    
    8656
    -  bigNatLcmWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8657
    -  bigNatLcmWordWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8658
    -  bigNatLe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
    
    8659
    -  bigNatLe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8660
    -  bigNatLeWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
    
    8661
    -  bigNatLeWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8662
    -  bigNatLog2 :: BigNat# -> GHC.Internal.Types.Word
    
    8663
    -  bigNatLog2# :: BigNat# -> GHC.Internal.Prim.Word#
    
    8664
    -  bigNatLogBase :: BigNat# -> BigNat# -> GHC.Internal.Types.Word
    
    8665
    -  bigNatLogBase# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word#
    
    8666
    -  bigNatLogBaseWord :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word
    
    8667
    -  bigNatLogBaseWord# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word#
    
    8668
    -  bigNatLt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
    
    8669
    -  bigNatLt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8670
    -  bigNatMul :: BigNat# -> BigNat# -> BigNat#
    
    8671
    -  bigNatMulWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
    
    8672
    -  bigNatMulWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8673
    -  bigNatNe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
    
    8674
    -  bigNatNe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8675
    -  bigNatOne :: BigNat
    
    8676
    -  bigNatOne# :: (# #) -> BigNat#
    
    8677
    -  bigNatOr :: BigNat# -> BigNat# -> BigNat#
    
    8678
    -  bigNatOrWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8679
    -  bigNatPopCount :: BigNat# -> GHC.Internal.Types.Word
    
    8680
    -  bigNatPopCount# :: BigNat# -> GHC.Internal.Prim.Word#
    
    8681
    -  bigNatPowMod :: BigNat# -> BigNat# -> BigNat# -> BigNat#
    
    8682
    -  bigNatPowModWord# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
    
    8683
    -  bigNatQuot :: BigNat# -> BigNat# -> BigNat#
    
    8684
    -  bigNatQuotRem# :: BigNat# -> BigNat# -> (# BigNat#, BigNat# #)
    
    8685
    -  bigNatQuotRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# BigNat#, GHC.Internal.Prim.Word# #)
    
    8686
    -  bigNatQuotWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
    
    8687
    -  bigNatQuotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8688
    -  bigNatRem :: BigNat# -> BigNat# -> BigNat#
    
    8689
    -  bigNatRemWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word
    
    8690
    -  bigNatRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
    
    8691
    -  bigNatSetBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8692
    -  bigNatShiftL :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
    
    8693
    -  bigNatShiftL# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8694
    -  bigNatShiftR :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
    
    8695
    -  bigNatShiftR# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8696
    -  bigNatShiftRNeg# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8697
    -  bigNatSize :: BigNat# -> GHC.Internal.Types.Word
    
    8698
    -  bigNatSize# :: BigNat# -> GHC.Internal.Prim.Int#
    
    8699
    -  bigNatSizeInBase :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word
    
    8700
    -  bigNatSizeInBase# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word#
    
    8701
    -  bigNatSqr :: BigNat# -> BigNat#
    
    8702
    -  bigNatSub :: BigNat# -> BigNat# -> (# (# #) | BigNat# #)
    
    8703
    -  bigNatSubUnsafe :: BigNat# -> BigNat# -> BigNat#
    
    8704
    -  bigNatSubWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# (# #) | BigNat# #)
    
    8705
    -  bigNatSubWordUnsafe :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
    
    8706
    -  bigNatSubWordUnsafe# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8707
    -  bigNatTestBit :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
    
    8708
    -  bigNatTestBit# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8709
    -  bigNatToAddr :: BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
    
    8710
    -  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# #)
    
    8711
    -  bigNatToAddrBE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
    
    8712
    -  bigNatToAddrLE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
    
    8713
    -  bigNatToInt :: BigNat# -> GHC.Internal.Types.Int
    
    8714
    -  bigNatToInt# :: BigNat# -> GHC.Internal.Prim.Int#
    
    8715
    -  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# #)
    
    8716
    -  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# #)
    
    8717
    -  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# #)
    
    8718
    -  bigNatToWord :: BigNat# -> GHC.Internal.Types.Word
    
    8719
    -  bigNatToWord# :: BigNat# -> GHC.Internal.Prim.Word#
    
    8720
    -  bigNatToWord64# :: BigNat# -> GHC.Internal.Prim.Word64#
    
    8721
    -  bigNatToWordList :: BigNat# -> [GHC.Internal.Types.Word]
    
    8722
    -  bigNatToWordMaybe# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #)
    
    8723
    -  bigNatXor :: BigNat# -> BigNat# -> BigNat#
    
    8724
    -  bigNatXorWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8725
    -  bigNatZero :: BigNat
    
    8726
    -  bigNatZero# :: (# #) -> BigNat#
    
    8727
    -  gcdInt :: GHC.Internal.Types.Int -> GHC.Internal.Types.Int -> GHC.Internal.Types.Int
    
    8728
    -  gcdInt# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int#
    
    8729
    -  gcdWord :: GHC.Internal.Types.Word -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word
    
    8730
    -  gcdWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
    
    8731
    -  powModWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
    
    8732
    -  raiseDivZero_BigNat :: (# #) -> BigNat#
    
    8733
    -
    
    8734
    -module GHC.Num.Integer where
    
    8735
    -  -- Safety: None
    
    8736
    -  type Integer :: *
    
    8737
    -  data Integer = IS GHC.Internal.Prim.Int# | IP GHC.Internal.Prim.ByteArray# | IN GHC.Internal.Prim.ByteArray#
    
    8738
    -  integerAbs :: Integer -> Integer
    
    8739
    -  integerAdd :: Integer -> Integer -> Integer
    
    8740
    -  integerAnd :: Integer -> Integer -> Integer
    
    8741
    -  integerBit :: GHC.Internal.Types.Word -> Integer
    
    8742
    -  integerBit# :: GHC.Internal.Prim.Word# -> Integer
    
    8743
    -  integerCheck :: Integer -> GHC.Internal.Types.Bool
    
    8744
    -  integerCheck# :: Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8745
    -  integerCompare :: Integer -> Integer -> GHC.Internal.Types.Ordering
    
    8746
    -  integerComplement :: Integer -> Integer
    
    8747
    -  integerDecodeDouble# :: GHC.Internal.Prim.Double# -> (# Integer, GHC.Internal.Prim.Int# #)
    
    8748
    -  integerDiv :: Integer -> Integer -> Integer
    
    8749
    -  integerDivMod :: Integer -> Integer -> (Integer, Integer)
    
    8750
    -  integerDivMod# :: Integer -> Integer -> (# Integer, Integer #)
    
    8751
    -  integerEncodeDouble :: Integer -> GHC.Internal.Types.Int -> GHC.Internal.Types.Double
    
    8752
    -  integerEncodeDouble# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double#
    
    8753
    -  integerEncodeFloat# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float#
    
    8754
    -  integerEq :: Integer -> Integer -> GHC.Internal.Types.Bool
    
    8755
    -  integerEq# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8756
    -  integerFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Integer
    
    8757
    -  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 #)
    
    8758
    -  integerFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer
    
    8759
    -  integerFromBigNatNeg# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer
    
    8760
    -  integerFromBigNatSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Bignum.BigNat.BigNat# -> Integer
    
    8761
    -  integerFromByteArray :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> Integer
    
    8762
    -  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 #)
    
    8763
    -  integerFromInt :: GHC.Internal.Types.Int -> Integer
    
    8764
    -  integerFromInt# :: GHC.Internal.Prim.Int# -> Integer
    
    8765
    -  integerFromInt64# :: GHC.Internal.Prim.Int64# -> Integer
    
    8766
    -  integerFromNatural :: GHC.Internal.Bignum.Natural.Natural -> Integer
    
    8767
    -  integerFromWord :: GHC.Internal.Types.Word -> Integer
    
    8768
    -  integerFromWord# :: GHC.Internal.Prim.Word# -> Integer
    
    8769
    -  integerFromWord64# :: GHC.Internal.Prim.Word64# -> Integer
    
    8770
    -  integerFromWordList :: GHC.Internal.Types.Bool -> [GHC.Internal.Types.Word] -> Integer
    
    8771
    -  integerFromWordNeg# :: GHC.Internal.Prim.Word# -> Integer
    
    8772
    -  integerFromWordSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word# -> Integer
    
    8773
    -  integerGcd :: Integer -> Integer -> Integer
    
    8774
    -  integerGcde :: Integer -> Integer -> (Integer, Integer, Integer)
    
    8775
    -  integerGcde# :: Integer -> Integer -> (# Integer, Integer, Integer #)
    
    8776
    -  integerGe :: Integer -> Integer -> GHC.Internal.Types.Bool
    
    8777
    -  integerGe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8778
    -  integerGt :: Integer -> Integer -> GHC.Internal.Types.Bool
    
    8779
    -  integerGt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8780
    -  integerIsNegative :: Integer -> GHC.Internal.Types.Bool
    
    8781
    -  integerIsNegative# :: Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8782
    -  integerIsOne :: Integer -> GHC.Internal.Types.Bool
    
    8783
    -  integerIsPowerOf2# :: Integer -> (# (# #) | GHC.Internal.Prim.Word# #)
    
    8784
    -  integerIsZero :: Integer -> GHC.Internal.Types.Bool
    
    8785
    -  integerLcm :: Integer -> Integer -> Integer
    
    8786
    -  integerLe :: Integer -> Integer -> GHC.Internal.Types.Bool
    
    8787
    -  integerLe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8788
    -  integerLog2 :: Integer -> GHC.Internal.Types.Word
    
    8789
    -  integerLog2# :: Integer -> GHC.Internal.Prim.Word#
    
    8790
    -  integerLogBase :: Integer -> Integer -> GHC.Internal.Types.Word
    
    8791
    -  integerLogBase# :: Integer -> Integer -> GHC.Internal.Prim.Word#
    
    8792
    -  integerLogBaseWord :: GHC.Internal.Types.Word -> Integer -> GHC.Internal.Types.Word
    
    8793
    -  integerLogBaseWord# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word#
    
    8794
    -  integerLt :: Integer -> Integer -> GHC.Internal.Types.Bool
    
    8795
    -  integerLt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8796
    -  integerMod :: Integer -> Integer -> Integer
    
    8797
    -  integerMul :: Integer -> Integer -> Integer
    
    8798
    -  integerNe :: Integer -> Integer -> GHC.Internal.Types.Bool
    
    8799
    -  integerNe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8800
    -  integerNegate :: Integer -> Integer
    
    8801
    -  integerOne :: Integer
    
    8802
    -  integerOr :: Integer -> Integer -> Integer
    
    8803
    -  integerPopCount# :: Integer -> GHC.Internal.Prim.Int#
    
    8804
    -  integerPowMod# :: Integer -> Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #)
    
    8805
    -  integerQuot :: Integer -> Integer -> Integer
    
    8806
    -  integerQuotRem :: Integer -> Integer -> (Integer, Integer)
    
    8807
    -  integerQuotRem# :: Integer -> Integer -> (# Integer, Integer #)
    
    8808
    -  integerRecipMod# :: Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #)
    
    8809
    -  integerRem :: Integer -> Integer -> Integer
    
    8810
    -  integerShiftL :: Integer -> GHC.Internal.Types.Word -> Integer
    
    8811
    -  integerShiftL# :: Integer -> GHC.Internal.Prim.Word# -> Integer
    
    8812
    -  integerShiftR :: Integer -> GHC.Internal.Types.Word -> Integer
    
    8813
    -  integerShiftR# :: Integer -> GHC.Internal.Prim.Word# -> Integer
    
    8814
    -  integerSignum :: Integer -> Integer
    
    8815
    -  integerSignum# :: Integer -> GHC.Internal.Prim.Int#
    
    8816
    -  integerSizeInBase# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word#
    
    8817
    -  integerSqr :: Integer -> Integer
    
    8818
    -  integerSub :: Integer -> Integer -> Integer
    
    8819
    -  integerTestBit :: Integer -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
    
    8820
    -  integerTestBit# :: Integer -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8821
    -  integerToAddr :: Integer -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
    
    8822
    -  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# #)
    
    8823
    -  integerToBigNatClamp# :: Integer -> GHC.Internal.Bignum.BigNat.BigNat#
    
    8824
    -  integerToBigNatSign# :: Integer -> (# GHC.Internal.Prim.Int#, GHC.Internal.Bignum.BigNat.BigNat# #)
    
    8825
    -  integerToInt :: Integer -> GHC.Internal.Types.Int
    
    8826
    -  integerToInt# :: Integer -> GHC.Internal.Prim.Int#
    
    8827
    -  integerToInt64# :: Integer -> GHC.Internal.Prim.Int64#
    
    8828
    -  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
    
    8829
    -  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# #)
    
    8830
    -  integerToNatural :: Integer -> GHC.Internal.Bignum.Natural.Natural
    
    8831
    -  integerToNaturalClamp :: Integer -> GHC.Internal.Bignum.Natural.Natural
    
    8832
    -  integerToNaturalThrow :: Integer -> GHC.Internal.Bignum.Natural.Natural
    
    8833
    -  integerToWord :: Integer -> GHC.Internal.Types.Word
    
    8834
    -  integerToWord# :: Integer -> GHC.Internal.Prim.Word#
    
    8835
    -  integerToWord64# :: Integer -> GHC.Internal.Prim.Word64#
    
    8836
    -  integerXor :: Integer -> Integer -> Integer
    
    8837
    -  integerZero :: Integer
    
    8838
    -
    
    8839
    -module GHC.Num.Natural where
    
    8840
    -  -- Safety: None
    
    8841
    -  type Natural :: *
    
    8842
    -  data Natural = NS GHC.Internal.Prim.Word# | NB GHC.Internal.Prim.ByteArray#
    
    8843
    -  naturalAdd :: Natural -> Natural -> Natural
    
    8844
    -  naturalAnd :: Natural -> Natural -> Natural
    
    8845
    -  naturalAndNot :: Natural -> Natural -> Natural
    
    8846
    -  naturalBit :: GHC.Internal.Types.Word -> Natural
    
    8847
    -  naturalBit# :: GHC.Internal.Prim.Word# -> Natural
    
    8848
    -  naturalCheck :: Natural -> GHC.Internal.Types.Bool
    
    8849
    -  naturalCheck# :: Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    8850
    -  naturalClearBit :: Natural -> GHC.Internal.Types.Word -> Natural
    
    8851
    -  naturalClearBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural
    
    8852
    -  naturalCompare :: Natural -> Natural -> GHC.Internal.Types.Ordering
    
    8853
    -  naturalComplementBit :: Natural -> GHC.Internal.Types.Word -> Natural
    
    8854
    -  naturalComplementBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural
    
    8855
    -  naturalEncodeDouble# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double#
    
    8856
    -  naturalEncodeFloat# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float#
    
    8857
    -  naturalEq :: Natural -> Natural -> GHC.Internal.Types.Bool
    
    8858
    -  naturalEq# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    8859
    -  naturalFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Natural
    
    8860
    -  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 #)
    
    8861
    -  naturalFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Natural
    
    8862
    -  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 #)
    
    8863
    -  naturalFromWord :: GHC.Internal.Types.Word -> Natural
    
    8864
    -  naturalFromWord# :: GHC.Internal.Prim.Word# -> Natural
    
    8865
    -  naturalFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> Natural
    
    8866
    -  naturalFromWordList :: [GHC.Internal.Types.Word] -> Natural
    
    8867
    -  naturalGcd :: Natural -> Natural -> Natural
    
    8868
    -  naturalGe :: Natural -> Natural -> GHC.Internal.Types.Bool
    
    8869
    -  naturalGe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    8870
    -  naturalGt :: Natural -> Natural -> GHC.Internal.Types.Bool
    
    8871
    -  naturalGt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    8872
    -  naturalIsOne :: Natural -> GHC.Internal.Types.Bool
    
    8873
    -  naturalIsPowerOf2# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #)
    
    8874
    -  naturalIsZero :: Natural -> GHC.Internal.Types.Bool
    
    8875
    -  naturalLcm :: Natural -> Natural -> Natural
    
    8876
    -  naturalLe :: Natural -> Natural -> GHC.Internal.Types.Bool
    
    8877
    -  naturalLe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    8878
    -  naturalLog2 :: Natural -> GHC.Internal.Types.Word
    
    8879
    -  naturalLog2# :: Natural -> GHC.Internal.Prim.Word#
    
    8880
    -  naturalLogBase :: Natural -> Natural -> GHC.Internal.Types.Word
    
    8881
    -  naturalLogBase# :: Natural -> Natural -> GHC.Internal.Prim.Word#
    
    8882
    -  naturalLogBaseWord :: GHC.Internal.Types.Word -> Natural -> GHC.Internal.Types.Word
    
    8883
    -  naturalLogBaseWord# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word#
    
    8884
    -  naturalLt :: Natural -> Natural -> GHC.Internal.Types.Bool
    
    8885
    -  naturalLt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    8886
    -  naturalMul :: Natural -> Natural -> Natural
    
    8887
    -  naturalNe :: Natural -> Natural -> GHC.Internal.Types.Bool
    
    8888
    -  naturalNe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    8889
    -  naturalNegate :: Natural -> Natural
    
    8890
    -  naturalOne :: Natural
    
    8891
    -  naturalOr :: Natural -> Natural -> Natural
    
    8892
    -  naturalPopCount :: Natural -> GHC.Internal.Types.Word
    
    8893
    -  naturalPopCount# :: Natural -> GHC.Internal.Prim.Word#
    
    8894
    -  naturalPowMod :: Natural -> Natural -> Natural -> Natural
    
    8895
    -  naturalQuot :: Natural -> Natural -> Natural
    
    8896
    -  naturalQuotRem :: Natural -> Natural -> (Natural, Natural)
    
    8897
    -  naturalQuotRem# :: Natural -> Natural -> (# Natural, Natural #)
    
    8898
    -  naturalRem :: Natural -> Natural -> Natural
    
    8899
    -  naturalSetBit :: Natural -> GHC.Internal.Types.Word -> Natural
    
    8900
    -  naturalSetBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural
    
    8901
    -  naturalShiftL :: Natural -> GHC.Internal.Types.Word -> Natural
    
    8902
    -  naturalShiftL# :: Natural -> GHC.Internal.Prim.Word# -> Natural
    
    8903
    -  naturalShiftR :: Natural -> GHC.Internal.Types.Word -> Natural
    
    8904
    -  naturalShiftR# :: Natural -> GHC.Internal.Prim.Word# -> Natural
    
    8905
    -  naturalSignum :: Natural -> Natural
    
    8906
    -  naturalSizeInBase# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word#
    
    8907
    -  naturalSqr :: Natural -> Natural
    
    8908
    -  naturalSub :: Natural -> Natural -> (# (# #) | Natural #)
    
    8909
    -  naturalSubThrow :: Natural -> Natural -> Natural
    
    8910
    -  naturalSubUnsafe :: Natural -> Natural -> Natural
    
    8911
    -  naturalTestBit :: Natural -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
    
    8912
    -  naturalTestBit# :: Natural -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8913
    -  naturalToAddr :: Natural -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
    
    8914
    -  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# #)
    
    8915
    -  naturalToBigNat# :: Natural -> GHC.Internal.Bignum.BigNat.BigNat#
    
    8916
    -  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# #)
    
    8917
    -  naturalToWord :: Natural -> GHC.Internal.Types.Word
    
    8918
    -  naturalToWord# :: Natural -> GHC.Internal.Prim.Word#
    
    8919
    -  naturalToWordClamp :: Natural -> GHC.Internal.Types.Word
    
    8920
    -  naturalToWordClamp# :: Natural -> GHC.Internal.Prim.Word#
    
    8921
    -  naturalToWordMaybe# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #)
    
    8922
    -  naturalXor :: Natural -> Natural -> Natural
    
    8923
    -  naturalZero :: Natural
    
    8924
    -
    
    8925 8591
     module GHC.OldList where
    
    8926 8592
       -- Safety: Safe
    
    8927 8593
       (!!) :: 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
    8768 8768
       quotRemInteger :: Integer -> Integer -> (# Integer, Integer #)
    
    8769 8769
       subtract :: forall a. Num a => a -> a -> a
    
    8770 8770
     
    
    8771
    -module GHC.Num.BigNat where
    
    8772
    -  -- Safety: None
    
    8773
    -  type BigNat :: *
    
    8774
    -  data BigNat = BN# {unBigNat :: BigNat#}
    
    8775
    -  type BigNat# :: GHC.Internal.Types.UnliftedType
    
    8776
    -  type BigNat# = GHC.Internal.Bignum.WordArray.WordArray#
    
    8777
    -  bigNatAdd :: BigNat# -> BigNat# -> BigNat#
    
    8778
    -  bigNatAddWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
    
    8779
    -  bigNatAddWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8780
    -  bigNatAnd :: BigNat# -> BigNat# -> BigNat#
    
    8781
    -  bigNatAndInt# :: BigNat# -> GHC.Internal.Prim.Int# -> BigNat#
    
    8782
    -  bigNatAndNot :: BigNat# -> BigNat# -> BigNat#
    
    8783
    -  bigNatAndNotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8784
    -  bigNatAndWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8785
    -  bigNatBit :: GHC.Internal.Types.Word -> BigNat#
    
    8786
    -  bigNatBit# :: GHC.Internal.Prim.Word# -> BigNat#
    
    8787
    -  bigNatCheck :: BigNat# -> GHC.Internal.Types.Bool
    
    8788
    -  bigNatCheck# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8789
    -  bigNatClearBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8790
    -  bigNatCompare :: BigNat# -> BigNat# -> GHC.Internal.Types.Ordering
    
    8791
    -  bigNatCompareWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Ordering
    
    8792
    -  bigNatCompareWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Types.Ordering
    
    8793
    -  bigNatComplementBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8794
    -  bigNatCtz :: BigNat# -> GHC.Internal.Types.Word
    
    8795
    -  bigNatCtz# :: BigNat# -> GHC.Internal.Prim.Word#
    
    8796
    -  bigNatCtzWord :: BigNat# -> GHC.Internal.Types.Word
    
    8797
    -  bigNatCtzWord# :: BigNat# -> GHC.Internal.Prim.Word#
    
    8798
    -  bigNatEncodeDouble# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double#
    
    8799
    -  bigNatEq :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
    
    8800
    -  bigNatEq# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8801
    -  bigNatEqWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8802
    -  bigNatFromAbsInt# :: GHC.Internal.Prim.Int# -> BigNat#
    
    8803
    -  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# #)
    
    8804
    -  bigNatFromAddrBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
    
    8805
    -  bigNatFromAddrLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
    
    8806
    -  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# #)
    
    8807
    -  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# #)
    
    8808
    -  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# #)
    
    8809
    -  bigNatFromWord :: GHC.Internal.Types.Word -> BigNat#
    
    8810
    -  bigNatFromWord# :: GHC.Internal.Prim.Word# -> BigNat#
    
    8811
    -  bigNatFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8812
    -  bigNatFromWord64# :: GHC.Internal.Prim.Word64# -> BigNat#
    
    8813
    -  bigNatFromWordArray :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat
    
    8814
    -  bigNatFromWordArray# :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8815
    -  bigNatFromWordList :: [GHC.Internal.Types.Word] -> BigNat#
    
    8816
    -  bigNatFromWordList# :: [GHC.Internal.Types.Word] -> GHC.Internal.Bignum.WordArray.WordArray#
    
    8817
    -  bigNatFromWordListUnsafe :: [GHC.Internal.Types.Word] -> BigNat#
    
    8818
    -  bigNatGcd :: BigNat# -> BigNat# -> BigNat#
    
    8819
    -  bigNatGcdWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
    
    8820
    -  bigNatGe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
    
    8821
    -  bigNatGe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8822
    -  bigNatGt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
    
    8823
    -  bigNatGt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8824
    -  bigNatGtWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
    
    8825
    -  bigNatGtWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8826
    -  bigNatIndex :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Types.Word
    
    8827
    -  bigNatIndex# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word#
    
    8828
    -  bigNatIsOne :: BigNat# -> GHC.Internal.Types.Bool
    
    8829
    -  bigNatIsOne# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8830
    -  bigNatIsPowerOf2# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #)
    
    8831
    -  bigNatIsTwo :: BigNat# -> GHC.Internal.Types.Bool
    
    8832
    -  bigNatIsTwo# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8833
    -  bigNatIsZero :: BigNat# -> GHC.Internal.Types.Bool
    
    8834
    -  bigNatIsZero# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8835
    -  bigNatLcm :: BigNat# -> BigNat# -> BigNat#
    
    8836
    -  bigNatLcmWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8837
    -  bigNatLcmWordWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8838
    -  bigNatLe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
    
    8839
    -  bigNatLe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8840
    -  bigNatLeWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
    
    8841
    -  bigNatLeWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8842
    -  bigNatLog2 :: BigNat# -> GHC.Internal.Types.Word
    
    8843
    -  bigNatLog2# :: BigNat# -> GHC.Internal.Prim.Word#
    
    8844
    -  bigNatLogBase :: BigNat# -> BigNat# -> GHC.Internal.Types.Word
    
    8845
    -  bigNatLogBase# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word#
    
    8846
    -  bigNatLogBaseWord :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word
    
    8847
    -  bigNatLogBaseWord# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word#
    
    8848
    -  bigNatLt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
    
    8849
    -  bigNatLt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8850
    -  bigNatMul :: BigNat# -> BigNat# -> BigNat#
    
    8851
    -  bigNatMulWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
    
    8852
    -  bigNatMulWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8853
    -  bigNatNe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
    
    8854
    -  bigNatNe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8855
    -  bigNatOne :: BigNat
    
    8856
    -  bigNatOne# :: (# #) -> BigNat#
    
    8857
    -  bigNatOr :: BigNat# -> BigNat# -> BigNat#
    
    8858
    -  bigNatOrWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8859
    -  bigNatPopCount :: BigNat# -> GHC.Internal.Types.Word
    
    8860
    -  bigNatPopCount# :: BigNat# -> GHC.Internal.Prim.Word#
    
    8861
    -  bigNatPowMod :: BigNat# -> BigNat# -> BigNat# -> BigNat#
    
    8862
    -  bigNatPowModWord# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
    
    8863
    -  bigNatQuot :: BigNat# -> BigNat# -> BigNat#
    
    8864
    -  bigNatQuotRem# :: BigNat# -> BigNat# -> (# BigNat#, BigNat# #)
    
    8865
    -  bigNatQuotRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# BigNat#, GHC.Internal.Prim.Word# #)
    
    8866
    -  bigNatQuotWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
    
    8867
    -  bigNatQuotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8868
    -  bigNatRem :: BigNat# -> BigNat# -> BigNat#
    
    8869
    -  bigNatRemWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word
    
    8870
    -  bigNatRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
    
    8871
    -  bigNatSetBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8872
    -  bigNatShiftL :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
    
    8873
    -  bigNatShiftL# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8874
    -  bigNatShiftR :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
    
    8875
    -  bigNatShiftR# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8876
    -  bigNatShiftRNeg# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8877
    -  bigNatSize :: BigNat# -> GHC.Internal.Types.Word
    
    8878
    -  bigNatSize# :: BigNat# -> GHC.Internal.Prim.Int#
    
    8879
    -  bigNatSizeInBase :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word
    
    8880
    -  bigNatSizeInBase# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word#
    
    8881
    -  bigNatSqr :: BigNat# -> BigNat#
    
    8882
    -  bigNatSub :: BigNat# -> BigNat# -> (# (# #) | BigNat# #)
    
    8883
    -  bigNatSubUnsafe :: BigNat# -> BigNat# -> BigNat#
    
    8884
    -  bigNatSubWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# (# #) | BigNat# #)
    
    8885
    -  bigNatSubWordUnsafe :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
    
    8886
    -  bigNatSubWordUnsafe# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8887
    -  bigNatTestBit :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
    
    8888
    -  bigNatTestBit# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8889
    -  bigNatToAddr :: BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
    
    8890
    -  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# #)
    
    8891
    -  bigNatToAddrBE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
    
    8892
    -  bigNatToAddrLE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
    
    8893
    -  bigNatToInt :: BigNat# -> GHC.Internal.Types.Int
    
    8894
    -  bigNatToInt# :: BigNat# -> GHC.Internal.Prim.Int#
    
    8895
    -  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# #)
    
    8896
    -  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# #)
    
    8897
    -  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# #)
    
    8898
    -  bigNatToWord :: BigNat# -> GHC.Internal.Types.Word
    
    8899
    -  bigNatToWord# :: BigNat# -> GHC.Internal.Prim.Word#
    
    8900
    -  bigNatToWord64# :: BigNat# -> GHC.Internal.Prim.Word64#
    
    8901
    -  bigNatToWordList :: BigNat# -> [GHC.Internal.Types.Word]
    
    8902
    -  bigNatToWordMaybe# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #)
    
    8903
    -  bigNatXor :: BigNat# -> BigNat# -> BigNat#
    
    8904
    -  bigNatXorWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8905
    -  bigNatZero :: BigNat
    
    8906
    -  bigNatZero# :: (# #) -> BigNat#
    
    8907
    -  gcdInt :: GHC.Internal.Types.Int -> GHC.Internal.Types.Int -> GHC.Internal.Types.Int
    
    8908
    -  gcdInt# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int#
    
    8909
    -  gcdWord :: GHC.Internal.Types.Word -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word
    
    8910
    -  gcdWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
    
    8911
    -  powModWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
    
    8912
    -  raiseDivZero_BigNat :: (# #) -> BigNat#
    
    8913
    -
    
    8914
    -module GHC.Num.Integer where
    
    8915
    -  -- Safety: None
    
    8916
    -  type Integer :: *
    
    8917
    -  data Integer = IS GHC.Internal.Prim.Int# | IP GHC.Internal.Prim.ByteArray# | IN GHC.Internal.Prim.ByteArray#
    
    8918
    -  integerAbs :: Integer -> Integer
    
    8919
    -  integerAdd :: Integer -> Integer -> Integer
    
    8920
    -  integerAnd :: Integer -> Integer -> Integer
    
    8921
    -  integerBit :: GHC.Internal.Types.Word -> Integer
    
    8922
    -  integerBit# :: GHC.Internal.Prim.Word# -> Integer
    
    8923
    -  integerCheck :: Integer -> GHC.Internal.Types.Bool
    
    8924
    -  integerCheck# :: Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8925
    -  integerCompare :: Integer -> Integer -> GHC.Internal.Types.Ordering
    
    8926
    -  integerComplement :: Integer -> Integer
    
    8927
    -  integerDecodeDouble# :: GHC.Internal.Prim.Double# -> (# Integer, GHC.Internal.Prim.Int# #)
    
    8928
    -  integerDiv :: Integer -> Integer -> Integer
    
    8929
    -  integerDivMod :: Integer -> Integer -> (Integer, Integer)
    
    8930
    -  integerDivMod# :: Integer -> Integer -> (# Integer, Integer #)
    
    8931
    -  integerEncodeDouble :: Integer -> GHC.Internal.Types.Int -> GHC.Internal.Types.Double
    
    8932
    -  integerEncodeDouble# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double#
    
    8933
    -  integerEncodeFloat# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float#
    
    8934
    -  integerEq :: Integer -> Integer -> GHC.Internal.Types.Bool
    
    8935
    -  integerEq# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8936
    -  integerFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Integer
    
    8937
    -  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 #)
    
    8938
    -  integerFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer
    
    8939
    -  integerFromBigNatNeg# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer
    
    8940
    -  integerFromBigNatSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Bignum.BigNat.BigNat# -> Integer
    
    8941
    -  integerFromByteArray :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> Integer
    
    8942
    -  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 #)
    
    8943
    -  integerFromInt :: GHC.Internal.Types.Int -> Integer
    
    8944
    -  integerFromInt# :: GHC.Internal.Prim.Int# -> Integer
    
    8945
    -  integerFromInt64# :: GHC.Internal.Prim.Int64# -> Integer
    
    8946
    -  integerFromNatural :: GHC.Internal.Bignum.Natural.Natural -> Integer
    
    8947
    -  integerFromWord :: GHC.Internal.Types.Word -> Integer
    
    8948
    -  integerFromWord# :: GHC.Internal.Prim.Word# -> Integer
    
    8949
    -  integerFromWord64# :: GHC.Internal.Prim.Word64# -> Integer
    
    8950
    -  integerFromWordList :: GHC.Internal.Types.Bool -> [GHC.Internal.Types.Word] -> Integer
    
    8951
    -  integerFromWordNeg# :: GHC.Internal.Prim.Word# -> Integer
    
    8952
    -  integerFromWordSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word# -> Integer
    
    8953
    -  integerGcd :: Integer -> Integer -> Integer
    
    8954
    -  integerGcde :: Integer -> Integer -> (Integer, Integer, Integer)
    
    8955
    -  integerGcde# :: Integer -> Integer -> (# Integer, Integer, Integer #)
    
    8956
    -  integerGe :: Integer -> Integer -> GHC.Internal.Types.Bool
    
    8957
    -  integerGe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8958
    -  integerGt :: Integer -> Integer -> GHC.Internal.Types.Bool
    
    8959
    -  integerGt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8960
    -  integerIsNegative :: Integer -> GHC.Internal.Types.Bool
    
    8961
    -  integerIsNegative# :: Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8962
    -  integerIsOne :: Integer -> GHC.Internal.Types.Bool
    
    8963
    -  integerIsPowerOf2# :: Integer -> (# (# #) | GHC.Internal.Prim.Word# #)
    
    8964
    -  integerIsZero :: Integer -> GHC.Internal.Types.Bool
    
    8965
    -  integerLcm :: Integer -> Integer -> Integer
    
    8966
    -  integerLe :: Integer -> Integer -> GHC.Internal.Types.Bool
    
    8967
    -  integerLe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8968
    -  integerLog2 :: Integer -> GHC.Internal.Types.Word
    
    8969
    -  integerLog2# :: Integer -> GHC.Internal.Prim.Word#
    
    8970
    -  integerLogBase :: Integer -> Integer -> GHC.Internal.Types.Word
    
    8971
    -  integerLogBase# :: Integer -> Integer -> GHC.Internal.Prim.Word#
    
    8972
    -  integerLogBaseWord :: GHC.Internal.Types.Word -> Integer -> GHC.Internal.Types.Word
    
    8973
    -  integerLogBaseWord# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word#
    
    8974
    -  integerLt :: Integer -> Integer -> GHC.Internal.Types.Bool
    
    8975
    -  integerLt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8976
    -  integerMod :: Integer -> Integer -> Integer
    
    8977
    -  integerMul :: Integer -> Integer -> Integer
    
    8978
    -  integerNe :: Integer -> Integer -> GHC.Internal.Types.Bool
    
    8979
    -  integerNe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8980
    -  integerNegate :: Integer -> Integer
    
    8981
    -  integerOne :: Integer
    
    8982
    -  integerOr :: Integer -> Integer -> Integer
    
    8983
    -  integerPopCount# :: Integer -> GHC.Internal.Prim.Int#
    
    8984
    -  integerPowMod# :: Integer -> Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #)
    
    8985
    -  integerQuot :: Integer -> Integer -> Integer
    
    8986
    -  integerQuotRem :: Integer -> Integer -> (Integer, Integer)
    
    8987
    -  integerQuotRem# :: Integer -> Integer -> (# Integer, Integer #)
    
    8988
    -  integerRecipMod# :: Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #)
    
    8989
    -  integerRem :: Integer -> Integer -> Integer
    
    8990
    -  integerShiftL :: Integer -> GHC.Internal.Types.Word -> Integer
    
    8991
    -  integerShiftL# :: Integer -> GHC.Internal.Prim.Word# -> Integer
    
    8992
    -  integerShiftR :: Integer -> GHC.Internal.Types.Word -> Integer
    
    8993
    -  integerShiftR# :: Integer -> GHC.Internal.Prim.Word# -> Integer
    
    8994
    -  integerSignum :: Integer -> Integer
    
    8995
    -  integerSignum# :: Integer -> GHC.Internal.Prim.Int#
    
    8996
    -  integerSizeInBase# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word#
    
    8997
    -  integerSqr :: Integer -> Integer
    
    8998
    -  integerSub :: Integer -> Integer -> Integer
    
    8999
    -  integerTestBit :: Integer -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
    
    9000
    -  integerTestBit# :: Integer -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
    
    9001
    -  integerToAddr :: Integer -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
    
    9002
    -  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# #)
    
    9003
    -  integerToBigNatClamp# :: Integer -> GHC.Internal.Bignum.BigNat.BigNat#
    
    9004
    -  integerToBigNatSign# :: Integer -> (# GHC.Internal.Prim.Int#, GHC.Internal.Bignum.BigNat.BigNat# #)
    
    9005
    -  integerToInt :: Integer -> GHC.Internal.Types.Int
    
    9006
    -  integerToInt# :: Integer -> GHC.Internal.Prim.Int#
    
    9007
    -  integerToInt64# :: Integer -> GHC.Internal.Prim.Int64#
    
    9008
    -  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
    
    9009
    -  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# #)
    
    9010
    -  integerToNatural :: Integer -> GHC.Internal.Bignum.Natural.Natural
    
    9011
    -  integerToNaturalClamp :: Integer -> GHC.Internal.Bignum.Natural.Natural
    
    9012
    -  integerToNaturalThrow :: Integer -> GHC.Internal.Bignum.Natural.Natural
    
    9013
    -  integerToWord :: Integer -> GHC.Internal.Types.Word
    
    9014
    -  integerToWord# :: Integer -> GHC.Internal.Prim.Word#
    
    9015
    -  integerToWord64# :: Integer -> GHC.Internal.Prim.Word64#
    
    9016
    -  integerXor :: Integer -> Integer -> Integer
    
    9017
    -  integerZero :: Integer
    
    9018
    -
    
    9019
    -module GHC.Num.Natural where
    
    9020
    -  -- Safety: None
    
    9021
    -  type Natural :: *
    
    9022
    -  data Natural = NS GHC.Internal.Prim.Word# | NB GHC.Internal.Prim.ByteArray#
    
    9023
    -  naturalAdd :: Natural -> Natural -> Natural
    
    9024
    -  naturalAnd :: Natural -> Natural -> Natural
    
    9025
    -  naturalAndNot :: Natural -> Natural -> Natural
    
    9026
    -  naturalBit :: GHC.Internal.Types.Word -> Natural
    
    9027
    -  naturalBit# :: GHC.Internal.Prim.Word# -> Natural
    
    9028
    -  naturalCheck :: Natural -> GHC.Internal.Types.Bool
    
    9029
    -  naturalCheck# :: Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    9030
    -  naturalClearBit :: Natural -> GHC.Internal.Types.Word -> Natural
    
    9031
    -  naturalClearBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural
    
    9032
    -  naturalCompare :: Natural -> Natural -> GHC.Internal.Types.Ordering
    
    9033
    -  naturalComplementBit :: Natural -> GHC.Internal.Types.Word -> Natural
    
    9034
    -  naturalComplementBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural
    
    9035
    -  naturalEncodeDouble# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double#
    
    9036
    -  naturalEncodeFloat# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float#
    
    9037
    -  naturalEq :: Natural -> Natural -> GHC.Internal.Types.Bool
    
    9038
    -  naturalEq# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    9039
    -  naturalFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Natural
    
    9040
    -  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 #)
    
    9041
    -  naturalFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Natural
    
    9042
    -  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 #)
    
    9043
    -  naturalFromWord :: GHC.Internal.Types.Word -> Natural
    
    9044
    -  naturalFromWord# :: GHC.Internal.Prim.Word# -> Natural
    
    9045
    -  naturalFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> Natural
    
    9046
    -  naturalFromWordList :: [GHC.Internal.Types.Word] -> Natural
    
    9047
    -  naturalGcd :: Natural -> Natural -> Natural
    
    9048
    -  naturalGe :: Natural -> Natural -> GHC.Internal.Types.Bool
    
    9049
    -  naturalGe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    9050
    -  naturalGt :: Natural -> Natural -> GHC.Internal.Types.Bool
    
    9051
    -  naturalGt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    9052
    -  naturalIsOne :: Natural -> GHC.Internal.Types.Bool
    
    9053
    -  naturalIsPowerOf2# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #)
    
    9054
    -  naturalIsZero :: Natural -> GHC.Internal.Types.Bool
    
    9055
    -  naturalLcm :: Natural -> Natural -> Natural
    
    9056
    -  naturalLe :: Natural -> Natural -> GHC.Internal.Types.Bool
    
    9057
    -  naturalLe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    9058
    -  naturalLog2 :: Natural -> GHC.Internal.Types.Word
    
    9059
    -  naturalLog2# :: Natural -> GHC.Internal.Prim.Word#
    
    9060
    -  naturalLogBase :: Natural -> Natural -> GHC.Internal.Types.Word
    
    9061
    -  naturalLogBase# :: Natural -> Natural -> GHC.Internal.Prim.Word#
    
    9062
    -  naturalLogBaseWord :: GHC.Internal.Types.Word -> Natural -> GHC.Internal.Types.Word
    
    9063
    -  naturalLogBaseWord# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word#
    
    9064
    -  naturalLt :: Natural -> Natural -> GHC.Internal.Types.Bool
    
    9065
    -  naturalLt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    9066
    -  naturalMul :: Natural -> Natural -> Natural
    
    9067
    -  naturalNe :: Natural -> Natural -> GHC.Internal.Types.Bool
    
    9068
    -  naturalNe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    9069
    -  naturalNegate :: Natural -> Natural
    
    9070
    -  naturalOne :: Natural
    
    9071
    -  naturalOr :: Natural -> Natural -> Natural
    
    9072
    -  naturalPopCount :: Natural -> GHC.Internal.Types.Word
    
    9073
    -  naturalPopCount# :: Natural -> GHC.Internal.Prim.Word#
    
    9074
    -  naturalPowMod :: Natural -> Natural -> Natural -> Natural
    
    9075
    -  naturalQuot :: Natural -> Natural -> Natural
    
    9076
    -  naturalQuotRem :: Natural -> Natural -> (Natural, Natural)
    
    9077
    -  naturalQuotRem# :: Natural -> Natural -> (# Natural, Natural #)
    
    9078
    -  naturalRem :: Natural -> Natural -> Natural
    
    9079
    -  naturalSetBit :: Natural -> GHC.Internal.Types.Word -> Natural
    
    9080
    -  naturalSetBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural
    
    9081
    -  naturalShiftL :: Natural -> GHC.Internal.Types.Word -> Natural
    
    9082
    -  naturalShiftL# :: Natural -> GHC.Internal.Prim.Word# -> Natural
    
    9083
    -  naturalShiftR :: Natural -> GHC.Internal.Types.Word -> Natural
    
    9084
    -  naturalShiftR# :: Natural -> GHC.Internal.Prim.Word# -> Natural
    
    9085
    -  naturalSignum :: Natural -> Natural
    
    9086
    -  naturalSizeInBase# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word#
    
    9087
    -  naturalSqr :: Natural -> Natural
    
    9088
    -  naturalSub :: Natural -> Natural -> (# (# #) | Natural #)
    
    9089
    -  naturalSubThrow :: Natural -> Natural -> Natural
    
    9090
    -  naturalSubUnsafe :: Natural -> Natural -> Natural
    
    9091
    -  naturalTestBit :: Natural -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
    
    9092
    -  naturalTestBit# :: Natural -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
    
    9093
    -  naturalToAddr :: Natural -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
    
    9094
    -  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# #)
    
    9095
    -  naturalToBigNat# :: Natural -> GHC.Internal.Bignum.BigNat.BigNat#
    
    9096
    -  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# #)
    
    9097
    -  naturalToWord :: Natural -> GHC.Internal.Types.Word
    
    9098
    -  naturalToWord# :: Natural -> GHC.Internal.Prim.Word#
    
    9099
    -  naturalToWordClamp :: Natural -> GHC.Internal.Types.Word
    
    9100
    -  naturalToWordClamp# :: Natural -> GHC.Internal.Prim.Word#
    
    9101
    -  naturalToWordMaybe# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #)
    
    9102
    -  naturalXor :: Natural -> Natural -> Natural
    
    9103
    -  naturalZero :: Natural
    
    9104
    -
    
    9105 8771
     module GHC.OldList where
    
    9106 8772
       -- Safety: Safe
    
    9107 8773
       (!!) :: 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
    8550 8550
       quotRemInteger :: Integer -> Integer -> (# Integer, Integer #)
    
    8551 8551
       subtract :: forall a. Num a => a -> a -> a
    
    8552 8552
     
    
    8553
    -module GHC.Num.BigNat where
    
    8554
    -  -- Safety: None
    
    8555
    -  type BigNat :: *
    
    8556
    -  data BigNat = BN# {unBigNat :: BigNat#}
    
    8557
    -  type BigNat# :: GHC.Internal.Types.UnliftedType
    
    8558
    -  type BigNat# = GHC.Internal.Bignum.WordArray.WordArray#
    
    8559
    -  bigNatAdd :: BigNat# -> BigNat# -> BigNat#
    
    8560
    -  bigNatAddWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
    
    8561
    -  bigNatAddWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8562
    -  bigNatAnd :: BigNat# -> BigNat# -> BigNat#
    
    8563
    -  bigNatAndInt# :: BigNat# -> GHC.Internal.Prim.Int# -> BigNat#
    
    8564
    -  bigNatAndNot :: BigNat# -> BigNat# -> BigNat#
    
    8565
    -  bigNatAndNotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8566
    -  bigNatAndWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8567
    -  bigNatBit :: GHC.Internal.Types.Word -> BigNat#
    
    8568
    -  bigNatBit# :: GHC.Internal.Prim.Word# -> BigNat#
    
    8569
    -  bigNatCheck :: BigNat# -> GHC.Internal.Types.Bool
    
    8570
    -  bigNatCheck# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8571
    -  bigNatClearBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8572
    -  bigNatCompare :: BigNat# -> BigNat# -> GHC.Internal.Types.Ordering
    
    8573
    -  bigNatCompareWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Ordering
    
    8574
    -  bigNatCompareWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Types.Ordering
    
    8575
    -  bigNatComplementBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8576
    -  bigNatCtz :: BigNat# -> GHC.Internal.Types.Word
    
    8577
    -  bigNatCtz# :: BigNat# -> GHC.Internal.Prim.Word#
    
    8578
    -  bigNatCtzWord :: BigNat# -> GHC.Internal.Types.Word
    
    8579
    -  bigNatCtzWord# :: BigNat# -> GHC.Internal.Prim.Word#
    
    8580
    -  bigNatEncodeDouble# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double#
    
    8581
    -  bigNatEq :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
    
    8582
    -  bigNatEq# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8583
    -  bigNatEqWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8584
    -  bigNatFromAbsInt# :: GHC.Internal.Prim.Int# -> BigNat#
    
    8585
    -  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# #)
    
    8586
    -  bigNatFromAddrBE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
    
    8587
    -  bigNatFromAddrLE# :: forall s. GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, BigNat# #)
    
    8588
    -  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# #)
    
    8589
    -  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# #)
    
    8590
    -  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# #)
    
    8591
    -  bigNatFromWord :: GHC.Internal.Types.Word -> BigNat#
    
    8592
    -  bigNatFromWord# :: GHC.Internal.Prim.Word# -> BigNat#
    
    8593
    -  bigNatFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8594
    -  bigNatFromWord64# :: GHC.Internal.Prim.Word64# -> BigNat#
    
    8595
    -  bigNatFromWordArray :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat
    
    8596
    -  bigNatFromWordArray# :: GHC.Internal.Bignum.WordArray.WordArray# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8597
    -  bigNatFromWordList :: [GHC.Internal.Types.Word] -> BigNat#
    
    8598
    -  bigNatFromWordList# :: [GHC.Internal.Types.Word] -> GHC.Internal.Bignum.WordArray.WordArray#
    
    8599
    -  bigNatFromWordListUnsafe :: [GHC.Internal.Types.Word] -> BigNat#
    
    8600
    -  bigNatGcd :: BigNat# -> BigNat# -> BigNat#
    
    8601
    -  bigNatGcdWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
    
    8602
    -  bigNatGe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
    
    8603
    -  bigNatGe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8604
    -  bigNatGt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
    
    8605
    -  bigNatGt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8606
    -  bigNatGtWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
    
    8607
    -  bigNatGtWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8608
    -  bigNatIndex :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Types.Word
    
    8609
    -  bigNatIndex# :: BigNat# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word#
    
    8610
    -  bigNatIsOne :: BigNat# -> GHC.Internal.Types.Bool
    
    8611
    -  bigNatIsOne# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8612
    -  bigNatIsPowerOf2# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #)
    
    8613
    -  bigNatIsTwo :: BigNat# -> GHC.Internal.Types.Bool
    
    8614
    -  bigNatIsTwo# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8615
    -  bigNatIsZero :: BigNat# -> GHC.Internal.Types.Bool
    
    8616
    -  bigNatIsZero# :: BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8617
    -  bigNatLcm :: BigNat# -> BigNat# -> BigNat#
    
    8618
    -  bigNatLcmWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8619
    -  bigNatLcmWordWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8620
    -  bigNatLe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
    
    8621
    -  bigNatLe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8622
    -  bigNatLeWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
    
    8623
    -  bigNatLeWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8624
    -  bigNatLog2 :: BigNat# -> GHC.Internal.Types.Word
    
    8625
    -  bigNatLog2# :: BigNat# -> GHC.Internal.Prim.Word#
    
    8626
    -  bigNatLogBase :: BigNat# -> BigNat# -> GHC.Internal.Types.Word
    
    8627
    -  bigNatLogBase# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word#
    
    8628
    -  bigNatLogBaseWord :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word
    
    8629
    -  bigNatLogBaseWord# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word#
    
    8630
    -  bigNatLt :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
    
    8631
    -  bigNatLt# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8632
    -  bigNatMul :: BigNat# -> BigNat# -> BigNat#
    
    8633
    -  bigNatMulWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
    
    8634
    -  bigNatMulWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8635
    -  bigNatNe :: BigNat# -> BigNat# -> GHC.Internal.Types.Bool
    
    8636
    -  bigNatNe# :: BigNat# -> BigNat# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8637
    -  bigNatOne :: BigNat
    
    8638
    -  bigNatOne# :: (# #) -> BigNat#
    
    8639
    -  bigNatOr :: BigNat# -> BigNat# -> BigNat#
    
    8640
    -  bigNatOrWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8641
    -  bigNatPopCount :: BigNat# -> GHC.Internal.Types.Word
    
    8642
    -  bigNatPopCount# :: BigNat# -> GHC.Internal.Prim.Word#
    
    8643
    -  bigNatPowMod :: BigNat# -> BigNat# -> BigNat# -> BigNat#
    
    8644
    -  bigNatPowModWord# :: BigNat# -> BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
    
    8645
    -  bigNatQuot :: BigNat# -> BigNat# -> BigNat#
    
    8646
    -  bigNatQuotRem# :: BigNat# -> BigNat# -> (# BigNat#, BigNat# #)
    
    8647
    -  bigNatQuotRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# BigNat#, GHC.Internal.Prim.Word# #)
    
    8648
    -  bigNatQuotWord :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
    
    8649
    -  bigNatQuotWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8650
    -  bigNatRem :: BigNat# -> BigNat# -> BigNat#
    
    8651
    -  bigNatRemWord :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word
    
    8652
    -  bigNatRemWord# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
    
    8653
    -  bigNatSetBit# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8654
    -  bigNatShiftL :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
    
    8655
    -  bigNatShiftL# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8656
    -  bigNatShiftR :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
    
    8657
    -  bigNatShiftR# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8658
    -  bigNatShiftRNeg# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8659
    -  bigNatSize :: BigNat# -> GHC.Internal.Types.Word
    
    8660
    -  bigNatSize# :: BigNat# -> GHC.Internal.Prim.Int#
    
    8661
    -  bigNatSizeInBase :: GHC.Internal.Types.Word -> BigNat# -> GHC.Internal.Types.Word
    
    8662
    -  bigNatSizeInBase# :: GHC.Internal.Prim.Word# -> BigNat# -> GHC.Internal.Prim.Word#
    
    8663
    -  bigNatSqr :: BigNat# -> BigNat#
    
    8664
    -  bigNatSub :: BigNat# -> BigNat# -> (# (# #) | BigNat# #)
    
    8665
    -  bigNatSubUnsafe :: BigNat# -> BigNat# -> BigNat#
    
    8666
    -  bigNatSubWord# :: BigNat# -> GHC.Internal.Prim.Word# -> (# (# #) | BigNat# #)
    
    8667
    -  bigNatSubWordUnsafe :: BigNat# -> GHC.Internal.Types.Word -> BigNat#
    
    8668
    -  bigNatSubWordUnsafe# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8669
    -  bigNatTestBit :: BigNat# -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
    
    8670
    -  bigNatTestBit# :: BigNat# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8671
    -  bigNatToAddr :: BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
    
    8672
    -  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# #)
    
    8673
    -  bigNatToAddrBE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
    
    8674
    -  bigNatToAddrLE# :: forall s. BigNat# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Prim.State# s -> (# GHC.Internal.Prim.State# s, GHC.Internal.Prim.Word# #)
    
    8675
    -  bigNatToInt :: BigNat# -> GHC.Internal.Types.Int
    
    8676
    -  bigNatToInt# :: BigNat# -> GHC.Internal.Prim.Int#
    
    8677
    -  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# #)
    
    8678
    -  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# #)
    
    8679
    -  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# #)
    
    8680
    -  bigNatToWord :: BigNat# -> GHC.Internal.Types.Word
    
    8681
    -  bigNatToWord# :: BigNat# -> GHC.Internal.Prim.Word#
    
    8682
    -  bigNatToWord64# :: BigNat# -> GHC.Internal.Prim.Word64#
    
    8683
    -  bigNatToWordList :: BigNat# -> [GHC.Internal.Types.Word]
    
    8684
    -  bigNatToWordMaybe# :: BigNat# -> (# (# #) | GHC.Internal.Prim.Word# #)
    
    8685
    -  bigNatXor :: BigNat# -> BigNat# -> BigNat#
    
    8686
    -  bigNatXorWord# :: BigNat# -> GHC.Internal.Prim.Word# -> BigNat#
    
    8687
    -  bigNatZero :: BigNat
    
    8688
    -  bigNatZero# :: (# #) -> BigNat#
    
    8689
    -  gcdInt :: GHC.Internal.Types.Int -> GHC.Internal.Types.Int -> GHC.Internal.Types.Int
    
    8690
    -  gcdInt# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Int#
    
    8691
    -  gcdWord :: GHC.Internal.Types.Word -> GHC.Internal.Types.Word -> GHC.Internal.Types.Word
    
    8692
    -  gcdWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
    
    8693
    -  powModWord# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word#
    
    8694
    -  raiseDivZero_BigNat :: (# #) -> BigNat#
    
    8695
    -
    
    8696
    -module GHC.Num.Integer where
    
    8697
    -  -- Safety: None
    
    8698
    -  type Integer :: *
    
    8699
    -  data Integer = IS GHC.Internal.Prim.Int# | IP GHC.Internal.Prim.ByteArray# | IN GHC.Internal.Prim.ByteArray#
    
    8700
    -  integerAbs :: Integer -> Integer
    
    8701
    -  integerAdd :: Integer -> Integer -> Integer
    
    8702
    -  integerAnd :: Integer -> Integer -> Integer
    
    8703
    -  integerBit :: GHC.Internal.Types.Word -> Integer
    
    8704
    -  integerBit# :: GHC.Internal.Prim.Word# -> Integer
    
    8705
    -  integerCheck :: Integer -> GHC.Internal.Types.Bool
    
    8706
    -  integerCheck# :: Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8707
    -  integerCompare :: Integer -> Integer -> GHC.Internal.Types.Ordering
    
    8708
    -  integerComplement :: Integer -> Integer
    
    8709
    -  integerDecodeDouble# :: GHC.Internal.Prim.Double# -> (# Integer, GHC.Internal.Prim.Int# #)
    
    8710
    -  integerDiv :: Integer -> Integer -> Integer
    
    8711
    -  integerDivMod :: Integer -> Integer -> (Integer, Integer)
    
    8712
    -  integerDivMod# :: Integer -> Integer -> (# Integer, Integer #)
    
    8713
    -  integerEncodeDouble :: Integer -> GHC.Internal.Types.Int -> GHC.Internal.Types.Double
    
    8714
    -  integerEncodeDouble# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double#
    
    8715
    -  integerEncodeFloat# :: Integer -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float#
    
    8716
    -  integerEq :: Integer -> Integer -> GHC.Internal.Types.Bool
    
    8717
    -  integerEq# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8718
    -  integerFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Integer
    
    8719
    -  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 #)
    
    8720
    -  integerFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer
    
    8721
    -  integerFromBigNatNeg# :: GHC.Internal.Bignum.BigNat.BigNat# -> Integer
    
    8722
    -  integerFromBigNatSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Bignum.BigNat.BigNat# -> Integer
    
    8723
    -  integerFromByteArray :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.ByteArray# -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool# -> Integer
    
    8724
    -  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 #)
    
    8725
    -  integerFromInt :: GHC.Internal.Types.Int -> Integer
    
    8726
    -  integerFromInt# :: GHC.Internal.Prim.Int# -> Integer
    
    8727
    -  integerFromInt64# :: GHC.Internal.Prim.Int64# -> Integer
    
    8728
    -  integerFromNatural :: GHC.Internal.Bignum.Natural.Natural -> Integer
    
    8729
    -  integerFromWord :: GHC.Internal.Types.Word -> Integer
    
    8730
    -  integerFromWord# :: GHC.Internal.Prim.Word# -> Integer
    
    8731
    -  integerFromWord64# :: GHC.Internal.Prim.Word64# -> Integer
    
    8732
    -  integerFromWordList :: GHC.Internal.Types.Bool -> [GHC.Internal.Types.Word] -> Integer
    
    8733
    -  integerFromWordNeg# :: GHC.Internal.Prim.Word# -> Integer
    
    8734
    -  integerFromWordSign# :: GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Word# -> Integer
    
    8735
    -  integerGcd :: Integer -> Integer -> Integer
    
    8736
    -  integerGcde :: Integer -> Integer -> (Integer, Integer, Integer)
    
    8737
    -  integerGcde# :: Integer -> Integer -> (# Integer, Integer, Integer #)
    
    8738
    -  integerGe :: Integer -> Integer -> GHC.Internal.Types.Bool
    
    8739
    -  integerGe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8740
    -  integerGt :: Integer -> Integer -> GHC.Internal.Types.Bool
    
    8741
    -  integerGt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8742
    -  integerIsNegative :: Integer -> GHC.Internal.Types.Bool
    
    8743
    -  integerIsNegative# :: Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8744
    -  integerIsOne :: Integer -> GHC.Internal.Types.Bool
    
    8745
    -  integerIsPowerOf2# :: Integer -> (# (# #) | GHC.Internal.Prim.Word# #)
    
    8746
    -  integerIsZero :: Integer -> GHC.Internal.Types.Bool
    
    8747
    -  integerLcm :: Integer -> Integer -> Integer
    
    8748
    -  integerLe :: Integer -> Integer -> GHC.Internal.Types.Bool
    
    8749
    -  integerLe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8750
    -  integerLog2 :: Integer -> GHC.Internal.Types.Word
    
    8751
    -  integerLog2# :: Integer -> GHC.Internal.Prim.Word#
    
    8752
    -  integerLogBase :: Integer -> Integer -> GHC.Internal.Types.Word
    
    8753
    -  integerLogBase# :: Integer -> Integer -> GHC.Internal.Prim.Word#
    
    8754
    -  integerLogBaseWord :: GHC.Internal.Types.Word -> Integer -> GHC.Internal.Types.Word
    
    8755
    -  integerLogBaseWord# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word#
    
    8756
    -  integerLt :: Integer -> Integer -> GHC.Internal.Types.Bool
    
    8757
    -  integerLt# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8758
    -  integerMod :: Integer -> Integer -> Integer
    
    8759
    -  integerMul :: Integer -> Integer -> Integer
    
    8760
    -  integerNe :: Integer -> Integer -> GHC.Internal.Types.Bool
    
    8761
    -  integerNe# :: Integer -> Integer -> GHC.Internal.Bignum.Primitives.Bool#
    
    8762
    -  integerNegate :: Integer -> Integer
    
    8763
    -  integerOne :: Integer
    
    8764
    -  integerOr :: Integer -> Integer -> Integer
    
    8765
    -  integerPopCount# :: Integer -> GHC.Internal.Prim.Int#
    
    8766
    -  integerPowMod# :: Integer -> Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #)
    
    8767
    -  integerQuot :: Integer -> Integer -> Integer
    
    8768
    -  integerQuotRem :: Integer -> Integer -> (Integer, Integer)
    
    8769
    -  integerQuotRem# :: Integer -> Integer -> (# Integer, Integer #)
    
    8770
    -  integerRecipMod# :: Integer -> GHC.Internal.Bignum.Natural.Natural -> (# GHC.Internal.Bignum.Natural.Natural | () #)
    
    8771
    -  integerRem :: Integer -> Integer -> Integer
    
    8772
    -  integerShiftL :: Integer -> GHC.Internal.Types.Word -> Integer
    
    8773
    -  integerShiftL# :: Integer -> GHC.Internal.Prim.Word# -> Integer
    
    8774
    -  integerShiftR :: Integer -> GHC.Internal.Types.Word -> Integer
    
    8775
    -  integerShiftR# :: Integer -> GHC.Internal.Prim.Word# -> Integer
    
    8776
    -  integerSignum :: Integer -> Integer
    
    8777
    -  integerSignum# :: Integer -> GHC.Internal.Prim.Int#
    
    8778
    -  integerSizeInBase# :: GHC.Internal.Prim.Word# -> Integer -> GHC.Internal.Prim.Word#
    
    8779
    -  integerSqr :: Integer -> Integer
    
    8780
    -  integerSub :: Integer -> Integer -> Integer
    
    8781
    -  integerTestBit :: Integer -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
    
    8782
    -  integerTestBit# :: Integer -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8783
    -  integerToAddr :: Integer -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
    
    8784
    -  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# #)
    
    8785
    -  integerToBigNatClamp# :: Integer -> GHC.Internal.Bignum.BigNat.BigNat#
    
    8786
    -  integerToBigNatSign# :: Integer -> (# GHC.Internal.Prim.Int#, GHC.Internal.Bignum.BigNat.BigNat# #)
    
    8787
    -  integerToInt :: Integer -> GHC.Internal.Types.Int
    
    8788
    -  integerToInt# :: Integer -> GHC.Internal.Prim.Int#
    
    8789
    -  integerToInt64# :: Integer -> GHC.Internal.Prim.Int64#
    
    8790
    -  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
    
    8791
    -  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# #)
    
    8792
    -  integerToNatural :: Integer -> GHC.Internal.Bignum.Natural.Natural
    
    8793
    -  integerToNaturalClamp :: Integer -> GHC.Internal.Bignum.Natural.Natural
    
    8794
    -  integerToNaturalThrow :: Integer -> GHC.Internal.Bignum.Natural.Natural
    
    8795
    -  integerToWord :: Integer -> GHC.Internal.Types.Word
    
    8796
    -  integerToWord# :: Integer -> GHC.Internal.Prim.Word#
    
    8797
    -  integerToWord64# :: Integer -> GHC.Internal.Prim.Word64#
    
    8798
    -  integerXor :: Integer -> Integer -> Integer
    
    8799
    -  integerZero :: Integer
    
    8800
    -
    
    8801
    -module GHC.Num.Natural where
    
    8802
    -  -- Safety: None
    
    8803
    -  type Natural :: *
    
    8804
    -  data Natural = NS GHC.Internal.Prim.Word# | NB GHC.Internal.Prim.ByteArray#
    
    8805
    -  naturalAdd :: Natural -> Natural -> Natural
    
    8806
    -  naturalAnd :: Natural -> Natural -> Natural
    
    8807
    -  naturalAndNot :: Natural -> Natural -> Natural
    
    8808
    -  naturalBit :: GHC.Internal.Types.Word -> Natural
    
    8809
    -  naturalBit# :: GHC.Internal.Prim.Word# -> Natural
    
    8810
    -  naturalCheck :: Natural -> GHC.Internal.Types.Bool
    
    8811
    -  naturalCheck# :: Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    8812
    -  naturalClearBit :: Natural -> GHC.Internal.Types.Word -> Natural
    
    8813
    -  naturalClearBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural
    
    8814
    -  naturalCompare :: Natural -> Natural -> GHC.Internal.Types.Ordering
    
    8815
    -  naturalComplementBit :: Natural -> GHC.Internal.Types.Word -> Natural
    
    8816
    -  naturalComplementBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural
    
    8817
    -  naturalEncodeDouble# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Double#
    
    8818
    -  naturalEncodeFloat# :: Natural -> GHC.Internal.Prim.Int# -> GHC.Internal.Prim.Float#
    
    8819
    -  naturalEq :: Natural -> Natural -> GHC.Internal.Types.Bool
    
    8820
    -  naturalEq# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    8821
    -  naturalFromAddr :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO Natural
    
    8822
    -  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 #)
    
    8823
    -  naturalFromBigNat# :: GHC.Internal.Bignum.BigNat.BigNat# -> Natural
    
    8824
    -  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 #)
    
    8825
    -  naturalFromWord :: GHC.Internal.Types.Word -> Natural
    
    8826
    -  naturalFromWord# :: GHC.Internal.Prim.Word# -> Natural
    
    8827
    -  naturalFromWord2# :: GHC.Internal.Prim.Word# -> GHC.Internal.Prim.Word# -> Natural
    
    8828
    -  naturalFromWordList :: [GHC.Internal.Types.Word] -> Natural
    
    8829
    -  naturalGcd :: Natural -> Natural -> Natural
    
    8830
    -  naturalGe :: Natural -> Natural -> GHC.Internal.Types.Bool
    
    8831
    -  naturalGe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    8832
    -  naturalGt :: Natural -> Natural -> GHC.Internal.Types.Bool
    
    8833
    -  naturalGt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    8834
    -  naturalIsOne :: Natural -> GHC.Internal.Types.Bool
    
    8835
    -  naturalIsPowerOf2# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #)
    
    8836
    -  naturalIsZero :: Natural -> GHC.Internal.Types.Bool
    
    8837
    -  naturalLcm :: Natural -> Natural -> Natural
    
    8838
    -  naturalLe :: Natural -> Natural -> GHC.Internal.Types.Bool
    
    8839
    -  naturalLe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    8840
    -  naturalLog2 :: Natural -> GHC.Internal.Types.Word
    
    8841
    -  naturalLog2# :: Natural -> GHC.Internal.Prim.Word#
    
    8842
    -  naturalLogBase :: Natural -> Natural -> GHC.Internal.Types.Word
    
    8843
    -  naturalLogBase# :: Natural -> Natural -> GHC.Internal.Prim.Word#
    
    8844
    -  naturalLogBaseWord :: GHC.Internal.Types.Word -> Natural -> GHC.Internal.Types.Word
    
    8845
    -  naturalLogBaseWord# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word#
    
    8846
    -  naturalLt :: Natural -> Natural -> GHC.Internal.Types.Bool
    
    8847
    -  naturalLt# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    8848
    -  naturalMul :: Natural -> Natural -> Natural
    
    8849
    -  naturalNe :: Natural -> Natural -> GHC.Internal.Types.Bool
    
    8850
    -  naturalNe# :: Natural -> Natural -> GHC.Internal.Bignum.Primitives.Bool#
    
    8851
    -  naturalNegate :: Natural -> Natural
    
    8852
    -  naturalOne :: Natural
    
    8853
    -  naturalOr :: Natural -> Natural -> Natural
    
    8854
    -  naturalPopCount :: Natural -> GHC.Internal.Types.Word
    
    8855
    -  naturalPopCount# :: Natural -> GHC.Internal.Prim.Word#
    
    8856
    -  naturalPowMod :: Natural -> Natural -> Natural -> Natural
    
    8857
    -  naturalQuot :: Natural -> Natural -> Natural
    
    8858
    -  naturalQuotRem :: Natural -> Natural -> (Natural, Natural)
    
    8859
    -  naturalQuotRem# :: Natural -> Natural -> (# Natural, Natural #)
    
    8860
    -  naturalRem :: Natural -> Natural -> Natural
    
    8861
    -  naturalSetBit :: Natural -> GHC.Internal.Types.Word -> Natural
    
    8862
    -  naturalSetBit# :: Natural -> GHC.Internal.Prim.Word# -> Natural
    
    8863
    -  naturalShiftL :: Natural -> GHC.Internal.Types.Word -> Natural
    
    8864
    -  naturalShiftL# :: Natural -> GHC.Internal.Prim.Word# -> Natural
    
    8865
    -  naturalShiftR :: Natural -> GHC.Internal.Types.Word -> Natural
    
    8866
    -  naturalShiftR# :: Natural -> GHC.Internal.Prim.Word# -> Natural
    
    8867
    -  naturalSignum :: Natural -> Natural
    
    8868
    -  naturalSizeInBase# :: GHC.Internal.Prim.Word# -> Natural -> GHC.Internal.Prim.Word#
    
    8869
    -  naturalSqr :: Natural -> Natural
    
    8870
    -  naturalSub :: Natural -> Natural -> (# (# #) | Natural #)
    
    8871
    -  naturalSubThrow :: Natural -> Natural -> Natural
    
    8872
    -  naturalSubUnsafe :: Natural -> Natural -> Natural
    
    8873
    -  naturalTestBit :: Natural -> GHC.Internal.Types.Word -> GHC.Internal.Types.Bool
    
    8874
    -  naturalTestBit# :: Natural -> GHC.Internal.Prim.Word# -> GHC.Internal.Bignum.Primitives.Bool#
    
    8875
    -  naturalToAddr :: Natural -> GHC.Internal.Prim.Addr# -> GHC.Internal.Bignum.Primitives.Bool# -> GHC.Internal.Types.IO GHC.Internal.Types.Word
    
    8876
    -  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# #)
    
    8877
    -  naturalToBigNat# :: Natural -> GHC.Internal.Bignum.BigNat.BigNat#
    
    8878
    -  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# #)
    
    8879
    -  naturalToWord :: Natural -> GHC.Internal.Types.Word
    
    8880
    -  naturalToWord# :: Natural -> GHC.Internal.Prim.Word#
    
    8881
    -  naturalToWordClamp :: Natural -> GHC.Internal.Types.Word
    
    8882
    -  naturalToWordClamp# :: Natural -> GHC.Internal.Prim.Word#
    
    8883
    -  naturalToWordMaybe# :: Natural -> (# (# #) | GHC.Internal.Prim.Word# #)
    
    8884
    -  naturalXor :: Natural -> Natural -> Natural
    
    8885
    -  naturalZero :: Natural
    
    8886
    -
    
    8887 8553
     module GHC.OldList where
    
    8888 8554
       -- Safety: Safe
    
    8889 8555
       (!!) :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> GHC.Internal.Types.Int -> a