{-# LANGUAGE CPP #-}
{-# LANGUAGE UnboxedTuples #-}
module Clash.Sized.Internal.Mod where
#if MIN_VERSION_base(4,15,0)
import GHC.Exts (eqWord#, leWord#, word2Int#)
#else
import GHC.Exts ((==#))
#endif
import GHC.Exts
((<=#), geWord#, isTrue#, minusWord#, plusWord#, uncheckedShiftL#, xor#,
timesWord2#, quotRemWord2#, and#)
#if MIN_VERSION_base(4,12,0)
import GHC.Exts (addWordC#)
#endif
#if !MIN_VERSION_base(4,12,0)
import GHC.Exts (Int#, Word#, plusWord2#, word2Int#)
#endif
#if MIN_VERSION_base(4,15,0)
import GHC.Num.BigNat
(BigNat#, bigNatAdd, bigNatAddWord#, bigNatAnd, bigNatBit#, bigNatCompare,
bigNatFromWord#, bigNatFromWord2#, bigNatMul, bigNatMulWord#, bigNatRem,
bigNatSize#, bigNatSubUnsafe, bigNatSubWordUnsafe#, bigNatToWord#, bigNatXor)
import GHC.Num.Natural (Natural (..))
#else
import GHC.Natural (Natural (..))
import GHC.Integer.GMP.Internals
(BigNat, Integer (..), bigNatToWord, compareBigNat, minusBigNat, minusBigNatWord,
plusBigNat, plusBigNatWord, sizeofBigNat#, bitBigNat, wordToBigNat2,
remBigNat, timesBigNat, timesBigNatWord, xorBigNat, wordToBigNat, andBigNat)
#endif
#if !MIN_VERSION_base(4,12,0)
import GHC.Integer.GMP.Internals (wordToInteger)
#endif
#include "MachDeps.h"
#if MIN_VERSION_base(4,15,0)
subMod :: Natural -> Natural -> Natural -> Natural
subMod (NS m#) (NS x#) (NS y#) =
if isTrue# (x# `geWord#` y#) then NS z# else NS (z# `plusWord#` m#)
where
z# = x# `minusWord#` y#
subMod NS{} _ _ = brokenInvariant
subMod (NB m#) (NS x#) (NS y#) =
if isTrue# (x# `geWord#` y#)
then NS (x# `minusWord#` y#)
else bigNatToNat (m# `bigNatSubWordUnsafe#` (y# `minusWord#` x#))
subMod (NB m#) (NS x#) (NB y#) =
bigNatToNat ((m# `bigNatSubUnsafe` y#) `bigNatAddWord#` x#)
subMod NB{} (NB x#) (NS y#) =
bigNatToNat (x# `bigNatSubWordUnsafe#` y#)
subMod (NB m#) (NB x#) (NB y#) = case x# `bigNatCompare` y# of
LT -> bigNatToNat ((m# `bigNatSubUnsafe` y#) `bigNatAdd` x#)
EQ -> NS 0##
GT -> bigNatToNat (x# `bigNatSubUnsafe` y#)
addMod :: Natural -> Natural -> Natural -> Natural
addMod (NS m#) (NS x#) (NS y#) =
if isTrue# c# || isTrue# (z# `geWord#` m#) then NS (z# `minusWord#` m#) else NS z#
where
!(# z#, c# #) = x# `addWordC#` y#
addMod NS{} _ _ = brokenInvariant
addMod (NB m#) (NS x#) (NS y#) =
if isTrue# c# then subIfGe (bigNatFromWord2# 1## z#) m# else NS z#
where
!(# z#, c# #) = x# `addWordC#` y#
addMod (NB m#) (NS x#) (NB y#) = subIfGe (y# `bigNatAddWord#` x#) m#
addMod (NB m#) (NB x#) (NS y#) = subIfGe (x# `bigNatAddWord#` y#) m#
addMod (NB m#) (NB x#) (NB y#) = subIfGe (x# `bigNatAdd` y#) m#
mulMod :: Natural -> Natural -> Natural -> Natural
mulMod (NS m#) (NS x#) (NS y#) = NS r#
where
!(# z1#, z2# #) = timesWord2# x# y#
!(# _, r# #) = quotRemWord2# z1# z2# m#
mulMod NS{} _ _ = brokenInvariant
mulMod (NB m#) (NS x#) (NS y#) =
bigNatToNat (bigNatFromWord2# z1# z2# `bigNatRem` m#)
where
!(# z1#, z2# #) = timesWord2# x# y#
mulMod (NB m#) (NS x#) (NB y#) =
bigNatToNat ((y# `bigNatMulWord#` x#) `bigNatRem` m#)
mulMod (NB m#) (NB x#) (NS y#) =
bigNatToNat ((x# `bigNatMulWord#` y#) `bigNatRem` m#)
mulMod (NB m#) (NB x#) (NB y#) =
bigNatToNat ((x# `bigNatMul` y#) `bigNatRem` m#)
mulMod2 :: Natural -> Natural -> Natural -> Natural
mulMod2 (NS m#) (NS x#) (NS y#) = NS (z2# `and#` m#)
where
!(# _, z2# #) = timesWord2# x# y#
mulMod2 NS{} _ _ = brokenInvariant
mulMod2 (NB m#) (NS x#) (NS y#) =
bigNatToNat (bigNatFromWord2# z1# z2# `bigNatAnd` m#)
where
!(# z1#, z2# #) = timesWord2# x# y#
mulMod2 (NB m#) (NS x#) (NB y#) =
bigNatToNat ((y# `bigNatMulWord#` x#) `bigNatAnd` m#)
mulMod2 (NB m#) (NB x#) (NS y#) =
bigNatToNat ((x# `bigNatMulWord#` y#) `bigNatAnd` m#)
mulMod2 (NB m#) (NB x#) (NB y#) =
bigNatToNat ((x# `bigNatMul` y#) `bigNatAnd` m#)
negateMod :: Natural -> Natural -> Natural
negateMod _ (NS 0##) = NS 0##
negateMod (NS m#) (NS x#) = NS (m# `minusWord#` x#)
negateMod NS{} _ = brokenInvariant
negateMod (NB m#) (NS x#) = bigNatToNat (m# `bigNatSubWordUnsafe#` x#)
negateMod (NB m#) (NB x#) = bigNatToNat (m# `bigNatSubUnsafe` x#)
complementMod
:: Natural
-> (Natural -> Natural)
complementMod (NS sz#) =
if isTrue# (sz# `leWord#` WORD_SIZE_IN_BITS##) then
let m# = if isTrue# (sz# `eqWord#` WORD_SIZE_IN_BITS##) then
#if WORD_SIZE_IN_BITS == 64
0xFFFFFFFFFFFFFFFF##
#elif WORD_SIZE_IN_BITS == 32
0xFFFFFFFF##
#else
#error Unhandled value for WORD_SIZE_IN_BITS
#endif
else
(1## `uncheckedShiftL#` (word2Int# sz#)) `minusWord#` 1##
go (NS x#) = NS (x# `xor#` m#)
go (NB r#) = NS (bigNatToWord# r# `xor#` m#)
in go
else
let m# = bigNatBit# sz# `bigNatSubWordUnsafe#` 1##
go (NS x#) = bigNatToNat (bigNatXor (bigNatFromWord# x#) m#)
go (NB x#) = bigNatToNat (bigNatXor x# m#)
in go
complementMod _ = error "size too large"
maskMod
:: Natural
-> (Natural -> Natural)
maskMod (NS sz#) =
if isTrue# (sz# `leWord#` WORD_SIZE_IN_BITS##) then
if isTrue# (sz# `eqWord#` WORD_SIZE_IN_BITS##) then
let go (NB x#) = NS (bigNatToWord# x#)
go n = n
in go
else
let m# = (1## `uncheckedShiftL#` (word2Int# sz#)) `minusWord#` 1##
go (NS x#) = NS (x# `and#` m#)
go (NB x#) = NS (bigNatToWord# x# `and#` m#)
in go
else
let m# = bigNatBit# sz#
go (NB x#) = bigNatToNat (bigNatRem x# m#)
go x = x
in go
maskMod _ = error "size too large"
bigNatToNat :: BigNat# -> Natural
bigNatToNat r# =
if isTrue# (bigNatSize# r# <=# 1#) then
NS (bigNatToWord# r#)
else
NB r#
subIfGe :: BigNat# -> BigNat# -> Natural
subIfGe z# m# = case z# `bigNatCompare` m# of
LT -> NB z#
EQ -> NS 0##
GT -> bigNatToNat (z# `bigNatSubUnsafe` m#)
#else
subMod :: Natural -> Natural -> Natural -> Natural
subMod :: Natural -> Natural -> Natural -> Natural
subMod (NatS# GmpLimb#
m#) (NatS# GmpLimb#
x#) (NatS# GmpLimb#
y#) =
if Int# -> Bool
isTrue# (GmpLimb#
x# GmpLimb# -> GmpLimb# -> Int#
`geWord#` GmpLimb#
y#) then GmpLimb# -> Natural
NatS# GmpLimb#
z# else GmpLimb# -> Natural
NatS# (GmpLimb#
z# GmpLimb# -> GmpLimb# -> GmpLimb#
`plusWord#` GmpLimb#
m#)
where
z# :: GmpLimb#
z# = GmpLimb#
x# GmpLimb# -> GmpLimb# -> GmpLimb#
`minusWord#` GmpLimb#
y#
subMod NatS#{} Natural
_ Natural
_ = Natural
forall a. a
brokenInvariant
subMod (NatJ# BigNat
m#) (NatS# GmpLimb#
x#) (NatS# GmpLimb#
y#) =
if Int# -> Bool
isTrue# (GmpLimb#
x# GmpLimb# -> GmpLimb# -> Int#
`geWord#` GmpLimb#
y#)
then GmpLimb# -> Natural
NatS# (GmpLimb#
x# GmpLimb# -> GmpLimb# -> GmpLimb#
`minusWord#` GmpLimb#
y#)
else BigNat -> Natural
bigNatToNat (BigNat -> Natural) -> BigNat -> Natural
forall a b. (a -> b) -> a -> b
$ BigNat
m# BigNat -> GmpLimb# -> BigNat
`minusBigNatWord` (GmpLimb#
y# GmpLimb# -> GmpLimb# -> GmpLimb#
`minusWord#` GmpLimb#
x#)
subMod (NatJ# BigNat
m#) (NatS# GmpLimb#
x#) (NatJ# BigNat
y#) =
BigNat -> Natural
bigNatToNat (BigNat -> Natural) -> BigNat -> Natural
forall a b. (a -> b) -> a -> b
$ (BigNat
m# BigNat -> BigNat -> BigNat
`minusBigNat` BigNat
y#) BigNat -> GmpLimb# -> BigNat
`plusBigNatWord` GmpLimb#
x#
subMod NatJ#{} (NatJ# BigNat
x#) (NatS# GmpLimb#
y#) =
BigNat -> Natural
bigNatToNat (BigNat -> Natural) -> BigNat -> Natural
forall a b. (a -> b) -> a -> b
$ BigNat
x# BigNat -> GmpLimb# -> BigNat
`minusBigNatWord` GmpLimb#
y#
subMod (NatJ# BigNat
m#) (NatJ# BigNat
x#) (NatJ# BigNat
y#) = case BigNat
x# BigNat -> BigNat -> Ordering
`compareBigNat` BigNat
y# of
Ordering
LT -> BigNat -> Natural
bigNatToNat (BigNat -> Natural) -> BigNat -> Natural
forall a b. (a -> b) -> a -> b
$ (BigNat
m# BigNat -> BigNat -> BigNat
`minusBigNat` BigNat
y#) BigNat -> BigNat -> BigNat
`plusBigNat` BigNat
x#
Ordering
EQ -> GmpLimb# -> Natural
NatS# GmpLimb#
0##
Ordering
GT -> BigNat -> Natural
bigNatToNat (BigNat -> Natural) -> BigNat -> Natural
forall a b. (a -> b) -> a -> b
$ BigNat
x# BigNat -> BigNat -> BigNat
`minusBigNat` BigNat
y#
addMod :: Natural -> Natural -> Natural -> Natural
addMod :: Natural -> Natural -> Natural -> Natural
addMod (NatS# GmpLimb#
m#) (NatS# GmpLimb#
x#) (NatS# GmpLimb#
y#) =
if Int# -> Bool
isTrue# Int#
c# Bool -> Bool -> Bool
|| Int# -> Bool
isTrue# (GmpLimb#
z# GmpLimb# -> GmpLimb# -> Int#
`geWord#` GmpLimb#
m#) then GmpLimb# -> Natural
NatS# (GmpLimb#
z# GmpLimb# -> GmpLimb# -> GmpLimb#
`minusWord#` GmpLimb#
m#) else GmpLimb# -> Natural
NatS# GmpLimb#
z#
where
!(# GmpLimb#
z#, Int#
c# #) = GmpLimb#
x# GmpLimb# -> GmpLimb# -> (# GmpLimb#, Int# #)
`addWordC#` GmpLimb#
y#
addMod NatS#{} Natural
_ Natural
_ = Natural
forall a. a
brokenInvariant
addMod (NatJ# BigNat
m#) (NatS# GmpLimb#
x#) (NatS# GmpLimb#
y#) =
if Int# -> Bool
isTrue# Int#
c# then BigNat -> BigNat -> Natural
subIfGe (GmpLimb# -> GmpLimb# -> BigNat
wordToBigNat2 GmpLimb#
1## GmpLimb#
z#) BigNat
m# else GmpLimb# -> Natural
NatS# GmpLimb#
z#
where
!(# GmpLimb#
z#, Int#
c# #) = GmpLimb#
x# GmpLimb# -> GmpLimb# -> (# GmpLimb#, Int# #)
`addWordC#` GmpLimb#
y#
addMod (NatJ# BigNat
m#) (NatS# GmpLimb#
x#) (NatJ# BigNat
y#) = BigNat -> BigNat -> Natural
subIfGe (BigNat
y# BigNat -> GmpLimb# -> BigNat
`plusBigNatWord` GmpLimb#
x#) BigNat
m#
addMod (NatJ# BigNat
m#) (NatJ# BigNat
x#) (NatS# GmpLimb#
y#) = BigNat -> BigNat -> Natural
subIfGe (BigNat
x# BigNat -> GmpLimb# -> BigNat
`plusBigNatWord` GmpLimb#
y#) BigNat
m#
addMod (NatJ# BigNat
m#) (NatJ# BigNat
x#) (NatJ# BigNat
y#) = BigNat -> BigNat -> Natural
subIfGe (BigNat
x# BigNat -> BigNat -> BigNat
`plusBigNat` BigNat
y#) BigNat
m#
mulMod :: Natural -> Natural -> Natural -> Natural
mulMod :: Natural -> Natural -> Natural -> Natural
mulMod (NatS# GmpLimb#
m#) (NatS# GmpLimb#
x#) (NatS# GmpLimb#
y#) = GmpLimb# -> Natural
NatS# GmpLimb#
r#
where
!(# GmpLimb#
z1#, GmpLimb#
z2# #) = GmpLimb# -> GmpLimb# -> (# GmpLimb#, GmpLimb# #)
timesWord2# GmpLimb#
x# GmpLimb#
y#
!(# GmpLimb#
_, GmpLimb#
r# #) = GmpLimb# -> GmpLimb# -> GmpLimb# -> (# GmpLimb#, GmpLimb# #)
quotRemWord2# GmpLimb#
z1# GmpLimb#
z2# GmpLimb#
m#
mulMod NatS#{} Natural
_ Natural
_ = Natural
forall a. a
brokenInvariant
mulMod (NatJ# BigNat
m#) (NatS# GmpLimb#
x#) (NatS# GmpLimb#
y#) =
BigNat -> Natural
bigNatToNat (BigNat -> Natural) -> BigNat -> Natural
forall a b. (a -> b) -> a -> b
$ GmpLimb# -> GmpLimb# -> BigNat
wordToBigNat2 GmpLimb#
z1# GmpLimb#
z2# BigNat -> BigNat -> BigNat
`remBigNat` BigNat
m#
where
!(# GmpLimb#
z1#, GmpLimb#
z2# #) = GmpLimb# -> GmpLimb# -> (# GmpLimb#, GmpLimb# #)
timesWord2# GmpLimb#
x# GmpLimb#
y#
mulMod (NatJ# BigNat
m#) (NatS# GmpLimb#
x#) (NatJ# BigNat
y#) =
BigNat -> Natural
bigNatToNat (BigNat -> Natural) -> BigNat -> Natural
forall a b. (a -> b) -> a -> b
$ (BigNat
y# BigNat -> GmpLimb# -> BigNat
`timesBigNatWord` GmpLimb#
x#) BigNat -> BigNat -> BigNat
`remBigNat` BigNat
m#
mulMod (NatJ# BigNat
m#) (NatJ# BigNat
x#) (NatS# GmpLimb#
y#) =
BigNat -> Natural
bigNatToNat (BigNat -> Natural) -> BigNat -> Natural
forall a b. (a -> b) -> a -> b
$ (BigNat
x# BigNat -> GmpLimb# -> BigNat
`timesBigNatWord` GmpLimb#
y#) BigNat -> BigNat -> BigNat
`remBigNat` BigNat
m#
mulMod (NatJ# BigNat
m#) (NatJ# BigNat
x#) (NatJ# BigNat
y#) =
BigNat -> Natural
bigNatToNat (BigNat -> Natural) -> BigNat -> Natural
forall a b. (a -> b) -> a -> b
$ (BigNat
x# BigNat -> BigNat -> BigNat
`timesBigNat` BigNat
y#) BigNat -> BigNat -> BigNat
`remBigNat` BigNat
m#
mulMod2 :: Natural -> Natural -> Natural -> Natural
mulMod2 :: Natural -> Natural -> Natural -> Natural
mulMod2 (NatS# GmpLimb#
m#) (NatS# GmpLimb#
x#) (NatS# GmpLimb#
y#) = GmpLimb# -> Natural
NatS# (GmpLimb#
z2# GmpLimb# -> GmpLimb# -> GmpLimb#
`and#` GmpLimb#
m#)
where
!(# GmpLimb#
_, GmpLimb#
z2# #) = GmpLimb# -> GmpLimb# -> (# GmpLimb#, GmpLimb# #)
timesWord2# GmpLimb#
x# GmpLimb#
y#
mulMod2 NatS#{} Natural
_ Natural
_ = Natural
forall a. a
brokenInvariant
mulMod2 (NatJ# BigNat
m#) (NatS# GmpLimb#
x#) (NatS# GmpLimb#
y#) =
BigNat -> Natural
bigNatToNat (BigNat -> Natural) -> BigNat -> Natural
forall a b. (a -> b) -> a -> b
$ GmpLimb# -> GmpLimb# -> BigNat
wordToBigNat2 GmpLimb#
z1# GmpLimb#
z2# BigNat -> BigNat -> BigNat
`andBigNat` BigNat
m#
where
!(# GmpLimb#
z1#, GmpLimb#
z2# #) = GmpLimb# -> GmpLimb# -> (# GmpLimb#, GmpLimb# #)
timesWord2# GmpLimb#
x# GmpLimb#
y#
mulMod2 (NatJ# BigNat
m#) (NatS# GmpLimb#
x#) (NatJ# BigNat
y#) =
BigNat -> Natural
bigNatToNat (BigNat -> Natural) -> BigNat -> Natural
forall a b. (a -> b) -> a -> b
$ (BigNat
y# BigNat -> GmpLimb# -> BigNat
`timesBigNatWord` GmpLimb#
x#) BigNat -> BigNat -> BigNat
`andBigNat` BigNat
m#
mulMod2 (NatJ# BigNat
m#) (NatJ# BigNat
x#) (NatS# GmpLimb#
y#) =
BigNat -> Natural
bigNatToNat (BigNat -> Natural) -> BigNat -> Natural
forall a b. (a -> b) -> a -> b
$ (BigNat
x# BigNat -> GmpLimb# -> BigNat
`timesBigNatWord` GmpLimb#
y#) BigNat -> BigNat -> BigNat
`andBigNat` BigNat
m#
mulMod2 (NatJ# BigNat
m#) (NatJ# BigNat
x#) (NatJ# BigNat
y#) =
BigNat -> Natural
bigNatToNat (BigNat -> Natural) -> BigNat -> Natural
forall a b. (a -> b) -> a -> b
$ (BigNat
x# BigNat -> BigNat -> BigNat
`timesBigNat` BigNat
y#) BigNat -> BigNat -> BigNat
`andBigNat` BigNat
m#
negateMod :: Natural -> Natural -> Natural
negateMod :: Natural -> Natural -> Natural
negateMod Natural
_ (NatS# GmpLimb#
0##) = GmpLimb# -> Natural
NatS# GmpLimb#
0##
negateMod (NatS# GmpLimb#
m#) (NatS# GmpLimb#
x#) = GmpLimb# -> Natural
NatS# (GmpLimb#
m# GmpLimb# -> GmpLimb# -> GmpLimb#
`minusWord#` GmpLimb#
x#)
negateMod NatS#{} Natural
_ = Natural
forall a. a
brokenInvariant
negateMod (NatJ# BigNat
m#) (NatS# GmpLimb#
x#) = BigNat -> Natural
bigNatToNat (BigNat -> Natural) -> BigNat -> Natural
forall a b. (a -> b) -> a -> b
$ BigNat
m# BigNat -> GmpLimb# -> BigNat
`minusBigNatWord` GmpLimb#
x#
negateMod (NatJ# BigNat
m#) (NatJ# BigNat
x#) = BigNat -> Natural
bigNatToNat (BigNat -> Natural) -> BigNat -> Natural
forall a b. (a -> b) -> a -> b
$ BigNat
m# BigNat -> BigNat -> BigNat
`minusBigNat` BigNat
x#
complementMod
:: Integer
-> (Natural -> Natural)
complementMod :: Integer -> Natural -> Natural
complementMod (S# Int#
sz#) =
if Int# -> Bool
isTrue# (Int#
sz# Int# -> Int# -> Int#
<=# WORD_SIZE_IN_BITS#) then
let m# :: GmpLimb#
m# = if Int# -> Bool
isTrue# (Int#
sz# Int# -> Int# -> Int#
==# WORD_SIZE_IN_BITS#) then
#if WORD_SIZE_IN_BITS == 64
GmpLimb#
0xFFFFFFFFFFFFFFFF##
#elif WORD_SIZE_IN_BITS == 32
0xFFFFFFFF##
#else
#error Unhandled value for WORD_SIZE_IN_BITS
#endif
else
(GmpLimb#
1## GmpLimb# -> Int# -> GmpLimb#
`uncheckedShiftL#` Int#
sz#) GmpLimb# -> GmpLimb# -> GmpLimb#
`minusWord#` GmpLimb#
1##
go :: Natural -> Natural
go (NatS# GmpLimb#
x#) = GmpLimb# -> Natural
NatS# (GmpLimb#
x# GmpLimb# -> GmpLimb# -> GmpLimb#
`xor#` GmpLimb#
m#)
go (NatJ# BigNat
r#) = GmpLimb# -> Natural
NatS# (BigNat -> GmpLimb#
bigNatToWord BigNat
r# GmpLimb# -> GmpLimb# -> GmpLimb#
`xor#` GmpLimb#
m#)
in Natural -> Natural
go
else
let m# :: BigNat
m# = Int# -> BigNat
bitBigNat Int#
sz# BigNat -> GmpLimb# -> BigNat
`minusBigNatWord` GmpLimb#
1##
go :: Natural -> Natural
go (NatS# GmpLimb#
x#) = BigNat -> Natural
bigNatToNat (BigNat -> BigNat -> BigNat
xorBigNat (GmpLimb# -> BigNat
wordToBigNat GmpLimb#
x#) BigNat
m#)
go (NatJ# BigNat
x#) = BigNat -> Natural
bigNatToNat (BigNat -> BigNat -> BigNat
xorBigNat BigNat
x# BigNat
m#)
in Natural -> Natural
go
complementMod Integer
_ = [Char] -> Natural -> Natural
forall a. HasCallStack => [Char] -> a
error [Char]
"size too large"
maskMod
:: Integer
-> (Natural -> Natural)
maskMod :: Integer -> Natural -> Natural
maskMod (S# Int#
sz#) =
if Int# -> Bool
isTrue# (Int#
sz# Int# -> Int# -> Int#
<=# WORD_SIZE_IN_BITS#) then
if Int# -> Bool
isTrue# (Int#
sz# Int# -> Int# -> Int#
==# WORD_SIZE_IN_BITS#) then
let go :: Natural -> Natural
go (NatJ# BigNat
x#) = GmpLimb# -> Natural
NatS# (BigNat -> GmpLimb#
bigNatToWord BigNat
x#)
go Natural
n = Natural
n
in Natural -> Natural
go
else
let m# :: GmpLimb#
m# = (GmpLimb#
1## GmpLimb# -> Int# -> GmpLimb#
`uncheckedShiftL#` Int#
sz#) GmpLimb# -> GmpLimb# -> GmpLimb#
`minusWord#` GmpLimb#
1##
go :: Natural -> Natural
go (NatS# GmpLimb#
x#) = GmpLimb# -> Natural
NatS# (GmpLimb#
x# GmpLimb# -> GmpLimb# -> GmpLimb#
`and#` GmpLimb#
m#)
go (NatJ# BigNat
x#) = GmpLimb# -> Natural
NatS# (BigNat -> GmpLimb#
bigNatToWord BigNat
x# GmpLimb# -> GmpLimb# -> GmpLimb#
`and#` GmpLimb#
m#)
in Natural -> Natural
go
else
let m# :: BigNat
m# = Int# -> BigNat
bitBigNat Int#
sz#
go :: Natural -> Natural
go (NatJ# BigNat
x#) = BigNat -> Natural
bigNatToNat (BigNat -> BigNat -> BigNat
remBigNat BigNat
x# BigNat
m#)
go Natural
x = Natural
x
in Natural -> Natural
go
maskMod Integer
_ = [Char] -> Natural -> Natural
forall a. HasCallStack => [Char] -> a
error [Char]
"size too large"
bigNatToNat :: BigNat -> Natural
bigNatToNat :: BigNat -> Natural
bigNatToNat BigNat
r# =
if Int# -> Bool
isTrue# (BigNat -> Int#
sizeofBigNat# BigNat
r# Int# -> Int# -> Int#
==# Int#
1#) then
GmpLimb# -> Natural
NatS# (BigNat -> GmpLimb#
bigNatToWord BigNat
r#)
else
BigNat -> Natural
NatJ# BigNat
r#
subIfGe :: BigNat -> BigNat -> Natural
subIfGe :: BigNat -> BigNat -> Natural
subIfGe BigNat
z# BigNat
m# = case BigNat
z# BigNat -> BigNat -> Ordering
`compareBigNat` BigNat
m# of
Ordering
LT -> BigNat -> Natural
NatJ# BigNat
z#
Ordering
EQ -> GmpLimb# -> Natural
NatS# GmpLimb#
0##
Ordering
GT -> BigNat -> Natural
bigNatToNat (BigNat -> Natural) -> BigNat -> Natural
forall a b. (a -> b) -> a -> b
$ BigNat
z# BigNat -> BigNat -> BigNat
`minusBigNat` BigNat
m#
#if !MIN_VERSION_base(4,12,0)
addWordC# :: Word# -> Word# -> (# Word#, Int# #)
addWordC# x# y# = (# z#, word2Int# c# #)
where
!(# c#, z# #) = x# `plusWord2#` y#
naturalToInteger :: Natural -> Integer
naturalToInteger (NatS# w) = wordToInteger w
naturalToInteger (NatJ# bn) = Jp# bn
#endif
#endif
brokenInvariant :: a
brokenInvariant :: a
brokenInvariant = [Char] -> a
forall a. HasCallStack => [Char] -> a
error [Char]
"argument is larger than modulo"