summaryrefslogtreecommitdiff
path: root/libraries/integer-gmp/src
diff options
context:
space:
mode:
Diffstat (limited to 'libraries/integer-gmp/src')
-rw-r--r--libraries/integer-gmp/src/GHC/Integer/Logarithms.hs3
-rw-r--r--libraries/integer-gmp/src/GHC/Integer/Type.hs32
2 files changed, 18 insertions, 17 deletions
diff --git a/libraries/integer-gmp/src/GHC/Integer/Logarithms.hs b/libraries/integer-gmp/src/GHC/Integer/Logarithms.hs
index cbcc860002..76467e18a7 100644
--- a/libraries/integer-gmp/src/GHC/Integer/Logarithms.hs
+++ b/libraries/integer-gmp/src/GHC/Integer/Logarithms.hs
@@ -3,6 +3,7 @@
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UnliftedFFITypes #-}
{-# LANGUAGE CPP #-}
+{-# LANGUAGE BangPatterns #-}
module GHC.Integer.Logarithms
( wordLog2#
@@ -43,7 +44,7 @@ integerLogBase# :: Integer -> Integer -> Int#
integerLogBase# (S# 2#) m = integerLog2# m
integerLogBase# b m = e'
where
- (# _, e' #) = go b
+ !(# _, e' #) = go b
go pw | m `ltInteger` pw = (# m, 0# #)
go pw = case go (sqrInteger pw) of
diff --git a/libraries/integer-gmp/src/GHC/Integer/Type.hs b/libraries/integer-gmp/src/GHC/Integer/Type.hs
index 9800f55692..035cb1e7ba 100644
--- a/libraries/integer-gmp/src/GHC/Integer/Type.hs
+++ b/libraries/integer-gmp/src/GHC/Integer/Type.hs
@@ -762,7 +762,7 @@ divModInteger n d
in (# q', r' #)
| True = qr
where
- qr@(# q, r #) = quotRemInteger n d
+ !qr@(# q, r #) = quotRemInteger n d
{-# CONSTANT_FOLDED divModInteger #-}
divInteger :: Integer -> Integer -> Integer
@@ -1036,7 +1036,7 @@ timesBigNatWord !_ 0## = zeroBigNat
timesBigNatWord x 1## = x
timesBigNatWord x@(BN# x#) y#
| isTrue# (nx# ==# 1#) =
- let (# !h#, !l# #) = timesWord2# (bigNatToWord x) y#
+ let !(# !h#, !l# #) = timesWord2# (bigNatToWord x) y#
in wordToBigNat2 h# l#
| True = runS $ do
mbn@(MBN# mba#) <- newBigNat# nx#
@@ -1066,7 +1066,7 @@ bitBigNat i#
_ <- svoid (writeBigNat# mbn li# (uncheckedShiftL# 1## bi#))
unsafeFreezeBigNat# mbn
where
- (# li#, bi# #) = quotRemInt# i# GMP_LIMB_BITS#
+ !(# li#, bi# #) = quotRemInt# i# GMP_LIMB_BITS#
testBitBigNat :: BigNat -> Int# -> Bool
testBitBigNat bn i#
@@ -1074,7 +1074,7 @@ testBitBigNat bn i#
| isTrue# (li# <# nx#) = isTrue# (testBitWord# (indexBigNat# bn li#) bi#)
| True = False
where
- (# li#, bi# #) = quotRemInt# i# GMP_LIMB_BITS#
+ !(# li#, bi# #) = quotRemInt# i# GMP_LIMB_BITS#
nx# = sizeofBigNat# bn
testBitNegBigNat :: BigNat -> Int# -> Bool
@@ -1085,7 +1085,7 @@ testBitNegBigNat bn i#
(indexBigNat# bn li# `minusWord#` 1##) bi#) ==# 0#)
| True = isTrue# ((testBitWord# (indexBigNat# bn li#) bi#) ==# 0#)
where
- (# li#, bi# #) = quotRemInt# i# GMP_LIMB_BITS#
+ !(# li#, bi# #) = quotRemInt# i# GMP_LIMB_BITS#
nx# = sizeofBigNat# bn
allZ 0# = True
@@ -1108,7 +1108,7 @@ shiftLBigNat x@(BN# xba#) n# = runS $ do
where
xn# = sizeofBigNat# x
yn# = xn# +# nlimbs# +# (nbits# /=# 0#)
- (# nlimbs#, nbits# #) = quotRemInt# n# GMP_LIMB_BITS#
+ !(# nlimbs#, nbits# #) = quotRemInt# n# GMP_LIMB_BITS#
@@ -1693,7 +1693,7 @@ resizeMutBigNat# (MBN# mba0#) nsz# s
(# s'', mba# #) -> (# s'', MBN# mba# #)
where
bsz# = nsz# `uncheckedIShiftL#` GMP_LIMB_SHIFT#
- (# s', n# #) = getSizeofMutableByteArray# mba0# s
+ !(# s', n# #) = getSizeofMutableByteArray# mba0# s
shrinkMutBigNat# :: MutBigNat s -> GmpSize# -> State# s -> State# s
shrinkMutBigNat# (MBN# mba0#) nsz# s
@@ -1701,13 +1701,13 @@ shrinkMutBigNat# (MBN# mba0#) nsz# s
| True = shrinkMutableByteArray# mba0# bsz# s'
where
bsz# = nsz# `uncheckedIShiftL#` GMP_LIMB_SHIFT#
- (# s', n# #) = getSizeofMutableByteArray# mba0# s
+ !(# s', n# #) = getSizeofMutableByteArray# mba0# s
unsafeSnocFreezeBigNat# :: MutBigNat s -> GmpLimb# -> S s BigNat
unsafeSnocFreezeBigNat# mbn0@(MBN# mba0#) limb# s = go s'
where
n# = nb0# `uncheckedIShiftRL#` GMP_LIMB_SHIFT#
- (# s', nb0# #) = getSizeofMutableByteArray# mba0# s
+ !(# s', nb0# #) = getSizeofMutableByteArray# mba0# s
go = do
(MBN# mba#) <- resizeMutBigNat# mbn0 (n# +# 1#)
_ <- svoid (writeWordArray# mba# n# limb#)
@@ -1721,8 +1721,8 @@ unsafeRenormFreezeBigNat# mbn s
| isTrue# (n# ==# n0#) = (unsafeFreezeBigNat# mbn) s''
| True = (unsafeShrinkFreezeBigNat# mbn n#) s''
where
- (# s', n0# #) = getSizeofMutBigNat# mbn s
- (# s'', n# #) = normSizeofMutBigNat'# mbn n0# s'
+ !(# s', n0# #) = getSizeofMutBigNat# mbn s
+ !(# s'', n# #) = normSizeofMutBigNat'# mbn n0# s'
-- | Shrink MBN
unsafeShrinkFreezeBigNat# :: MutBigNat s -> GmpSize# -> S s BigNat
@@ -1752,7 +1752,7 @@ copyWordArray# src src_ofs dst dst_ofs len
normSizeofMutBigNat# :: MutBigNat s -> State# s -> (# State# s, Int# #)
normSizeofMutBigNat# mbn@(MBN# mba) s = normSizeofMutBigNat'# mbn sz# s'
where
- (# s', n# #) = getSizeofMutableByteArray# mba s
+ !(# s', n# #) = getSizeofMutableByteArray# mba s
sz# = n# `uncheckedIShiftRA#` GMP_LIMB_SHIFT#
-- | Find most-significant non-zero limb and return its index-position
@@ -1783,13 +1783,13 @@ byteArrayToBigNat# ba# n0#
| isTrue# (baszr# ==# 0#) -- i.e. ba# is multiple of limb-size
, isTrue# (baszq# ==# n#) = (BN# ba#)
| True = runS $ \s ->
- let (# s', mbn@(MBN# mba#) #) = newBigNat# n# s
- (# s'', ba_sz# #) = getSizeofMutableByteArray# mba# s'
+ let !(# s', mbn@(MBN# mba#) #) = newBigNat# n# s
+ !(# s'', ba_sz# #) = getSizeofMutableByteArray# mba# s'
go = do _ <- svoid (copyByteArray# ba# 0# mba# 0# ba_sz# )
unsafeFreezeBigNat# mbn
in go s''
where
- (# baszq#, baszr# #) = quotRemInt# (sizeofByteArray# ba#) GMP_LIMB_BYTES#
+ !(# baszq#, baszr# #) = quotRemInt# (sizeofByteArray# ba#) GMP_LIMB_BYTES#
n# = fmssl (n0# -# 1#)
@@ -1914,7 +1914,7 @@ isValidBigNat# (BN# ba#)
sz# = sizeofByteArray# ba#
- (# szq#, szr# #) = quotRemInt# sz# GMP_LIMB_BYTES#
+ !(# szq#, szr# #) = quotRemInt# sz# GMP_LIMB_BYTES#
-- | Version of 'nextPrimeInteger' operating on 'BigNat's
--