Skip to content
Snippets Groups Projects
Commit d613ed76 authored by Sylvain Henry's avatar Sylvain Henry Committed by Marge Bot
Browse files

Bignum: add backward compat integer-gmp functions

Also enhance bigNatCheck# and isValidNatural test
parent ef2ae81a
No related branches found
No related tags found
No related merge requests found
......@@ -3,8 +3,16 @@
import GHC.Num.Natural
import GHC.Num.BigNat
import GHC.Exts
import GHC.IO
main = print $ map naturalCheck [0, 1, maxWord, maxWord + 1, invalid]
where
maxWord = fromIntegral (maxBound :: Word)
invalid = NB (bigNatOne# (# #)) -- 1 would fit into the NS constructor.
main = do
let
maxWord = fromIntegral (maxBound :: Word)
invalid = NB (bigNatOne# (# #)) -- 1 would fit into the NS constructor.
-- byteArray whose size is not a multiple of Word size
invalid2 <- IO $ \s -> case newByteArray# 27# s of
(# s', mba #) -> case unsafeFreezeByteArray# mba s' of
(# s'', ba #) -> (# s'', NB ba #)
print $ map naturalCheck [0, 1, maxWord, maxWord + 1, invalid, invalid2]
[True,True,True,True,False]
[True,True,True,True,False,False]
......@@ -80,6 +80,10 @@ data BigNat = BN# { unBigNat :: BigNat# }
bigNatCheck# :: BigNat# -> Bool#
bigNatCheck# bn
| 0# <- bigNatSize# bn = 1#
-- check that size is a multiple of Word size
| r <- remInt# (sizeofByteArray# bn) WORD_SIZE_IN_BYTES#
, isTrue# (r /=# 0#) = 0#
-- check that most-significant limb isn't zero
| 0## <- bigNatIndex# bn (bigNatSize# bn -# 1#) = 0#
| True = 1#
......
......@@ -42,12 +42,20 @@ module GHC.Integer.GMP.Internals
, GmpLimb, GmpLimb#
, GmpSize, GmpSize#
-- **
, isValidBigNat#
, sizeofBigNat#
, zeroBigNat
, oneBigNat
) where
import GHC.Integer
import GHC.Natural
import GHC.Num.Integer (Integer(..))
import qualified GHC.Num.Integer as I
import qualified GHC.Num.BigNat as B
import GHC.Types
import GHC.Prim
......@@ -112,3 +120,19 @@ type GmpLimb = Word
type GmpLimb# = Word#
type GmpSize = Int
type GmpSize# = Int#
{-# DEPRECATED sizeofBigNat# "Use bigNatSize# instead" #-}
sizeofBigNat# :: BigNat -> GmpSize#
sizeofBigNat# (BN# i) = B.bigNatSize# i
{-# DEPRECATED isValidBigNat# "Use bigNatCheck# instead" #-}
isValidBigNat# :: BigNat -> Int#
isValidBigNat# (BN# i) = B.bigNatCheck# i
{-# DEPRECATED zeroBigNat "Use bigNatZero instead" #-}
zeroBigNat :: BigNat
zeroBigNat = B.bigNatZero
{-# DEPRECATED oneBigNat "Use bigNatOne instead" #-}
oneBigNat :: BigNat
oneBigNat = B.bigNatOne
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment