{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE UnboxedSums #-}
{-# LANGUAGE UnboxedTuples #-}

-- |
-- Module      :  GHC.Num.Compat
-- Description :  Defines numeric compatibility shims that work with both
--                ghc-bignum (GHC 9.0+) and integer-gmp (older GHCs).
-- Copyright   :  (c) 2021 Galois, Inc.
-- License     :  BSD3
-- Maintainer  :  cryptol@galois.com
-- Stability   :  provisional
-- Portability :  portable
module GHC.Num.Compat
  ( -- * BigNat#
    BigNat#
  , bigNatAdd
  , bigNatIsOne
  , bigNatIsZero
  , bigNatMul
  , bigNatRem
  , bigNatSqr
  , bigNatSub
  , bigNatSubUnsafe
  , oneBigNat
  , recipModBigNat
  , shiftLBigNat
  , shiftRBigNat
  , testBitBigNat
  , zeroBigNat

    -- * Integer
  , Integer(IS, IP, IN)
  , integerRecipMod

    -- * Conversions
  , bigNatToInteger
  , integerToBigNat
  ) where

#if defined(MIN_VERSION_ghc_bignum)
import           GHC.Num.BigNat (BigNat#, bigNatAdd, bigNatIsOne, bigNatIsZero, bigNatMul, bigNatRem, bigNatSqr, bigNatSub, bigNatSubUnsafe)
import qualified GHC.Num.Backend as BN
import qualified GHC.Num.BigNat as BN
import           GHC.Num.Integer (Integer(IS, IP, IN))
import qualified GHC.Num.Integer as Integer
import           GHC.Exts

-- | Coerce a @BigNat#@ to an integer value.
bigNatToInteger :: BigNat# -> Integer
bigNatToInteger = Integer.integerFromBigNat#

-- | @'integerRecipMod' x m@ computes the modular inverse of @x@ mod @m@.
--
-- PRECONDITION: @m@ must be strictly positive.
integerRecipMod :: Integer -> Integer -> Maybe Integer
integerRecipMod x y =
  case Integer.integerRecipMod# x (Integer.integerToNaturalClamp y) of
    (# r | #)  -> Just (toInteger r)
    (# | () #) -> Nothing

-- | Coerce an integer value to a @BigNat#@.  This operation only really makes
--   sense for nonnegative values, but this condition is not checked.
integerToBigNat :: Integer -> BigNat#
integerToBigNat = Integer.integerToBigNatClamp#

-- Top-level unlifted bindings aren't allowed, so we fake one with a thunk.
oneBigNat :: (# #) -> BigNat#
oneBigNat _ = BN.bigNatFromWord# 1##

recipModBigNat :: BigNat# -> BigNat# -> BigNat#
recipModBigNat = BN.sbignat_recip_mod 0#

shiftLBigNat :: BigNat# -> Int# -> BigNat#
shiftLBigNat bn i = BN.bigNatShiftL# bn (int2Word# i)

shiftRBigNat :: BigNat# -> Int# -> BigNat#
shiftRBigNat bn i = BN.bigNatShiftR# bn (int2Word# i)

testBitBigNat :: BigNat# -> Int# -> Bool
testBitBigNat bn i = isTrue# (BN.bigNatTestBit# bn (int2Word# i))

-- Top-level unlifted bindings aren't allowed, so we fake one with a thunk.
zeroBigNat :: (# #) -> BigNat#
zeroBigNat _ = BN.bigNatFromWord# 0##
#else
import           GHC.Integer.GMP.Internals (bigNatToInteger, recipModBigNat, shiftLBigNat, shiftRBigNat, testBitBigNat)
import qualified GHC.Integer.GMP.Internals as GMP
import           GHC.Exts

type BigNat# = GMP.BigNat

{-# COMPLETE IS, IP, IN #-}

pattern IS :: Int# -> Integer
pattern $bIS :: Int# -> Integer
$mIS :: forall r. Integer -> (Int# -> r) -> (Void# -> r) -> r
IS i = GMP.S# i

pattern IP :: ByteArray# -> Integer
pattern $bIP :: ByteArray# -> Integer
$mIP :: forall r. Integer -> (ByteArray# -> r) -> (Void# -> r) -> r
IP ba = GMP.Jp# (GMP.BN# ba)

pattern IN :: ByteArray# -> Integer
pattern $bIN :: ByteArray# -> Integer
$mIN :: forall r. Integer -> (ByteArray# -> r) -> (Void# -> r) -> r
IN ba = GMP.Jn# (GMP.BN# ba)

bigNatAdd :: BigNat# -> BigNat# -> BigNat#
bigNatAdd :: BigNat# -> BigNat# -> BigNat#
bigNatAdd = BigNat# -> BigNat# -> BigNat#
GMP.plusBigNat

bigNatIsOne :: BigNat# -> Bool
bigNatIsOne :: BigNat# -> Bool
bigNatIsOne BigNat#
bn = BigNat# -> BigNat# -> Bool
GMP.eqBigNat BigNat#
bn BigNat#
GMP.oneBigNat

bigNatIsZero :: BigNat# -> Bool
bigNatIsZero :: BigNat# -> Bool
bigNatIsZero = BigNat# -> Bool
GMP.isZeroBigNat

bigNatMul :: BigNat# -> BigNat# -> BigNat#
bigNatMul :: BigNat# -> BigNat# -> BigNat#
bigNatMul = BigNat# -> BigNat# -> BigNat#
GMP.timesBigNat

bigNatRem :: BigNat# -> BigNat# -> BigNat#
bigNatRem :: BigNat# -> BigNat# -> BigNat#
bigNatRem = BigNat# -> BigNat# -> BigNat#
GMP.remBigNat

bigNatSqr :: BigNat# -> BigNat#
bigNatSqr :: BigNat# -> BigNat#
bigNatSqr = BigNat# -> BigNat#
GMP.sqrBigNat

bigNatSub :: BigNat# -> BigNat# -> (# (# #) | BigNat# #)
bigNatSub :: BigNat# -> BigNat# -> (# (# #) | BigNat# #)
bigNatSub BigNat#
x BigNat#
y =
  case BigNat# -> Int#
GMP.isNullBigNat# BigNat#
res of
    Int#
0# -> (# | BigNat#
res #)
    Int#
_  -> (# (# #) | #)
  where
    res :: BigNat#
res = BigNat# -> BigNat# -> BigNat#
GMP.minusBigNat BigNat#
x BigNat#
y

bigNatSubUnsafe :: BigNat# -> BigNat# -> BigNat#
bigNatSubUnsafe :: BigNat# -> BigNat# -> BigNat#
bigNatSubUnsafe = BigNat# -> BigNat# -> BigNat#
GMP.minusBigNat

integerToBigNat :: Integer -> BigNat#
integerToBigNat :: Integer -> BigNat#
integerToBigNat (GMP.S# Int#
i)  = Word# -> BigNat#
GMP.wordToBigNat (Int# -> Word#
int2Word# Int#
i)
integerToBigNat (GMP.Jp# BigNat#
b) = BigNat#
b
integerToBigNat (GMP.Jn# BigNat#
b) = BigNat#
b

-- | @'integerRecipMod' x m@ computes the modular inverse of @x@ mod @m@.
--
-- PRECONDITION: @m@ must be strictly positive.
integerRecipMod :: Integer -> Integer -> Maybe Integer
integerRecipMod :: Integer -> Integer -> Maybe Integer
integerRecipMod Integer
x Integer
y
  | Integer
res Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
0  = Maybe Integer
forall a. Maybe a
Nothing
  | Bool
otherwise = Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
res
  where
    res :: Integer
res = Integer -> Integer -> Integer
GMP.recipModInteger Integer
x Integer
y

oneBigNat :: (##) -> BigNat#
oneBigNat :: (# #) -> BigNat#
oneBigNat (# #)
_ = BigNat#
GMP.oneBigNat

zeroBigNat :: (##) -> BigNat#
zeroBigNat :: (# #) -> BigNat#
zeroBigNat (# #)
_ = BigNat#
GMP.zeroBigNat
#endif