-- |
-- Module:      Data.Mod
-- Copyright:   (c) 2017-2020 Andrew Lelechenko
-- Licence:     MIT
-- Maintainer:  Andrew Lelechenko <andrew.lelechenko@gmail.com>
--
-- <https://en.wikipedia.org/wiki/Modular_arithmetic Modular arithmetic>,
-- promoting moduli to the type level, with an emphasis on performance.
-- Originally part of <https://hackage.haskell.org/package/arithmoi arithmoi> package.
--
-- This module supports moduli of arbitrary size.
-- Use "Data.Mod.Word" to achieve better performance,
-- when your moduli fit into 'Word'.

{-# LANGUAGE BangPatterns          #-}
{-# LANGUAGE CPP                   #-}
{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE DeriveGeneric         #-}
{-# LANGUAGE MagicHash             #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables   #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE TypeFamilies          #-}
{-# LANGUAGE UnboxedTuples         #-}

module Data.Mod
  ( Mod
  , unMod
  , invertMod
  , (^%)
  ) where

import Control.Exception
import Control.DeepSeq
import Control.Monad
import Data.Bits
import Data.Word (Word8)
#ifdef MIN_VERSION_semirings
import Data.Euclidean (GcdDomain(..), Euclidean(..), Field)
import Data.Ratio
import Data.Semiring (Semiring(..), Ring(..))
#endif
#ifdef MIN_VERSION_vector
import Control.Monad.Primitive
import Control.Monad.ST
import qualified Data.Primitive.Types        as P
import qualified Data.Vector.Generic         as G
import qualified Data.Vector.Generic.Mutable as M
import qualified Data.Vector.Unboxed         as U
import qualified Data.Vector.Primitive       as P
import Foreign (copyBytes)
import GHC.IO.Unsafe (unsafeDupablePerformIO)
#endif
import Foreign.Storable (Storable(..))
import GHC.Exts
import GHC.Generics
import GHC.Integer.GMP.Internals
import GHC.Natural (Natural(..), powModNatural)
import GHC.TypeNats (Nat, KnownNat, natVal, natVal')

-- | This data type represents
-- <https://en.wikipedia.org/wiki/Modular_arithmetic#Integers_modulo_n integers modulo m>,
-- equipped with useful instances.
--
-- For example, 3 :: 'Mod' 10 stands for the class of integers
-- congruent to \( 3 \bmod 10 \colon \ldots {}−17, −7, 3, 13, 23 \ldots \)
--
-- >>> :set -XDataKinds
-- >>> 3 + 8 :: Mod 10 -- 3 + 8 = 11 ≡ 1 (mod 10)
-- (1 `modulo` 10)
--
-- __Warning:__ division by residue, which is not
-- <https://en.wikipedia.org/wiki/Coprime_integers coprime>
-- with the modulo, throws 'DivideByZero'.
-- Consider using 'invertMod' for non-prime moduli.
newtype Mod (m :: Nat) = Mod
  { Mod m -> Natural
unMod :: Natural
  -- ^ The canonical representative of the residue class,
  -- always between 0 and \( m - 1 \) inclusively.
  --
  -- >>> :set -XDataKinds
  -- >>> -1 :: Mod 10
  -- (9 `modulo` 10)
  }
  deriving (Mod m -> Mod m -> Bool
(Mod m -> Mod m -> Bool) -> (Mod m -> Mod m -> Bool) -> Eq (Mod m)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (m :: Nat). Mod m -> Mod m -> Bool
/= :: Mod m -> Mod m -> Bool
$c/= :: forall (m :: Nat). Mod m -> Mod m -> Bool
== :: Mod m -> Mod m -> Bool
$c== :: forall (m :: Nat). Mod m -> Mod m -> Bool
Eq, Eq (Mod m)
Eq (Mod m)
-> (Mod m -> Mod m -> Ordering)
-> (Mod m -> Mod m -> Bool)
-> (Mod m -> Mod m -> Bool)
-> (Mod m -> Mod m -> Bool)
-> (Mod m -> Mod m -> Bool)
-> (Mod m -> Mod m -> Mod m)
-> (Mod m -> Mod m -> Mod m)
-> Ord (Mod m)
Mod m -> Mod m -> Bool
Mod m -> Mod m -> Ordering
Mod m -> Mod m -> Mod m
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall (m :: Nat). Eq (Mod m)
forall (m :: Nat). Mod m -> Mod m -> Bool
forall (m :: Nat). Mod m -> Mod m -> Ordering
forall (m :: Nat). Mod m -> Mod m -> Mod m
min :: Mod m -> Mod m -> Mod m
$cmin :: forall (m :: Nat). Mod m -> Mod m -> Mod m
max :: Mod m -> Mod m -> Mod m
$cmax :: forall (m :: Nat). Mod m -> Mod m -> Mod m
>= :: Mod m -> Mod m -> Bool
$c>= :: forall (m :: Nat). Mod m -> Mod m -> Bool
> :: Mod m -> Mod m -> Bool
$c> :: forall (m :: Nat). Mod m -> Mod m -> Bool
<= :: Mod m -> Mod m -> Bool
$c<= :: forall (m :: Nat). Mod m -> Mod m -> Bool
< :: Mod m -> Mod m -> Bool
$c< :: forall (m :: Nat). Mod m -> Mod m -> Bool
compare :: Mod m -> Mod m -> Ordering
$ccompare :: forall (m :: Nat). Mod m -> Mod m -> Ordering
$cp1Ord :: forall (m :: Nat). Eq (Mod m)
Ord, (forall x. Mod m -> Rep (Mod m) x)
-> (forall x. Rep (Mod m) x -> Mod m) -> Generic (Mod m)
forall x. Rep (Mod m) x -> Mod m
forall x. Mod m -> Rep (Mod m) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (m :: Nat) x. Rep (Mod m) x -> Mod m
forall (m :: Nat) x. Mod m -> Rep (Mod m) x
$cto :: forall (m :: Nat) x. Rep (Mod m) x -> Mod m
$cfrom :: forall (m :: Nat) x. Mod m -> Rep (Mod m) x
Generic)

instance NFData (Mod m)

instance KnownNat m => Show (Mod m) where
  show :: Mod m -> String
show Mod m
m = String
"(" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Natural -> String
forall a. Show a => a -> String
show (Mod m -> Natural
forall (m :: Nat). Mod m -> Natural
unMod Mod m
m) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" `modulo` " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Natural -> String
forall a. Show a => a -> String
show (Mod m -> Natural
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Natural
natVal Mod m
m) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")"

instance KnownNat m => Enum (Mod m) where
  succ :: Mod m -> Mod m
succ Mod m
x = if Mod m
x Mod m -> Mod m -> Bool
forall a. Eq a => a -> a -> Bool
== Mod m
forall a. Bounded a => a
maxBound then ArithException -> Mod m
forall a e. Exception e => e -> a
throw ArithException
Overflow  else (Natural -> Natural) -> Mod m -> Mod m
coerce (Enum Natural => Natural -> Natural
forall a. Enum a => a -> a
succ @Natural) Mod m
x
  pred :: Mod m -> Mod m
pred Mod m
x = if Mod m
x Mod m -> Mod m -> Bool
forall a. Eq a => a -> a -> Bool
== Mod m
forall a. Bounded a => a
minBound then ArithException -> Mod m
forall a e. Exception e => e -> a
throw ArithException
Underflow else (Natural -> Natural) -> Mod m -> Mod m
coerce (Enum Natural => Natural -> Natural
forall a. Enum a => a -> a
pred @Natural) Mod m
x

  toEnum :: Int -> Mod m
toEnum   = (Int -> Mod m
forall a b. (Integral a, Num b) => a -> b
fromIntegral :: Int -> Mod m)
  fromEnum :: Mod m -> Int
fromEnum = (Natural -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral :: Natural -> Int) (Natural -> Int) -> (Mod m -> Natural) -> Mod m -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Mod m -> Natural
forall (m :: Nat). Mod m -> Natural
unMod

  enumFrom :: Mod m -> [Mod m]
enumFrom Mod m
x       = Mod m -> Mod m -> [Mod m]
forall a. Enum a => a -> a -> [a]
enumFromTo Mod m
x Mod m
forall a. Bounded a => a
maxBound
  enumFromThen :: Mod m -> Mod m -> [Mod m]
enumFromThen Mod m
x Mod m
y = Mod m -> Mod m -> Mod m -> [Mod m]
forall a. Enum a => a -> a -> a -> [a]
enumFromThenTo Mod m
x Mod m
y (if Mod m
y Mod m -> Mod m -> Bool
forall a. Ord a => a -> a -> Bool
>= Mod m
x then Mod m
forall a. Bounded a => a
maxBound else Mod m
forall a. Bounded a => a
minBound)

  enumFromTo :: Mod m -> Mod m -> [Mod m]
enumFromTo     = (Natural -> Natural -> [Natural]) -> Mod m -> Mod m -> [Mod m]
coerce (Enum Natural => Natural -> Natural -> [Natural]
forall a. Enum a => a -> a -> [a]
enumFromTo     @Natural)
  enumFromThenTo :: Mod m -> Mod m -> Mod m -> [Mod m]
enumFromThenTo = (Natural -> Natural -> Natural -> [Natural])
-> Mod m -> Mod m -> Mod m -> [Mod m]
coerce (Enum Natural => Natural -> Natural -> Natural -> [Natural]
forall a. Enum a => a -> a -> a -> [a]
enumFromThenTo @Natural)

instance KnownNat m => Bounded (Mod m) where
  minBound :: Mod m
minBound = Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod Natural
0
  maxBound :: Mod m
maxBound = let mx :: Mod m
mx = Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod (Mod m -> Natural
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Natural
natVal Mod m
mx Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
- Natural
1) in Mod m
mx

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#
#endif

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#

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#

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#

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#

brokenInvariant :: a
brokenInvariant :: a
brokenInvariant = String -> a
forall a. HasCallStack => String -> a
error String
"argument is larger than modulo"

instance KnownNat m => Num (Mod m) where
  mx :: Mod m
mx@(Mod !Natural
x) + :: Mod m -> Mod m -> Mod m
+ (Mod !Natural
y) = Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod (Natural -> Mod m) -> Natural -> Mod m
forall a b. (a -> b) -> a -> b
$ Natural -> Natural -> Natural -> Natural
addMod (Mod m -> Natural
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Natural
natVal Mod m
mx) Natural
x Natural
y
  {-# INLINE (+) #-}
  mx :: Mod m
mx@(Mod !Natural
x) - :: Mod m -> Mod m -> Mod m
- (Mod !Natural
y) = Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod (Natural -> Mod m) -> Natural -> Mod m
forall a b. (a -> b) -> a -> b
$ Natural -> Natural -> Natural -> Natural
subMod (Mod m -> Natural
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Natural
natVal Mod m
mx) Natural
x Natural
y
  {-# INLINE (-) #-}
  negate :: Mod m -> Mod m
negate mx :: Mod m
mx@(Mod !Natural
x) = Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod (Natural -> Mod m) -> Natural -> Mod m
forall a b. (a -> b) -> a -> b
$ Natural -> Natural -> Natural
negateMod (Mod m -> Natural
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Natural
natVal Mod m
mx) Natural
x
  {-# INLINE negate #-}
  mx :: Mod m
mx@(Mod !Natural
x) * :: Mod m -> Mod m -> Mod m
* (Mod !Natural
y) = Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod (Natural -> Mod m) -> Natural -> Mod m
forall a b. (a -> b) -> a -> b
$ Natural -> Natural -> Natural -> Natural
mulMod (Mod m -> Natural
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Natural
natVal Mod m
mx) Natural
x Natural
y
  {-# INLINE (*) #-}
  abs :: Mod m -> Mod m
abs = Mod m -> Mod m
forall a. a -> a
id
  {-# INLINE abs #-}
  signum :: Mod m -> Mod m
signum = Mod m -> Mod m -> Mod m
forall a b. a -> b -> a
const Mod m
x
    where
      x :: Mod m
x = if Mod m -> Natural
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Natural
natVal Mod m
x Natural -> Natural -> Bool
forall a. Ord a => a -> a -> Bool
> Natural
1 then Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod Natural
1 else Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod Natural
0
  {-# INLINE signum #-}
  fromInteger :: Integer -> Mod m
fromInteger Integer
x = Mod m
mx
    where
      mx :: Mod m
mx = Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod (Natural -> Mod m) -> Natural -> Mod m
forall a b. (a -> b) -> a -> b
$ Integer -> Natural
forall a. Num a => Integer -> a
fromInteger (Integer -> Natural) -> Integer -> Natural
forall a b. (a -> b) -> a -> b
$ Integer
x Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`mod` Natural -> Integer
forall a. Integral a => a -> Integer
toInteger (Mod m -> Natural
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Natural
natVal Mod m
mx)
  {-# INLINE fromInteger #-}

#ifdef MIN_VERSION_semirings

instance KnownNat m => Semiring (Mod m) where
  plus :: Mod m -> Mod m -> Mod m
plus  = Mod m -> Mod m -> Mod m
forall a. Num a => a -> a -> a
(+)
  {-# INLINE plus #-}
  times :: Mod m -> Mod m -> Mod m
times = Mod m -> Mod m -> Mod m
forall a. Num a => a -> a -> a
(*)
  {-# INLINE times #-}
  zero :: Mod m
zero  = Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod Natural
0
  {-# INLINE zero #-}
  one :: Mod m
one   = Mod m
mx
    where
      mx :: Mod m
mx = if Mod m -> Natural
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Natural
natVal Mod m
mx Natural -> Natural -> Bool
forall a. Ord a => a -> a -> Bool
> Natural
1 then Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod Natural
1 else Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod Natural
0
  {-# INLINE one #-}
  fromNatural :: Natural -> Mod m
fromNatural Natural
x = Mod m
mx
    where
      mx :: Mod m
mx = Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod (Natural -> Mod m) -> Natural -> Mod m
forall a b. (a -> b) -> a -> b
$ Natural
x Natural -> Natural -> Natural
forall a. Integral a => a -> a -> a
`mod` Mod m -> Natural
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Natural
natVal Mod m
mx
  {-# INLINE fromNatural #-}

instance KnownNat m => Ring (Mod m) where
  negate :: Mod m -> Mod m
negate = Mod m -> Mod m
forall a. Num a => a -> a
Prelude.negate
  {-# INLINE negate #-}

-- | See the warning about division above.
instance KnownNat m => Fractional (Mod m) where
  fromRational :: Rational -> Mod m
fromRational Rational
r = case Rational -> Integer
forall a. Ratio a -> a
denominator Rational
r of
    Integer
1   -> Mod m
num
    Integer
den -> Mod m
num Mod m -> Mod m -> Mod m
forall a. Fractional a => a -> a -> a
/ Integer -> Mod m
forall a. Num a => Integer -> a
fromInteger Integer
den
    where
      num :: Mod m
num = Integer -> Mod m
forall a. Num a => Integer -> a
fromInteger (Rational -> Integer
forall a. Ratio a -> a
numerator Rational
r)
  {-# INLINE fromRational #-}
  recip :: Mod m -> Mod m
recip Mod m
mx = case Mod m -> Maybe (Mod m)
forall (m :: Nat). KnownNat m => Mod m -> Maybe (Mod m)
invertMod Mod m
mx of
    Maybe (Mod m)
Nothing -> ArithException -> Mod m
forall a e. Exception e => e -> a
throw ArithException
DivideByZero
    Just Mod m
y  -> Mod m
y
  {-# INLINE recip #-}

-- | See the warning about division above.
instance KnownNat m => GcdDomain (Mod m) where
  divide :: Mod m -> Mod m -> Maybe (Mod m)
divide Mod m
x Mod m
y = Mod m -> Maybe (Mod m)
forall a. a -> Maybe a
Just (Mod m
x Mod m -> Mod m -> Mod m
forall a. Fractional a => a -> a -> a
/ Mod m
y)
  gcd :: Mod m -> Mod m -> Mod m
gcd        = (Mod m -> Mod m) -> Mod m -> Mod m -> Mod m
forall a b. a -> b -> a
const ((Mod m -> Mod m) -> Mod m -> Mod m -> Mod m)
-> (Mod m -> Mod m) -> Mod m -> Mod m -> Mod m
forall a b. (a -> b) -> a -> b
$ Mod m -> Mod m -> Mod m
forall a b. a -> b -> a
const Mod m
1
  lcm :: Mod m -> Mod m -> Mod m
lcm        = (Mod m -> Mod m) -> Mod m -> Mod m -> Mod m
forall a b. a -> b -> a
const ((Mod m -> Mod m) -> Mod m -> Mod m -> Mod m)
-> (Mod m -> Mod m) -> Mod m -> Mod m -> Mod m
forall a b. (a -> b) -> a -> b
$ Mod m -> Mod m -> Mod m
forall a b. a -> b -> a
const Mod m
1
  coprime :: Mod m -> Mod m -> Bool
coprime    = (Mod m -> Bool) -> Mod m -> Mod m -> Bool
forall a b. a -> b -> a
const ((Mod m -> Bool) -> Mod m -> Mod m -> Bool)
-> (Mod m -> Bool) -> Mod m -> Mod m -> Bool
forall a b. (a -> b) -> a -> b
$ Bool -> Mod m -> Bool
forall a b. a -> b -> a
const Bool
True

-- | See the warning about division above.
instance KnownNat m => Euclidean (Mod m) where
  degree :: Mod m -> Natural
degree      = Natural -> Mod m -> Natural
forall a b. a -> b -> a
const Natural
0
  quotRem :: Mod m -> Mod m -> (Mod m, Mod m)
quotRem Mod m
x Mod m
y = (Mod m
x Mod m -> Mod m -> Mod m
forall a. Fractional a => a -> a -> a
/ Mod m
y, Mod m
0)
  quot :: Mod m -> Mod m -> Mod m
quot        = Mod m -> Mod m -> Mod m
forall a. Fractional a => a -> a -> a
(/)
  rem :: Mod m -> Mod m -> Mod m
rem         = (Mod m -> Mod m) -> Mod m -> Mod m -> Mod m
forall a b. a -> b -> a
const ((Mod m -> Mod m) -> Mod m -> Mod m -> Mod m)
-> (Mod m -> Mod m) -> Mod m -> Mod m -> Mod m
forall a b. (a -> b) -> a -> b
$ Mod m -> Mod m -> Mod m
forall a b. a -> b -> a
const Mod m
0

-- | See the warning about division above.
instance KnownNat m => Field (Mod m)

#endif

-- | If an argument is
-- <https://en.wikipedia.org/wiki/Coprime_integers coprime>
-- with the modulo, return its modular inverse.
-- Otherwise return 'Nothing'.
--
-- >>> :set -XDataKinds
-- >>> invertMod 3 :: Mod 10 -- 3 * 7 = 21 ≡ 1 (mod 10)
-- Just (7 `modulo` 10)
-- >>> invertMod 4 :: Mod 10 -- 4 and 10 are not coprime
-- Nothing
invertMod :: KnownNat m => Mod m -> Maybe (Mod m)
invertMod :: Mod m -> Maybe (Mod m)
invertMod Mod m
mx
  = if Integer
y Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= Integer
0
    then Maybe (Mod m)
forall a. Maybe a
Nothing
    else Mod m -> Maybe (Mod m)
forall a. a -> Maybe a
Just (Mod m -> Maybe (Mod m)) -> Mod m -> Maybe (Mod m)
forall a b. (a -> b) -> a -> b
$ Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod (Natural -> Mod m) -> Natural -> Mod m
forall a b. (a -> b) -> a -> b
$ Integer -> Natural
forall a. Num a => Integer -> a
fromInteger Integer
y
  where
    y :: Integer
y = Integer -> Integer -> Integer
recipModInteger (Natural -> Integer
forall a. Integral a => a -> Integer
toInteger (Mod m -> Natural
forall (m :: Nat). Mod m -> Natural
unMod Mod m
mx)) (Natural -> Integer
forall a. Integral a => a -> Integer
toInteger (Mod m -> Natural
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Natural
natVal Mod m
mx))
{-# INLINABLE invertMod #-}

-- | Drop-in replacement for 'Prelude.^' with much better performance.
-- Negative powers are allowed, but may throw 'DivideByZero', if an argument
-- is not <https://en.wikipedia.org/wiki/Coprime_integers coprime> with the modulo.
--
-- Building with @-O@ triggers a rewrite rule 'Prelude.^' = '^%'.
--
-- >>> :set -XDataKinds
-- >>> 3 ^% 4 :: Mod 10    -- 3 ^ 4 = 81 ≡ 1 (mod 10)
-- (1 `modulo` 10)
-- >>> 3 ^% (-1) :: Mod 10 -- 3 * 7 = 21 ≡ 1 (mod 10)
-- (7 `modulo` 10)
-- >>> 4 ^% (-1) :: Mod 10 -- 4 and 10 are not coprime
-- (*** Exception: divide by zero
(^%) :: (KnownNat m, Integral a) => Mod m -> a -> Mod m
Mod m
mx ^% :: Mod m -> a -> Mod m
^% a
a
  | a
a a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0     = case Mod m -> Maybe (Mod m)
forall (m :: Nat). KnownNat m => Mod m -> Maybe (Mod m)
invertMod Mod m
mx of
    Maybe (Mod m)
Nothing ->  ArithException -> Mod m
forall a e. Exception e => e -> a
throw ArithException
DivideByZero
    Just Mod m
my ->  Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod (Natural -> Mod m) -> Natural -> Mod m
forall a b. (a -> b) -> a -> b
$ Natural -> Natural -> Natural -> Natural
powModNatural (Mod m -> Natural
forall (m :: Nat). Mod m -> Natural
unMod Mod m
my) (a -> Natural
fromIntegral' (-a
a)) (Mod m -> Natural
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Natural
natVal Mod m
mx)
  | Bool
otherwise = Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod (Natural -> Mod m) -> Natural -> Mod m
forall a b. (a -> b) -> a -> b
$ Natural -> Natural -> Natural -> Natural
powModNatural (Mod m -> Natural
forall (m :: Nat). Mod m -> Natural
unMod Mod m
mx) (a -> Natural
fromIntegral' a
a)    (Mod m -> Natural
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Natural
natVal Mod m
mx)
  where
#if __GLASGOW_HASKELL__ == 900 && __GLASGOW_HASKELL_PATCHLEVEL1__ == 1
    -- Cannot use fromIntegral because of https://gitlab.haskell.org/ghc/ghc/-/issues/19411
    fromIntegral' = fromInteger . toInteger
#else
    fromIntegral' :: a -> Natural
fromIntegral' = a -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral
#endif
{-# INLINABLE [1] (^%) #-}

{-# SPECIALISE [1] (^%) ::
  KnownNat m => Mod m -> Integer -> Mod m,
  KnownNat m => Mod m -> Natural -> Mod m,
  KnownNat m => Mod m -> Int     -> Mod m,
  KnownNat m => Mod m -> Word    -> Mod m #-}

{-# RULES
"powMod"               forall (x :: KnownNat m => Mod m) p. x ^ p = x ^% p

"powMod/2/Integer"     forall x. x ^% (2 :: Integer) = let u = x in u*u
"powMod/3/Integer"     forall x. x ^% (3 :: Integer) = let u = x in u*u*u
"powMod/2/Int"         forall x. x ^% (2 :: Int)     = let u = x in u*u
"powMod/3/Int"         forall x. x ^% (3 :: Int)     = let u = x in u*u*u
"powMod/2/Word"        forall x. x ^% (2 :: Word)    = let u = x in u*u
"powMod/3/Word"        forall x. x ^% (3 :: Word)    = let u = x in u*u*u #-}

infixr 8 ^%

wordSize :: Int
wordSize :: Int
wordSize = Word -> Int
forall b. FiniteBits b => b -> Int
finiteBitSize (Word
0 :: Word)

lgWordSize :: Int
lgWordSize :: Int
lgWordSize = case Int
wordSize of
  Int
32 -> Int
2 -- 2^2 bytes in word
  Int
64 -> Int
3 -- 2^3 bytes in word
  Int
_  -> String -> Int
forall a. HasCallStack => String -> a
error String
"lgWordSize: unknown architecture"

instance KnownNat m => Storable (Mod m) where
  sizeOf :: Mod m -> Int
sizeOf Mod m
_ = case Proxy# m -> Natural
forall (n :: Nat). KnownNat n => Proxy# n -> Natural
natVal' (Proxy# m
forall k (a :: k). Proxy# a
proxy# :: Proxy# m) of
    NatS#{}  -> Word -> Int
forall a. Storable a => a -> Int
sizeOf (Word
0 :: Word)
    NatJ# BigNat
m# -> Int# -> Int
I# (BigNat -> Int#
sizeofBigNat# BigNat
m#) Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
lgWordSize
  {-# INLINE sizeOf #-}

  alignment :: Mod m -> Int
alignment Mod m
_ = Word -> Int
forall a. Storable a => a -> Int
alignment (Word
0 :: Word)
  {-# INLINE alignment #-}

  peek :: Ptr (Mod m) -> IO (Mod m)
peek (Ptr Addr#
addr#) = case Proxy# m -> Natural
forall (n :: Nat). KnownNat n => Proxy# n -> Natural
natVal' (Proxy# m
forall k (a :: k). Proxy# a
proxy# :: Proxy# m) of
    NatS#{} -> do
      W# GmpLimb#
w# <- Ptr Word -> IO Word
forall a. Storable a => Ptr a -> IO a
peek (Addr# -> Ptr Word
forall a. Addr# -> Ptr a
Ptr Addr#
addr#)
      Mod m -> IO (Mod m)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Mod m -> IO (Mod m))
-> (Natural -> Mod m) -> Natural -> IO (Mod m)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod (Natural -> IO (Mod m)) -> Natural -> IO (Mod m)
forall a b. (a -> b) -> a -> b
$! GmpLimb# -> Natural
NatS# GmpLimb#
w#
    NatJ# BigNat
m# -> do
      let !(I# Int#
lgWordSize#) = Int
lgWordSize
          sz# :: Int#
sz# = BigNat -> Int#
sizeofBigNat# BigNat
m# Int# -> Int# -> Int#
`iShiftL#` Int#
lgWordSize#
      BigNat
bn <- Addr# -> GmpLimb# -> Int# -> IO BigNat
importBigNatFromAddr Addr#
addr# (Int# -> GmpLimb#
int2Word# Int#
sz#) Int#
0#
      Mod m -> IO (Mod m)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Mod m -> IO (Mod m))
-> (Natural -> Mod m) -> Natural -> IO (Mod m)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod (Natural -> IO (Mod m)) -> Natural -> IO (Mod m)
forall a b. (a -> b) -> a -> b
$! BigNat -> Natural
bigNatToNat BigNat
bn
  {-# INLINE peek #-}

  poke :: Ptr (Mod m) -> Mod m -> IO ()
poke (Ptr Addr#
addr#) (Mod Natural
x) = case Proxy# m -> Natural
forall (n :: Nat). KnownNat n => Proxy# n -> Natural
natVal' (Proxy# m
forall k (a :: k). Proxy# a
proxy# :: Proxy# m) of
    NatS#{} -> case Natural
x of
      NatS# GmpLimb#
x# -> Ptr Word -> Word -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Addr# -> Ptr Word
forall a. Addr# -> Ptr a
Ptr Addr#
addr#) (GmpLimb# -> Word
W# GmpLimb#
x#)
      Natural
_        -> IO ()
forall a. a
brokenInvariant
    NatJ# BigNat
m# -> case Natural
x of
      NatS# GmpLimb#
x# -> do
        Ptr Word -> Word -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Addr# -> Ptr Word
forall a. Addr# -> Ptr a
Ptr Addr#
addr#) (GmpLimb# -> Word
W# GmpLimb#
x#)
        [Int] -> (Int -> IO ()) -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Int
1 .. Int
sz Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1] ((Int -> IO ()) -> IO ()) -> (Int -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Int
off ->
          Ptr Word -> Int -> Word -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff (Addr# -> Ptr Word
forall a. Addr# -> Ptr a
Ptr Addr#
addr#) Int
off (Word
0 :: Word)
      NatJ# BigNat
bn -> do
        Word
l <- BigNat -> Addr# -> Int# -> IO Word
exportBigNatToAddr BigNat
bn Addr#
addr# Int#
0#
        [Int] -> (Int -> IO ()) -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [(Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral :: Word -> Int) Word
l .. (Int
sz Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
lgWordSize) Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1] ((Int -> IO ()) -> IO ()) -> (Int -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Int
off ->
          Ptr Word8 -> Int -> Word8 -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff (Addr# -> Ptr Word8
forall a. Addr# -> Ptr a
Ptr Addr#
addr#) Int
off (Word8
0 :: Word8)
      where
        sz :: Int
sz = Int# -> Int
I# (BigNat -> Int#
sizeofBigNat# BigNat
m#)
  {-# INLINE poke #-}

#ifdef MIN_VERSION_vector

instance KnownNat m => P.Prim (Mod m) where
  sizeOf# :: Mod m -> Int#
sizeOf# Mod m
x    = let !(I# Int#
sz#) = Mod m -> Int
forall a. Storable a => a -> Int
sizeOf Mod m
x    in Int#
sz#
  {-# INLINE sizeOf# #-}

  alignment# :: Mod m -> Int#
alignment# Mod m
x = let !(I# Int#
a#)  = Mod m -> Int
forall a. Storable a => a -> Int
alignment Mod m
x in Int#
a#
  {-# INLINE alignment# #-}

  indexByteArray# :: ByteArray# -> Int# -> Mod m
indexByteArray# ByteArray#
arr# Int#
i' = case Proxy# m -> Natural
forall (n :: Nat). KnownNat n => Proxy# n -> Natural
natVal' (Proxy# m
forall k (a :: k). Proxy# a
proxy# :: Proxy# m) of
    NatS#{} -> Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod (GmpLimb# -> Natural
NatS# GmpLimb#
w#)
      where
        !(W# GmpLimb#
w#) = ByteArray# -> Int# -> Word
forall a. Prim a => ByteArray# -> Int# -> a
P.indexByteArray# ByteArray#
arr# Int#
i'
    NatJ# BigNat
m# -> Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod (Natural -> Mod m) -> Natural -> Mod m
forall a b. (a -> b) -> a -> b
$ BigNat -> Natural
bigNatToNat (BigNat -> Natural) -> BigNat -> Natural
forall a b. (a -> b) -> a -> b
$ ByteArray# -> GmpLimb# -> GmpLimb# -> Int# -> BigNat
importBigNatFromByteArray ByteArray#
arr# (Int# -> GmpLimb#
int2Word# Int#
i#) (Int# -> GmpLimb#
int2Word# Int#
sz#) Int#
0#
      where
        !(I# Int#
lgWordSize#) = Int
lgWordSize
        sz# :: Int#
sz# = BigNat -> Int#
sizeofBigNat# BigNat
m# Int# -> Int# -> Int#
`iShiftL#` Int#
lgWordSize#
        i# :: Int#
i# = Int#
i' Int# -> Int# -> Int#
*# Int#
sz#
  {-# INLINE indexByteArray# #-}

  indexOffAddr# :: Addr# -> Int# -> Mod m
indexOffAddr# Addr#
arr# Int#
i' = case Proxy# m -> Natural
forall (n :: Nat). KnownNat n => Proxy# n -> Natural
natVal' (Proxy# m
forall k (a :: k). Proxy# a
proxy# :: Proxy# m) of
    NatS#{} -> Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod (GmpLimb# -> Natural
NatS# GmpLimb#
w#)
      where
        !(W# GmpLimb#
w#) = Addr# -> Int# -> Word
forall a. Prim a => Addr# -> Int# -> a
P.indexOffAddr# Addr#
arr# Int#
i'
    NatJ# BigNat
m# -> Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod (Natural -> Mod m) -> Natural -> Mod m
forall a b. (a -> b) -> a -> b
$ BigNat -> Natural
bigNatToNat (BigNat -> Natural) -> BigNat -> Natural
forall a b. (a -> b) -> a -> b
$ IO BigNat -> BigNat
forall a. IO a -> a
unsafeDupablePerformIO (IO BigNat -> BigNat) -> IO BigNat -> BigNat
forall a b. (a -> b) -> a -> b
$ Addr# -> GmpLimb# -> Int# -> IO BigNat
importBigNatFromAddr (Addr#
arr# Addr# -> Int# -> Addr#
`plusAddr#` Int#
i#) (Int# -> GmpLimb#
int2Word# Int#
sz#) Int#
0#
      where
        !(I# Int#
lgWordSize#) = Int
lgWordSize
        sz# :: Int#
sz# = BigNat -> Int#
sizeofBigNat# BigNat
m# Int# -> Int# -> Int#
`iShiftL#` Int#
lgWordSize#
        i# :: Int#
i# = Int#
i' Int# -> Int# -> Int#
*# Int#
sz#
  {-# INLINE indexOffAddr# #-}

  readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Mod m #)
readByteArray# MutableByteArray# s
marr !Int#
i' State# s
token = case Proxy# m -> Natural
forall (n :: Nat). KnownNat n => Proxy# n -> Natural
natVal' (Proxy# m
forall k (a :: k). Proxy# a
proxy# :: Proxy# m) of
    NatS#{} -> case MutableByteArray# s -> Int# -> State# s -> (# State# s, Word #)
forall a s.
Prim a =>
MutableByteArray# s -> Int# -> State# s -> (# State# s, a #)
P.readByteArray# MutableByteArray# s
marr Int#
i' State# s
token of
      (# State# s
newToken, W# GmpLimb#
w# #) -> (# State# s
newToken, Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod (GmpLimb# -> Natural
NatS# GmpLimb#
w#) #)
    NatJ# BigNat
m# -> case MutableByteArray# s -> State# s -> (# State# s, ByteArray# #)
forall d.
MutableByteArray# d -> State# d -> (# State# d, ByteArray# #)
unsafeFreezeByteArray# MutableByteArray# s
marr State# s
token of
      (# State# s
newToken, ByteArray#
arr #) -> (# State# s
newToken, Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod (BigNat -> Natural
bigNatToNat (ByteArray# -> GmpLimb# -> GmpLimb# -> Int# -> BigNat
importBigNatFromByteArray ByteArray#
arr (Int# -> GmpLimb#
int2Word# Int#
i#) (Int# -> GmpLimb#
int2Word# Int#
sz#) Int#
0#)) #)
      where
        !(I# Int#
lgWordSize#) = Int
lgWordSize
        sz# :: Int#
sz# = BigNat -> Int#
sizeofBigNat# BigNat
m# Int# -> Int# -> Int#
`iShiftL#` Int#
lgWordSize#
        i# :: Int#
i# = Int#
i' Int# -> Int# -> Int#
*# Int#
sz#
  {-# INLINE readByteArray# #-}

  readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Mod m #)
readOffAddr# Addr#
marr !Int#
i' State# s
token = case Proxy# m -> Natural
forall (n :: Nat). KnownNat n => Proxy# n -> Natural
natVal' (Proxy# m
forall k (a :: k). Proxy# a
proxy# :: Proxy# m) of
    NatS#{} -> case Addr# -> Int# -> State# s -> (# State# s, Word #)
forall a s.
Prim a =>
Addr# -> Int# -> State# s -> (# State# s, a #)
P.readOffAddr# Addr#
marr Int#
i' State# s
token of
      (# State# s
newToken, W# GmpLimb#
w# #) -> (# State# s
newToken, Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod (GmpLimb# -> Natural
NatS# GmpLimb#
w#) #)
    NatJ# BigNat
m# -> case ST s BigNat
-> State# (PrimState (ST s))
-> (# State# (PrimState (ST s)), BigNat #)
forall (m :: * -> *) a.
PrimBase m =>
m a -> State# (PrimState m) -> (# State# (PrimState m), a #)
internal (IO BigNat -> ST s BigNat
forall (m :: * -> *) a. PrimMonad m => IO a -> m a
unsafeIOToPrim (Addr# -> GmpLimb# -> Int# -> IO BigNat
importBigNatFromAddr (Addr#
marr Addr# -> Int# -> Addr#
`plusAddr#` Int#
i#) (Int# -> GmpLimb#
int2Word# Int#
sz#) Int#
0#) :: ST s BigNat) State# s
State# (PrimState (ST s))
token of
      (# State# (PrimState (ST s))
newToken, BigNat
bn #) -> (# State# s
State# (PrimState (ST s))
newToken, Natural -> Mod m
forall (m :: Nat). Natural -> Mod m
Mod (BigNat -> Natural
bigNatToNat BigNat
bn) #)
      where
        !(I# Int#
lgWordSize#) = Int
lgWordSize
        sz# :: Int#
sz# = BigNat -> Int#
sizeofBigNat# BigNat
m# Int# -> Int# -> Int#
`iShiftL#` Int#
lgWordSize#
        i# :: Int#
i# = Int#
i' Int# -> Int# -> Int#
*# Int#
sz#
  {-# INLINE readOffAddr# #-}

  writeByteArray# :: MutableByteArray# s -> Int# -> Mod m -> State# s -> State# s
writeByteArray# MutableByteArray# s
marr !Int#
i' !(Mod Natural
x) State# s
token = case Proxy# m -> Natural
forall (n :: Nat). KnownNat n => Proxy# n -> Natural
natVal' (Proxy# m
forall k (a :: k). Proxy# a
proxy# :: Proxy# m) of
    NatS#{} -> case Natural
x of
      NatS# GmpLimb#
x# -> MutableByteArray# s -> Int# -> Word -> State# s -> State# s
forall a s.
Prim a =>
MutableByteArray# s -> Int# -> a -> State# s -> State# s
P.writeByteArray# MutableByteArray# s
marr Int#
i' (GmpLimb# -> Word
W# GmpLimb#
x#) State# s
token
      Natural
_        -> String -> State# s
forall a. HasCallStack => String -> a
error String
"argument is larger than modulo"
    NatJ# BigNat
m# -> case Natural
x of
      NatS# GmpLimb#
x# -> case MutableByteArray# s -> Int# -> Word -> State# s -> State# s
forall a s.
Prim a =>
MutableByteArray# s -> Int# -> a -> State# s -> State# s
P.writeByteArray# MutableByteArray# s
marr Int#
i# (GmpLimb# -> Word
W# GmpLimb#
x#) State# s
token of
        State# s
newToken -> MutableByteArray# s -> Int# -> Int# -> Word -> State# s -> State# s
forall a s.
Prim a =>
MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s
P.setByteArray# MutableByteArray# s
marr (Int#
i# Int# -> Int# -> Int#
+# Int#
1#) (Int#
sz# Int# -> Int# -> Int#
-# Int#
1#) (Word
0 :: Word) State# s
newToken
      NatJ# BigNat
bn -> case ST s Word
-> State# (PrimState (ST s))
-> (# State# (PrimState (ST s)), Word #)
forall (m :: * -> *) a.
PrimBase m =>
m a -> State# (PrimState m) -> (# State# (PrimState m), a #)
internal (IO Word -> ST s Word
forall (m :: * -> *) a. PrimMonad m => IO a -> m a
unsafeIOToPrim (BigNat
-> MutableByteArray# RealWorld -> GmpLimb# -> Int# -> IO Word
exportBigNatToMutableByteArray BigNat
bn (MutableByteArray# s -> MutableByteArray# RealWorld
unsafeCoerce# MutableByteArray# s
marr) (Int# -> GmpLimb#
int2Word# (Int#
i# Int# -> Int# -> Int#
`iShiftL#` Int#
lgWordSize#)) Int#
0#) :: ST s Word) State# s
State# (PrimState (ST s))
token of
        (# State# (PrimState (ST s))
newToken, W# GmpLimb#
l# #) -> MutableByteArray# s
-> Int# -> Int# -> Word8 -> State# s -> State# s
forall a s.
Prim a =>
MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s
P.setByteArray# MutableByteArray# s
marr (Int#
i# Int# -> Int# -> Int#
`iShiftL#` Int#
lgWordSize# Int# -> Int# -> Int#
+# GmpLimb# -> Int#
word2Int# GmpLimb#
l#) (Int#
sz# Int# -> Int# -> Int#
`iShiftL#` Int#
lgWordSize# Int# -> Int# -> Int#
-# GmpLimb# -> Int#
word2Int# GmpLimb#
l#) (Word8
0 :: Word8) State# s
State# (PrimState (ST s))
newToken
      where
        !(I# Int#
lgWordSize#) = Int
lgWordSize
        !sz :: Int
sz@(I# Int#
sz#) = Int# -> Int
I# (BigNat -> Int#
sizeofBigNat# BigNat
m#)
        !(I# Int#
i#)     = Int# -> Int
I# Int#
i' Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
sz
  {-# INLINE writeByteArray# #-}

  writeOffAddr# :: Addr# -> Int# -> Mod m -> State# s -> State# s
writeOffAddr# Addr#
marr !Int#
i' !(Mod Natural
x) State# s
token = case Proxy# m -> Natural
forall (n :: Nat). KnownNat n => Proxy# n -> Natural
natVal' (Proxy# m
forall k (a :: k). Proxy# a
proxy# :: Proxy# m) of
    NatS#{} -> case Natural
x of
      NatS# GmpLimb#
x# -> Addr# -> Int# -> Word -> State# s -> State# s
forall a s. Prim a => Addr# -> Int# -> a -> State# s -> State# s
P.writeOffAddr# Addr#
marr Int#
i' (GmpLimb# -> Word
W# GmpLimb#
x#) State# s
token
      Natural
_        -> String -> State# s
forall a. HasCallStack => String -> a
error String
"argument is larger than modulo"
    NatJ# BigNat
m# -> case Natural
x of
      NatS# GmpLimb#
x# -> case Addr# -> Int# -> Word -> State# s -> State# s
forall a s. Prim a => Addr# -> Int# -> a -> State# s -> State# s
P.writeOffAddr# Addr#
marr Int#
i# (GmpLimb# -> Word
W# GmpLimb#
x#) State# s
token of
        State# s
newToken -> Addr# -> Int# -> Int# -> Word -> State# s -> State# s
forall a s.
Prim a =>
Addr# -> Int# -> Int# -> a -> State# s -> State# s
P.setOffAddr# Addr#
marr (Int#
i# Int# -> Int# -> Int#
+# Int#
1#) (Int#
sz# Int# -> Int# -> Int#
-# Int#
1#) (Word
0 :: Word) State# s
newToken
      NatJ# BigNat
bn -> case ST s Word
-> State# (PrimState (ST s))
-> (# State# (PrimState (ST s)), Word #)
forall (m :: * -> *) a.
PrimBase m =>
m a -> State# (PrimState m) -> (# State# (PrimState m), a #)
internal (IO Word -> ST s Word
forall (m :: * -> *) a. PrimMonad m => IO a -> m a
unsafeIOToPrim (BigNat -> Addr# -> Int# -> IO Word
exportBigNatToAddr BigNat
bn (Addr#
marr Addr# -> Int# -> Addr#
`plusAddr#` (Int#
i# Int# -> Int# -> Int#
`iShiftL#` Int#
lgWordSize#)) Int#
0#) :: ST s Word) State# s
State# (PrimState (ST s))
token of
        (# State# (PrimState (ST s))
newToken, W# GmpLimb#
l# #) -> Addr# -> Int# -> Int# -> Word8 -> State# s -> State# s
forall a s.
Prim a =>
Addr# -> Int# -> Int# -> a -> State# s -> State# s
P.setOffAddr# Addr#
marr (Int#
i# Int# -> Int# -> Int#
`iShiftL#` Int#
lgWordSize# Int# -> Int# -> Int#
+# GmpLimb# -> Int#
word2Int# GmpLimb#
l#) (Int#
sz# Int# -> Int# -> Int#
`iShiftL#` Int#
lgWordSize# Int# -> Int# -> Int#
-# GmpLimb# -> Int#
word2Int# GmpLimb#
l#) (Word8
0 :: Word8) State# s
State# (PrimState (ST s))
newToken
      where
        !(I# Int#
lgWordSize#) = Int
lgWordSize
        !sz :: Int
sz@(I# Int#
sz#) = Int# -> Int
I# (BigNat -> Int#
sizeofBigNat# BigNat
m#)
        !(I# Int#
i#)   = Int# -> Int
I# Int#
i' Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
sz
  {-# INLINE writeOffAddr# #-}

  setByteArray# :: MutableByteArray# s
-> Int# -> Int# -> Mod m -> State# s -> State# s
setByteArray# !MutableByteArray# s
_ !Int#
_ Int#
0# !Mod m
_ State# s
token = State# s
token
  setByteArray# MutableByteArray# s
marr Int#
off Int#
len mx :: Mod m
mx@(Mod Natural
x) State# s
token = case Proxy# m -> Natural
forall (n :: Nat). KnownNat n => Proxy# n -> Natural
natVal' (Proxy# m
forall k (a :: k). Proxy# a
proxy# :: Proxy# m) of
    NatS#{} -> case Natural
x of
      NatS# GmpLimb#
x# -> MutableByteArray# s -> Int# -> Int# -> Word -> State# s -> State# s
forall a s.
Prim a =>
MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s
P.setByteArray# MutableByteArray# s
marr Int#
off Int#
len (GmpLimb# -> Word
W# GmpLimb#
x#) State# s
token
      Natural
_        -> String -> State# s
forall a. HasCallStack => String -> a
error String
"argument is larger than modulo"
    NatJ# BigNat
m# -> case MutableByteArray# s -> Int# -> Mod m -> State# s -> State# s
forall a s.
Prim a =>
MutableByteArray# s -> Int# -> a -> State# s -> State# s
P.writeByteArray# MutableByteArray# s
marr Int#
off Mod m
mx State# s
token of
      State# s
newToken -> Int# -> State# s -> State# s
doSet (Int#
sz Int# -> Int# -> Int#
`iShiftL#` Int#
lgWordSize#) State# s
newToken
      where
        !(I# Int#
lgWordSize#) = Int
lgWordSize
        sz :: Int#
sz = BigNat -> Int#
sizeofBigNat# BigNat
m#
        off' :: Int#
off' = (Int#
off Int# -> Int# -> Int#
*# Int#
sz) Int# -> Int# -> Int#
`iShiftL#` Int#
lgWordSize#
        len' :: Int#
len' = (Int#
len Int# -> Int# -> Int#
*# Int#
sz) Int# -> Int# -> Int#
`iShiftL#` Int#
lgWordSize#
        doSet :: Int# -> State# s -> State# s
doSet Int#
i State# s
tkn
          | Int# -> Bool
isTrue# (Int#
2# Int# -> Int# -> Int#
*# Int#
i Int# -> Int# -> Int#
<# Int#
len') = case MutableByteArray# s
-> Int#
-> MutableByteArray# s
-> Int#
-> Int#
-> State# s
-> State# s
forall d.
MutableByteArray# d
-> Int#
-> MutableByteArray# d
-> Int#
-> Int#
-> State# d
-> State# d
copyMutableByteArray# MutableByteArray# s
marr Int#
off' MutableByteArray# s
marr (Int#
off' Int# -> Int# -> Int#
+# Int#
i) Int#
i State# s
tkn of
            State# s
tkn' -> Int# -> State# s -> State# s
doSet (Int#
2# Int# -> Int# -> Int#
*# Int#
i) State# s
tkn'
          | Bool
otherwise    = MutableByteArray# s
-> Int#
-> MutableByteArray# s
-> Int#
-> Int#
-> State# s
-> State# s
forall d.
MutableByteArray# d
-> Int#
-> MutableByteArray# d
-> Int#
-> Int#
-> State# d
-> State# d
copyMutableByteArray# MutableByteArray# s
marr Int#
off' MutableByteArray# s
marr (Int#
off' Int# -> Int# -> Int#
+# Int#
i) (Int#
len' Int# -> Int# -> Int#
-# Int#
i) State# s
tkn
  {-# INLINE setByteArray# #-}

  setOffAddr# :: Addr# -> Int# -> Int# -> Mod m -> State# s -> State# s
setOffAddr# !Addr#
_ !Int#
_ Int#
0# !Mod m
_ State# s
token = State# s
token
  setOffAddr# Addr#
marr Int#
off Int#
len mx :: Mod m
mx@(Mod Natural
x) State# s
token = case Proxy# m -> Natural
forall (n :: Nat). KnownNat n => Proxy# n -> Natural
natVal' (Proxy# m
forall k (a :: k). Proxy# a
proxy# :: Proxy# m) of
    NatS#{} -> case Natural
x of
      NatS# GmpLimb#
x# -> Addr# -> Int# -> Int# -> Word -> State# s -> State# s
forall a s.
Prim a =>
Addr# -> Int# -> Int# -> a -> State# s -> State# s
P.setOffAddr# Addr#
marr Int#
off Int#
len (GmpLimb# -> Word
W# GmpLimb#
x#) State# s
token
      Natural
_        -> String -> State# s
forall a. HasCallStack => String -> a
error String
"argument is larger than modulo"
    NatJ# BigNat
m# -> case Addr# -> Int# -> Mod m -> State# s -> State# s
forall a s. Prim a => Addr# -> Int# -> a -> State# s -> State# s
P.writeOffAddr# Addr#
marr Int#
off Mod m
mx State# s
token of
      State# s
newToken -> Int# -> State# s -> State# s
doSet (Int#
sz Int# -> Int# -> Int#
`iShiftL#` Int#
lgWordSize#) State# s
newToken
      where
        !(I# Int#
lgWordSize#) = Int
lgWordSize
        sz :: Int#
sz = BigNat -> Int#
sizeofBigNat# BigNat
m#
        off' :: Int#
off' = (Int#
off Int# -> Int# -> Int#
*# Int#
sz) Int# -> Int# -> Int#
`iShiftL#` Int#
lgWordSize#
        len' :: Int#
len' = (Int#
len Int# -> Int# -> Int#
*# Int#
sz) Int# -> Int# -> Int#
`iShiftL#` Int#
lgWordSize#
        doSet :: Int# -> State# s -> State# s
doSet Int#
i State# s
tkn -- = tkn
          | Int# -> Bool
isTrue# (Int#
2# Int# -> Int# -> Int#
*# Int#
i Int# -> Int# -> Int#
<# Int#
len') = case ST s ()
-> State# (PrimState (ST s)) -> (# State# (PrimState (ST s)), () #)
forall (m :: * -> *) a.
PrimBase m =>
m a -> State# (PrimState m) -> (# State# (PrimState m), a #)
internal (IO () -> ST s ()
forall (m :: * -> *) a. PrimMonad m => IO a -> m a
unsafeIOToPrim (Ptr Any -> Ptr Any -> Int -> IO ()
forall a. Ptr a -> Ptr a -> Int -> IO ()
copyBytes (Addr# -> Ptr Any
forall a. Addr# -> Ptr a
Ptr (Addr#
marr Addr# -> Int# -> Addr#
`plusAddr#` (Int#
off' Int# -> Int# -> Int#
+# Int#
i))) (Addr# -> Ptr Any
forall a. Addr# -> Ptr a
Ptr (Addr#
marr Addr# -> Int# -> Addr#
`plusAddr#` Int#
off')) (Int# -> Int
I# Int#
i)) :: ST s ()) State# s
State# (PrimState (ST s))
tkn of
            (# State# (PrimState (ST s))
tkn', () #) -> Int# -> State# s -> State# s
doSet (Int#
2# Int# -> Int# -> Int#
*# Int#
i) State# s
State# (PrimState (ST s))
tkn'
          | Bool
otherwise    = case ST s ()
-> State# (PrimState (ST s)) -> (# State# (PrimState (ST s)), () #)
forall (m :: * -> *) a.
PrimBase m =>
m a -> State# (PrimState m) -> (# State# (PrimState m), a #)
internal (IO () -> ST s ()
forall (m :: * -> *) a. PrimMonad m => IO a -> m a
unsafeIOToPrim (Ptr Any -> Ptr Any -> Int -> IO ()
forall a. Ptr a -> Ptr a -> Int -> IO ()
copyBytes (Addr# -> Ptr Any
forall a. Addr# -> Ptr a
Ptr (Addr#
marr Addr# -> Int# -> Addr#
`plusAddr#` (Int#
off' Int# -> Int# -> Int#
+# Int#
i))) (Addr# -> Ptr Any
forall a. Addr# -> Ptr a
Ptr (Addr#
marr Addr# -> Int# -> Addr#
`plusAddr#` Int#
off')) (Int# -> Int
I# (Int#
len' Int# -> Int# -> Int#
-# Int#
i))) :: ST s ()) State# s
State# (PrimState (ST s))
tkn of
            (# State# (PrimState (ST s))
tkn', () #) -> State# s
State# (PrimState (ST s))
tkn'
  {-# INLINE setOffAddr# #-}

-- | Unboxed vectors of 'Mod' cause more nursery allocations
-- than boxed ones, but reduce pressure on garbage collector,
-- especially for large vectors.
newtype instance U.MVector s (Mod m) = ModMVec (P.MVector s (Mod m))

-- | Unboxed vectors of 'Mod' cause more nursery allocations
-- than boxed ones, but reduce pressure on garbage collector,
-- especially for large vectors.
newtype instance U.Vector    (Mod m) = ModVec  (P.Vector (Mod m))

instance KnownNat m => U.Unbox (Mod m)

instance KnownNat m => M.MVector U.MVector (Mod m) where
  {-# INLINE basicLength #-}
  {-# INLINE basicUnsafeSlice #-}
  {-# INLINE basicOverlaps #-}
  {-# INLINE basicUnsafeNew #-}
  {-# INLINE basicInitialize #-}
  {-# INLINE basicUnsafeReplicate #-}
  {-# INLINE basicUnsafeRead #-}
  {-# INLINE basicUnsafeWrite #-}
  {-# INLINE basicClear #-}
  {-# INLINE basicSet #-}
  {-# INLINE basicUnsafeCopy #-}
  {-# INLINE basicUnsafeGrow #-}
  basicLength :: MVector s (Mod m) -> Int
basicLength (ModMVec v) = MVector s (Mod m) -> Int
forall (v :: * -> * -> *) a s. MVector v a => v s a -> Int
M.basicLength MVector s (Mod m)
v
  basicUnsafeSlice :: Int -> Int -> MVector s (Mod m) -> MVector s (Mod m)
basicUnsafeSlice Int
i Int
n (ModMVec v) = MVector s (Mod m) -> MVector s (Mod m)
forall s (m :: Nat). MVector s (Mod m) -> MVector s (Mod m)
ModMVec (MVector s (Mod m) -> MVector s (Mod m))
-> MVector s (Mod m) -> MVector s (Mod m)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> MVector s (Mod m) -> MVector s (Mod m)
forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> Int -> v s a -> v s a
M.basicUnsafeSlice Int
i Int
n MVector s (Mod m)
v
  basicOverlaps :: MVector s (Mod m) -> MVector s (Mod m) -> Bool
basicOverlaps (ModMVec v1) (ModMVec v2) = MVector s (Mod m) -> MVector s (Mod m) -> Bool
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> Bool
M.basicOverlaps MVector s (Mod m)
v1 MVector s (Mod m)
v2
  basicUnsafeNew :: Int -> m (MVector (PrimState m) (Mod m))
basicUnsafeNew Int
n = MVector (PrimState m) (Mod m) -> MVector (PrimState m) (Mod m)
forall s (m :: Nat). MVector s (Mod m) -> MVector s (Mod m)
ModMVec (MVector (PrimState m) (Mod m) -> MVector (PrimState m) (Mod m))
-> m (MVector (PrimState m) (Mod m))
-> m (MVector (PrimState m) (Mod m))
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` Int -> m (MVector (PrimState m) (Mod m))
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
Int -> m (v (PrimState m) a)
M.basicUnsafeNew Int
n
  basicInitialize :: MVector (PrimState m) (Mod m) -> m ()
basicInitialize (ModMVec v) = MVector (PrimState m) (Mod m) -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> m ()
M.basicInitialize MVector (PrimState m) (Mod m)
v
  basicUnsafeReplicate :: Int -> Mod m -> m (MVector (PrimState m) (Mod m))
basicUnsafeReplicate Int
n Mod m
x = MVector (PrimState m) (Mod m) -> MVector (PrimState m) (Mod m)
forall s (m :: Nat). MVector s (Mod m) -> MVector s (Mod m)
ModMVec (MVector (PrimState m) (Mod m) -> MVector (PrimState m) (Mod m))
-> m (MVector (PrimState m) (Mod m))
-> m (MVector (PrimState m) (Mod m))
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` Int -> Mod m -> m (MVector (PrimState m) (Mod m))
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
Int -> a -> m (v (PrimState m) a)
M.basicUnsafeReplicate Int
n Mod m
x
  basicUnsafeRead :: MVector (PrimState m) (Mod m) -> Int -> m (Mod m)
basicUnsafeRead (ModMVec v) Int
i = MVector (PrimState m) (Mod m) -> Int -> m (Mod m)
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m a
M.basicUnsafeRead MVector (PrimState m) (Mod m)
v Int
i
  basicUnsafeWrite :: MVector (PrimState m) (Mod m) -> Int -> Mod m -> m ()
basicUnsafeWrite (ModMVec v) Int
i Mod m
x = MVector (PrimState m) (Mod m) -> Int -> Mod m -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> a -> m ()
M.basicUnsafeWrite MVector (PrimState m) (Mod m)
v Int
i Mod m
x
  basicClear :: MVector (PrimState m) (Mod m) -> m ()
basicClear (ModMVec v) = MVector (PrimState m) (Mod m) -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> m ()
M.basicClear MVector (PrimState m) (Mod m)
v
  basicSet :: MVector (PrimState m) (Mod m) -> Mod m -> m ()
basicSet (ModMVec v) Mod m
x = MVector (PrimState m) (Mod m) -> Mod m -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> a -> m ()
M.basicSet MVector (PrimState m) (Mod m)
v Mod m
x
  basicUnsafeCopy :: MVector (PrimState m) (Mod m)
-> MVector (PrimState m) (Mod m) -> m ()
basicUnsafeCopy (ModMVec v1) (ModMVec v2) = MVector (PrimState m) (Mod m)
-> MVector (PrimState m) (Mod m) -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> v (PrimState m) a -> m ()
M.basicUnsafeCopy MVector (PrimState m) (Mod m)
v1 MVector (PrimState m) (Mod m)
v2
  basicUnsafeMove :: MVector (PrimState m) (Mod m)
-> MVector (PrimState m) (Mod m) -> m ()
basicUnsafeMove (ModMVec v1) (ModMVec v2) = MVector (PrimState m) (Mod m)
-> MVector (PrimState m) (Mod m) -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> v (PrimState m) a -> m ()
M.basicUnsafeMove MVector (PrimState m) (Mod m)
v1 MVector (PrimState m) (Mod m)
v2
  basicUnsafeGrow :: MVector (PrimState m) (Mod m)
-> Int -> m (MVector (PrimState m) (Mod m))
basicUnsafeGrow (ModMVec v) Int
n = MVector (PrimState m) (Mod m) -> MVector (PrimState m) (Mod m)
forall s (m :: Nat). MVector s (Mod m) -> MVector s (Mod m)
ModMVec (MVector (PrimState m) (Mod m) -> MVector (PrimState m) (Mod m))
-> m (MVector (PrimState m) (Mod m))
-> m (MVector (PrimState m) (Mod m))
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` MVector (PrimState m) (Mod m)
-> Int -> m (MVector (PrimState m) (Mod m))
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m (v (PrimState m) a)
M.basicUnsafeGrow MVector (PrimState m) (Mod m)
v Int
n

instance KnownNat m => G.Vector U.Vector (Mod m) where
  {-# INLINE basicUnsafeFreeze #-}
  {-# INLINE basicUnsafeThaw #-}
  {-# INLINE basicLength #-}
  {-# INLINE basicUnsafeSlice #-}
  {-# INLINE basicUnsafeIndexM #-}
  {-# INLINE elemseq #-}
  basicUnsafeFreeze :: Mutable Vector (PrimState m) (Mod m) -> m (Vector (Mod m))
basicUnsafeFreeze (ModMVec v) = Vector (Mod m) -> Vector (Mod m)
forall (m :: Nat). Vector (Mod m) -> Vector (Mod m)
ModVec (Vector (Mod m) -> Vector (Mod m))
-> m (Vector (Mod m)) -> m (Vector (Mod m))
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` Mutable Vector (PrimState m) (Mod m) -> m (Vector (Mod m))
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
Mutable v (PrimState m) a -> m (v a)
G.basicUnsafeFreeze MVector (PrimState m) (Mod m)
Mutable Vector (PrimState m) (Mod m)
v
  basicUnsafeThaw :: Vector (Mod m) -> m (Mutable Vector (PrimState m) (Mod m))
basicUnsafeThaw (ModVec v) = MVector (PrimState m) (Mod m) -> MVector (PrimState m) (Mod m)
forall s (m :: Nat). MVector s (Mod m) -> MVector s (Mod m)
ModMVec (MVector (PrimState m) (Mod m) -> MVector (PrimState m) (Mod m))
-> m (MVector (PrimState m) (Mod m))
-> m (MVector (PrimState m) (Mod m))
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` Vector (Mod m) -> m (Mutable Vector (PrimState m) (Mod m))
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
v a -> m (Mutable v (PrimState m) a)
G.basicUnsafeThaw Vector (Mod m)
v
  basicLength :: Vector (Mod m) -> Int
basicLength (ModVec v) = Vector (Mod m) -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
G.basicLength Vector (Mod m)
v
  basicUnsafeSlice :: Int -> Int -> Vector (Mod m) -> Vector (Mod m)
basicUnsafeSlice Int
i Int
n (ModVec v) = Vector (Mod m) -> Vector (Mod m)
forall (m :: Nat). Vector (Mod m) -> Vector (Mod m)
ModVec (Vector (Mod m) -> Vector (Mod m))
-> Vector (Mod m) -> Vector (Mod m)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Vector (Mod m) -> Vector (Mod m)
forall (v :: * -> *) a. Vector v a => Int -> Int -> v a -> v a
G.basicUnsafeSlice Int
i Int
n Vector (Mod m)
v
  basicUnsafeIndexM :: Vector (Mod m) -> Int -> m (Mod m)
basicUnsafeIndexM (ModVec v) Int
i = Vector (Mod m) -> Int -> m (Mod m)
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, Monad m) =>
v a -> Int -> m a
G.basicUnsafeIndexM Vector (Mod m)
v Int
i
  basicUnsafeCopy :: Mutable Vector (PrimState m) (Mod m) -> Vector (Mod m) -> m ()
basicUnsafeCopy (ModMVec mv) (ModVec v) = Mutable Vector (PrimState m) (Mod m) -> Vector (Mod m) -> m ()
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
Mutable v (PrimState m) a -> v a -> m ()
G.basicUnsafeCopy MVector (PrimState m) (Mod m)
Mutable Vector (PrimState m) (Mod m)
mv Vector (Mod m)
v
  elemseq :: Vector (Mod m) -> Mod m -> b -> b
elemseq Vector (Mod m)
_ = Mod m -> b -> b
seq

#endif