-- |
-- Module:      Data.Mod.Word
-- Copyright:   (c) 2017-2022 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 the <https://hackage.haskell.org/package/arithmoi arithmoi> package.
--
-- This module supports only moduli, which fit into 'Word'.
-- Use the (slower) "Data.Mod" module for handling arbitrary-sized moduli.

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

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

import Prelude as P hiding (even)
import Control.Exception
import Control.DeepSeq
import Data.Bits
import Data.Mod.Compat (timesWord2#, remWord2#)
import Data.Ratio
#ifdef MIN_VERSION_semirings
import Data.Euclidean (GcdDomain(..), Euclidean(..), Field)
import Data.Semiring (Semiring(..), Ring(..))
#endif
#ifdef MIN_VERSION_vector
import Data.Primitive (Prim)
import qualified Data.Vector.Generic         as G
import qualified Data.Vector.Generic.Mutable as M
import qualified Data.Vector.Primitive       as P
import qualified Data.Vector.Unboxed         as U
#endif
import Foreign.Storable (Storable)
import GHC.Exts hiding (timesWord2#, quotRemWord2#)
import GHC.Generics
import GHC.Natural (Natural(..))
import GHC.Num.BigNat
import GHC.Num.Integer
import GHC.TypeNats (Nat, KnownNat, natVal)
import Text.Read (Read(readPrec))

-- | 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
--
-- __Note:__ 'Mod' 0 has no inhabitants, eventhough \( \mathbb{Z}/0\mathbb{Z} \) is technically isomorphic to \( \mathbb{Z} \).
newtype Mod (m :: Nat) = Mod
  { forall (m :: Nat). Mod m -> Word
unMod :: Word
  -- ^ The canonical representative of the residue class,
  -- always between 0 and \( m - 1 \) (inclusively).
  --
  -- >>> :set -XDataKinds
  -- >>> -1 :: Mod 10
  -- 9
  }
  deriving (Mod m -> Mod m -> Bool
forall (m :: Nat). Mod m -> Mod m -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: 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, Mod m -> Mod m -> Bool
Mod m -> Mod m -> Ordering
Mod m -> Mod m -> Mod m
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
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
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
Ord, forall (m :: Nat) x. Rep (Mod m) x -> Mod m
forall (m :: Nat) x. Mod m -> Rep (Mod m) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall (m :: Nat) x. Rep (Mod m) x -> Mod m
$cfrom :: forall (m :: Nat) x. Mod m -> Rep (Mod m) x
Generic)
  deriving Ptr (Mod m) -> IO (Mod m)
Ptr (Mod m) -> Int -> IO (Mod m)
Ptr (Mod m) -> Int -> Mod m -> IO ()
Ptr (Mod m) -> Mod m -> IO ()
Mod m -> Int
forall (m :: Nat). Ptr (Mod m) -> IO (Mod m)
forall (m :: Nat). Ptr (Mod m) -> Int -> IO (Mod m)
forall (m :: Nat). Ptr (Mod m) -> Int -> Mod m -> IO ()
forall (m :: Nat). Ptr (Mod m) -> Mod m -> IO ()
forall (m :: Nat). Mod m -> Int
forall (m :: Nat) b. Ptr b -> Int -> IO (Mod m)
forall (m :: Nat) b. Ptr b -> Int -> Mod m -> IO ()
forall b. Ptr b -> Int -> IO (Mod m)
forall b. Ptr b -> Int -> Mod m -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr (Mod m) -> Mod m -> IO ()
$cpoke :: forall (m :: Nat). Ptr (Mod m) -> Mod m -> IO ()
peek :: Ptr (Mod m) -> IO (Mod m)
$cpeek :: forall (m :: Nat). Ptr (Mod m) -> IO (Mod m)
pokeByteOff :: forall b. Ptr b -> Int -> Mod m -> IO ()
$cpokeByteOff :: forall (m :: Nat) b. Ptr b -> Int -> Mod m -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO (Mod m)
$cpeekByteOff :: forall (m :: Nat) b. Ptr b -> Int -> IO (Mod m)
pokeElemOff :: Ptr (Mod m) -> Int -> Mod m -> IO ()
$cpokeElemOff :: forall (m :: Nat). Ptr (Mod m) -> Int -> Mod m -> IO ()
peekElemOff :: Ptr (Mod m) -> Int -> IO (Mod m)
$cpeekElemOff :: forall (m :: Nat). Ptr (Mod m) -> Int -> IO (Mod m)
alignment :: Mod m -> Int
$calignment :: forall (m :: Nat). Mod m -> Int
sizeOf :: Mod m -> Int
$csizeOf :: forall (m :: Nat). Mod m -> Int
Storable
  -- ^ No validation checks are performed;
  -- reading untrusted data may corrupt internal invariants.
#ifdef MIN_VERSION_vector
  deriving Addr# -> Int# -> Mod m
ByteArray# -> Int# -> Mod m
Mod m -> Int#
forall (m :: Nat). Addr# -> Int# -> Mod m
forall (m :: Nat). ByteArray# -> Int# -> Mod m
forall (m :: Nat). Mod m -> Int#
forall (m :: Nat) s.
Addr# -> Int# -> Int# -> Mod m -> State# s -> State# s
forall (m :: Nat) s.
Addr# -> Int# -> State# s -> (# State# s, Mod m #)
forall (m :: Nat) s. Addr# -> Int# -> Mod m -> State# s -> State# s
forall (m :: Nat) s.
MutableByteArray# s
-> Int# -> Int# -> Mod m -> State# s -> State# s
forall (m :: Nat) s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Mod m #)
forall (m :: Nat) s.
MutableByteArray# s -> Int# -> Mod m -> State# s -> State# s
forall s. Addr# -> Int# -> Int# -> Mod m -> State# s -> State# s
forall s. Addr# -> Int# -> State# s -> (# State# s, Mod m #)
forall s. Addr# -> Int# -> Mod m -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> Int# -> Mod m -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Mod m #)
forall s.
MutableByteArray# s -> Int# -> Mod m -> State# s -> State# s
forall a.
(a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
setOffAddr# :: forall s. Addr# -> Int# -> Int# -> Mod m -> State# s -> State# s
$csetOffAddr# :: forall (m :: Nat) s.
Addr# -> Int# -> Int# -> Mod m -> State# s -> State# s
writeOffAddr# :: forall s. Addr# -> Int# -> Mod m -> State# s -> State# s
$cwriteOffAddr# :: forall (m :: Nat) s. Addr# -> Int# -> Mod m -> State# s -> State# s
readOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Mod m #)
$creadOffAddr# :: forall (m :: Nat) s.
Addr# -> Int# -> State# s -> (# State# s, Mod m #)
indexOffAddr# :: Addr# -> Int# -> Mod m
$cindexOffAddr# :: forall (m :: Nat). Addr# -> Int# -> Mod m
setByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Mod m -> State# s -> State# s
$csetByteArray# :: forall (m :: Nat) s.
MutableByteArray# s
-> Int# -> Int# -> Mod m -> State# s -> State# s
writeByteArray# :: forall s.
MutableByteArray# s -> Int# -> Mod m -> State# s -> State# s
$cwriteByteArray# :: forall (m :: Nat) s.
MutableByteArray# s -> Int# -> Mod m -> State# s -> State# s
readByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Mod m #)
$creadByteArray# :: forall (m :: Nat) s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Mod m #)
indexByteArray# :: ByteArray# -> Int# -> Mod m
$cindexByteArray# :: forall (m :: Nat). ByteArray# -> Int# -> Mod m
alignment# :: Mod m -> Int#
$calignment# :: forall (m :: Nat). Mod m -> Int#
sizeOf# :: Mod m -> Int#
$csizeOf# :: forall (m :: Nat). Mod m -> Int#
Prim
  -- ^ No validation checks are performed;
  -- reading untrusted data may corrupt internal invariants.
#endif

instance NFData (Mod m)

instance Show (Mod m) where
  show :: Mod m -> String
show (Mod Word
x) = forall a. Show a => a -> String
show Word
x

-- | Wrapping behaviour, similar to
-- the existing @instance@ 'Read' 'Int'.
instance KnownNat m => Read (Mod m) where
  readPrec :: ReadPrec (Mod m)
readPrec = forall a. Num a => Integer -> a
fromInteger forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Read a => ReadPrec a
readPrec

instance KnownNat m => Real (Mod m) where
  toRational :: Mod m -> Rational
toRational (Mod Word
x) = forall a. Real a => a -> Rational
toRational Word
x

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

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

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

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

instance KnownNat m => Bounded (Mod m) where
  minBound :: Mod m
minBound = Mod m
mx
    where
      mx :: Mod m
mx = if forall (n :: Nat) (proxy :: Nat -> *). KnownNat n => proxy n -> Nat
natVal Mod m
mx forall a. Ord a => a -> a -> Bool
> Nat
0 then forall (m :: Nat). Word -> Mod m
Mod Word
0 else forall a e. Exception e => e -> a
throw ArithException
DivideByZero
  maxBound :: Mod m
maxBound = Mod m
mx
    where
      mx :: Mod m
mx = if Nat
m forall a. Ord a => a -> a -> Bool
> Nat
0 then forall (m :: Nat). Word -> Mod m
Mod (forall a b. (Integral a, Num b) => a -> b
fromIntegral (Nat
m forall a. Num a => a -> a -> a
- Nat
1)) else forall a e. Exception e => e -> a
throw ArithException
DivideByZero
      m :: Nat
m = forall (n :: Nat) (proxy :: Nat -> *). KnownNat n => proxy n -> Nat
natVal Mod m
mx

addMod :: Natural -> Word -> Word -> Word
addMod :: Nat -> Word -> Word -> Word
addMod (NatS# Word#
m#) (W# Word#
x#) (W# Word#
y#) =
  if Int# -> Bool
isTrue# Int#
c# Bool -> Bool -> Bool
|| Int# -> Bool
isTrue# (Word#
z# Word# -> Word# -> Int#
`geWord#` Word#
m#) then Word# -> Word
W# (Word#
z# Word# -> Word# -> Word#
`minusWord#` Word#
m#) else Word# -> Word
W# Word#
z#
  where
    !(# Word#
z#, Int#
c# #) = Word#
x# Word# -> Word# -> (# Word#, Int# #)
`addWordC#` Word#
y#
addMod NatJ#{} Word
_ Word
_ = forall a. a
tooLargeModulus

subMod :: Natural -> Word -> Word -> Word
subMod :: Nat -> Word -> Word -> Word
subMod (NatS# Word#
m#) (W# Word#
x#) (W# Word#
y#) =
  if Int# -> Bool
isTrue# (Word#
x# Word# -> Word# -> Int#
`geWord#` Word#
y#) then Word# -> Word
W# Word#
z# else Word# -> Word
W# (Word#
z# Word# -> Word# -> Word#
`plusWord#` Word#
m#)
  where
    z# :: Word#
z# = Word#
x# Word# -> Word# -> Word#
`minusWord#` Word#
y#
subMod NatJ#{} Word
_ Word
_ = forall a. a
tooLargeModulus

negateMod :: Natural -> Word -> Word
negateMod :: Nat -> Word -> Word
negateMod Nat
_ (W# Word#
0##) = Word# -> Word
W# Word#
0##
negateMod (NatS# Word#
m#) (W# Word#
x#) = Word# -> Word
W# (Word#
m# Word# -> Word# -> Word#
`minusWord#` Word#
x#)
negateMod NatJ#{} Word
_ = forall a. a
tooLargeModulus

halfWord :: Word
halfWord :: Word
halfWord = Word
1 forall a. Bits a => a -> Int -> a
`shiftL` (forall b. FiniteBits b => b -> Int
finiteBitSize (Word
0 :: Word) forall a. Bits a => a -> Int -> a
`shiftR` Int
1)

mulMod :: Natural -> Word -> Word -> Word
mulMod :: Nat -> Word -> Word -> Word
mulMod (NatS# Word#
m#) (W# Word#
x#) (W# Word#
y#)
  | Word# -> Word
W# Word#
m# forall a. Ord a => a -> a -> Bool
<= Word
halfWord = Word# -> Word
W# (Word# -> Word# -> Word#
timesWord# Word#
x# Word#
y# Word# -> Word# -> Word#
`remWord#` Word#
m#)
  | Bool
otherwise = Word# -> Word
W# Word#
r#
  where
    !(# Word#
hi#, Word#
lo# #) = Word# -> Word# -> (# Word#, Word# #)
timesWord2# Word#
x# Word#
y#
    !r# :: Word#
r# = Word# -> Word# -> Word# -> Word#
remWord2# Word#
lo# Word#
hi# Word#
m#
mulMod NatJ#{} Word
_ Word
_ = forall a. a
tooLargeModulus

fromIntegerMod :: Natural -> Integer -> Word
fromIntegerMod :: Nat -> Integer -> Word
fromIntegerMod (NatS# Word#
0##) !Integer
_ = forall a e. Exception e => e -> a
throw ArithException
DivideByZero
fromIntegerMod (NatS# Word#
m#) (IS Int#
x#) =
  if Int# -> Bool
isTrue# (Int#
x# Int# -> Int# -> Int#
>=# Int#
0#)
    then Word# -> Word
W# (Int# -> Word#
int2Word# Int#
x# Word# -> Word# -> Word#
`remWord#` Word#
m#)
    else Nat -> Word -> Word
negateMod (Word# -> Nat
NatS# Word#
m#) (Word# -> Word
W# (Int# -> Word#
int2Word# (Int# -> Int#
negateInt# Int#
x#) Word# -> Word# -> Word#
`remWord#` Word#
m#))
fromIntegerMod (NatS# Word#
m#) (IP ByteArray#
x#) =
  Word# -> Word
W# (ByteArray#
x# ByteArray# -> Word# -> Word#
`bigNatRemWord#` Word#
m#)
fromIntegerMod (NatS# Word#
m#) (IN ByteArray#
x#) =
  Nat -> Word -> Word
negateMod (Word# -> Nat
NatS# Word#
m#) (Word# -> Word
W# (ByteArray#
x# ByteArray# -> Word# -> Word#
`bigNatRemWord#` Word#
m#))
fromIntegerMod NatJ#{} Integer
_ = forall a. a
tooLargeModulus

#ifdef MIN_VERSION_semirings

fromNaturalMod :: Natural -> Natural -> Word
fromNaturalMod :: Nat -> Nat -> Word
fromNaturalMod (NatS# Word#
0##) !Nat
_ = forall a e. Exception e => e -> a
throw ArithException
DivideByZero
fromNaturalMod (NatS# Word#
m#) (NatS# Word#
x#) = Word# -> Word
W# (Word#
x# Word# -> Word# -> Word#
`remWord#` Word#
m#)
fromNaturalMod (NatS# Word#
m#) (NatJ# (BN# ByteArray#
x#)) = Word# -> Word
W# (ByteArray#
x# ByteArray# -> Word# -> Word#
`bigNatRemWord#` Word#
m#)
fromNaturalMod NatJ#{} Nat
_ = forall a. a
tooLargeModulus

getModulus :: Natural -> Word
getModulus :: Nat -> Word
getModulus (NatS# Word#
m#) = Word# -> Word
W# Word#
m#
getModulus NatJ#{} = forall a. a
tooLargeModulus

#endif

tooLargeModulus :: a
tooLargeModulus :: forall a. a
tooLargeModulus = forall a. HasCallStack => String -> a
error String
"modulus does not fit into a machine word"

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

#ifdef MIN_VERSION_semirings

instance KnownNat m => Semiring (Mod m) where
  plus :: Mod m -> Mod m -> Mod m
plus  = forall a. Num a => a -> a -> a
(+)
  {-# INLINE plus #-}
  times :: Mod m -> Mod m -> Mod m
times = forall a. Num a => a -> a -> a
(*)
  {-# INLINE times #-}
  zero :: Mod m
zero  = Mod m
mx
    where
      mx :: Mod m
mx = if forall (n :: Nat) (proxy :: Nat -> *). KnownNat n => proxy n -> Nat
natVal Mod m
mx forall a. Ord a => a -> a -> Bool
> Nat
0 then forall (m :: Nat). Word -> Mod m
Mod Word
0 else forall a e. Exception e => e -> a
throw ArithException
DivideByZero
  {-# INLINE zero #-}
  one :: Mod m
one   = Mod m
mx
    where
      mx :: Mod m
mx = case Nat
m forall a. Ord a => a -> a -> Ordering
`compare` Nat
1 of
        Ordering
LT -> forall a e. Exception e => e -> a
throw ArithException
DivideByZero
        Ordering
EQ -> forall (m :: Nat). Word -> Mod m
Mod Word
0
        Ordering
GT -> forall (m :: Nat). Word -> Mod m
Mod Word
1
      m :: Nat
m = forall (n :: Nat) (proxy :: Nat -> *). KnownNat n => proxy n -> Nat
natVal Mod m
mx
  {-# INLINE one #-}
  fromNatural :: Nat -> Mod m
fromNatural Nat
x = Mod m
mx
    where
      mx :: Mod m
mx = forall (m :: Nat). Word -> Mod m
Mod forall a b. (a -> b) -> a -> b
$ Nat -> Nat -> Word
fromNaturalMod (forall (n :: Nat) (proxy :: Nat -> *). KnownNat n => proxy n -> Nat
natVal Mod m
mx) Nat
x
  {-# INLINE fromNatural #-}

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

-- | 'Mod' @m@ is not even an
-- <https://en.wikipedia.org/wiki/Integral_domain integral domain> for
-- <https://en.wikipedia.org/wiki/Composite_number composite> @m@,
-- much less a <https://en.wikipedia.org/wiki/GCD_domain GCD domain>.
-- However, 'Data.Euclidean.gcd' and 'Data.Euclidean.lcm' are still meaningful
-- even for composite @m@, corresponding to a sum and an intersection of
-- <https://en.wikipedia.org/wiki/Ideal_(ring_theory) ideals>.
--
-- The instance is lawful only for
-- <https://en.wikipedia.org/wiki/Prime_number prime> @m@, otherwise
-- @'Data.Euclidean.divide' x y@ tries to return any @Just z@ such that @x == y * z@.
--
instance KnownNat m => GcdDomain (Mod m) where
  divide :: Mod m -> Mod m -> Maybe (Mod m)
divide (Mod Word
0) !Mod m
_ = forall a. a -> Maybe a
Just (forall (m :: Nat). Word -> Mod m
Mod Word
0)
  divide Mod m
_ (Mod Word
0) = forall a. Maybe a
Nothing
  divide mx :: Mod m
mx@(Mod Word
x) (Mod Word
y) = case Maybe Word
mry of
    Just Word
ry -> if Word
xr forall a. Eq a => a -> a -> Bool
== Word
0 then forall a. a -> Maybe a
Just (forall (m :: Nat). Word -> Mod m
Mod Word
xq forall a. Num a => a -> a -> a
* forall (m :: Nat). Word -> Mod m
Mod Word
ry) else forall a. Maybe a
Nothing
    Maybe Word
Nothing -> forall a. Maybe a
Nothing
    where
      m :: Word
m = Nat -> Word
getModulus (forall (n :: Nat) (proxy :: Nat -> *). KnownNat n => proxy n -> Nat
natVal Mod m
mx)
      gmy :: Word
gmy = forall a. Integral a => a -> a -> a
P.gcd Word
m Word
y
      (Word
xq, Word
xr) = forall a. Integral a => a -> a -> (a, a)
P.quotRem Word
x Word
gmy
      mry :: Maybe Word
mry = Word -> Word -> Maybe Word
invertModWord (Word
y forall a. Integral a => a -> a -> a
`P.quot` Word
gmy)  (Word
m forall a. Integral a => a -> a -> a
`P.quot` Word
gmy)

  gcd :: Mod m -> Mod m -> Mod m
gcd (Mod !Word
x) (Mod !Word
y) = Mod m
g
    where
      m :: Word
m = Nat -> Word
getModulus (forall (n :: Nat) (proxy :: Nat -> *). KnownNat n => proxy n -> Nat
natVal Mod m
g)
      g :: Mod m
g = forall (m :: Nat). Word -> Mod m
Mod forall a b. (a -> b) -> a -> b
$ if Word
m forall a. Ord a => a -> a -> Bool
> Word
1 then forall a. Integral a => a -> a -> a
P.gcd (forall a. Integral a => a -> a -> a
P.gcd Word
m Word
x) Word
y else Word
0
  lcm :: Mod m -> Mod m -> Mod m
lcm (Mod !Word
x) (Mod !Word
y) = Mod m
l
    where
      m :: Word
m = Nat -> Word
getModulus (forall (n :: Nat) (proxy :: Nat -> *). KnownNat n => proxy n -> Nat
natVal Mod m
l)
      l :: Mod m
l = forall (m :: Nat). Word -> Mod m
Mod forall a b. (a -> b) -> a -> b
$ if Word
m forall a. Ord a => a -> a -> Bool
> Word
1 then forall a. Integral a => a -> a -> a
P.lcm (forall a. Integral a => a -> a -> a
P.gcd Word
m Word
x) (forall a. Integral a => a -> a -> a
P.gcd Word
m Word
y) else Word
0
  coprime :: Mod m -> Mod m -> Bool
coprime Mod m
x Mod m
y = forall a. GcdDomain a => a -> a -> a
Data.Euclidean.gcd Mod m
x Mod m
y forall a. Eq a => a -> a -> Bool
== forall a. Semiring a => a
one

-- | 'Mod' @m@ is not even an
-- <https://en.wikipedia.org/wiki/Integral_domain integral domain> for
-- <https://en.wikipedia.org/wiki/Composite_number composite> @m@,
-- much less a <https://en.wikipedia.org/wiki/Euclidean_domain Euclidean domain>.
--
-- The instance is lawful only for
-- <https://en.wikipedia.org/wiki/Prime_number prime> @m@, otherwise
-- we try to do our best:
-- @'Data.Euclidean.quot' x y@ returns any @z@ such that @x == y * z@,
-- 'Data.Euclidean.rem' is not always 0, and both can throw 'DivideByZero'.
--
instance KnownNat m => Euclidean (Mod m) where
  degree :: Mod m -> Nat
degree = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: Nat). Mod m -> Word
unMod

  quotRem :: Mod m -> Mod m -> (Mod m, Mod m)
quotRem (Mod Word
0) !Mod m
_ = (forall (m :: Nat). Word -> Mod m
Mod Word
0, forall (m :: Nat). Word -> Mod m
Mod Word
0)
  quotRem Mod m
_ (Mod Word
0) = forall a e. Exception e => e -> a
throw ArithException
DivideByZero
  quotRem mx :: Mod m
mx@(Mod Word
x) (Mod Word
y) = case Maybe Word
mry of
    Just Word
ry -> (forall (m :: Nat). Word -> Mod m
Mod Word
xq forall a. Num a => a -> a -> a
* forall (m :: Nat). Word -> Mod m
Mod Word
ry, forall (m :: Nat). Word -> Mod m
Mod Word
xr)
    Maybe Word
Nothing -> forall a e. Exception e => e -> a
throw ArithException
DivideByZero
    where
      m :: Word
m = Nat -> Word
getModulus (forall (n :: Nat) (proxy :: Nat -> *). KnownNat n => proxy n -> Nat
natVal Mod m
mx)
      gmy :: Word
gmy = forall a. Integral a => a -> a -> a
P.gcd Word
m Word
y
      (Word
xq, Word
xr) = forall a. Integral a => a -> a -> (a, a)
P.quotRem Word
x Word
gmy
      mry :: Maybe Word
mry = Word -> Word -> Maybe Word
invertModWord (Word
y forall a. Integral a => a -> a -> a
`P.quot` Word
gmy)  (Word
m forall a. Integral a => a -> a -> a
`P.quot` Word
gmy)

-- | 'Mod' @m@ is not even an
-- <https://en.wikipedia.org/wiki/Integral_domain integral domain> for
-- <https://en.wikipedia.org/wiki/Composite_number composite> @m@,
-- much less a <https://en.wikipedia.org/wiki/Field_(mathematics) field>.
--
-- The instance is lawful only for
-- <https://en.wikipedia.org/wiki/Prime_number prime> @m@, otherwise
-- division by a residue, which is not
-- <https://en.wikipedia.org/wiki/Coprime_integers coprime>
-- with the modulus, throws 'DivideByZero'.
-- Consider using 'invertMod' for non-prime moduli.
--
instance KnownNat m => Field (Mod m)

#endif

-- | Division by a residue, which is not
-- <https://en.wikipedia.org/wiki/Coprime_integers coprime>
-- with the modulus, throws 'DivideByZero'.
-- Consider using 'invertMod' for non-prime moduli.
instance KnownNat m => Fractional (Mod m) where
  fromRational :: Rational -> Mod m
fromRational Rational
r = case forall a. Ratio a -> a
denominator Rational
r of
    Integer
1   -> Mod m
num
    Integer
den -> Mod m
num forall a. Fractional a => a -> a -> a
/ forall a. Num a => Integer -> a
fromInteger Integer
den
    where
      num :: Mod m
num = forall a. Num a => Integer -> a
fromInteger (forall a. Ratio a -> a
numerator Rational
r)
  {-# INLINE fromRational #-}
  recip :: Mod m -> Mod m
recip Mod m
mx = case forall (m :: Nat). KnownNat m => Mod m -> Maybe (Mod m)
invertMod Mod m
mx of
    Maybe (Mod m)
Nothing -> forall a e. Exception e => e -> a
throw ArithException
DivideByZero
    Just Mod m
y  -> Mod m
y
  {-# INLINE recip #-}

-- | If an argument is
-- <https://en.wikipedia.org/wiki/Coprime_integers coprime>
-- with the modulus, return its modular inverse.
-- Otherwise return 'Nothing'.
--
-- >>> :set -XDataKinds
-- >>> invertMod 3 :: Mod 10 -- 3 * 7 = 21 ≡ 1 (mod 10)
-- Just 7
-- >>> invertMod 4 :: Mod 10 -- 4 and 10 are not coprime
-- Nothing
invertMod :: KnownNat m => Mod m -> Maybe (Mod m)
invertMod :: forall (m :: Nat). KnownNat m => Mod m -> Maybe (Mod m)
invertMod mx :: Mod m
mx@(Mod !Word
x) = case forall (n :: Nat) (proxy :: Nat -> *). KnownNat n => proxy n -> Nat
natVal Mod m
mx of
  NatJ#{}   -> forall a. a
tooLargeModulus
  NatS# Word#
0## -> forall a. Maybe a
Nothing
  NatS# Word#
m#  -> forall (m :: Nat). Word -> Mod m
Mod forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Word -> Word -> Maybe Word
invertModWord Word
x (Word# -> Word
W# Word#
m#)

invertModWord :: Word -> Word -> Maybe Word
invertModWord :: Word -> Word -> Maybe Word
invertModWord Word
x m :: Word
m@(W# Word#
m#)
  -- If both x and m are even, no inverse exists
  | Word -> Bool
even Word
x, Int# -> Bool
isTrue# (Word#
k# Word# -> Word# -> Int#
`gtWord#` Word#
0##) = forall a. Maybe a
Nothing
  | Bool
otherwise = case Word -> Word -> Maybe Word
invertModWordOdd Word
x Word
m' of
    Maybe Word
Nothing -> forall a. Maybe a
Nothing
    -- goDouble cares only about mod 2^k,
    -- so overflows and underflows in (1 - x * y) are fine
    Just Word
y -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Word -> Word -> Word
goDouble Word
y (Word
1 forall a. Num a => a -> a -> a
- Word
x forall a. Num a => a -> a -> a
* Word
y)
  where
    k# :: Word#
k# = Word# -> Word#
ctz# Word#
m#
    m' :: Word
m' = Word
m forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int# -> Int
I# (Word# -> Int#
word2Int# Word#
k#)

    xm' :: Word
xm' = Word
x forall a. Num a => a -> a -> a
* Word
m'

    goDouble :: Word -> Word -> Word
    goDouble :: Word -> Word -> Word
goDouble Word
acc r :: Word
r@(W# Word#
r#)
      | Int# -> Bool
isTrue# (Word#
tz# Word# -> Word# -> Int#
`geWord#` Word#
k#)
      = Word
acc
      | Bool
otherwise
      = Word -> Word -> Word
goDouble (Word
acc forall a. Num a => a -> a -> a
+ Word
m' forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
tz) (Word
r forall a. Num a => a -> a -> a
- Word
xm' forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
tz)
      where
        tz# :: Word#
tz# = Word# -> Word#
ctz# Word#
r#
        tz :: Int
tz = Int# -> Int
I# (Word# -> Int#
word2Int# Word#
tz#)

-- | Extended binary gcd.
-- The second argument must be odd.
invertModWordOdd :: Word -> Word -> Maybe Word
invertModWordOdd :: Word -> Word -> Maybe Word
invertModWordOdd Word
0 !Word
_ = forall a. Maybe a
Nothing
invertModWordOdd !Word
x !Word
m = Word -> Word -> Word -> Word -> Maybe Word
go00 Word
0 Word
m Word
1 Word
x
  where
    halfMp1 :: Word
    halfMp1 :: Word
halfMp1 = Word -> Word
half Word
m forall a. Num a => a -> a -> a
+ Word
1

    -- Both s and s' may be even
    go00 :: Word -> Word -> Word -> Word -> Maybe Word
    go00 :: Word -> Word -> Word -> Word -> Maybe Word
go00 !Word
r !Word
s !Word
r' !Word
s'
      | Word -> Bool
even Word
s = let (# Word
hr, Word
hs #) = Word -> Word -> (# Word, Word #)
doHalf Word
r Word
s in Word -> Word -> Word -> Word -> Maybe Word
go00 Word
hr Word
hs Word
r' Word
s'
      | Bool
otherwise = Word -> Word -> Word -> Word -> Maybe Word
go10 Word
r Word
s Word
r' Word
s'

    -- Here s is odd, s' may be even
    go10 :: Word -> Word -> Word -> Word -> Maybe Word
    go10 :: Word -> Word -> Word -> Word -> Maybe Word
go10 !Word
r !Word
s !Word
r' !Word
s'
      | Word -> Bool
even Word
s' = let (# Word
hr', Word
hs' #) = Word -> Word -> (# Word, Word #)
doHalf Word
r' Word
s' in Word -> Word -> Word -> Word -> Maybe Word
go10 Word
r Word
s Word
hr' Word
hs'
      | Bool
otherwise = Word -> Word -> Word -> Word -> Maybe Word
go11 Word
r Word
s Word
r' Word
s'

    -- Here s may be even, s' is odd
    go01 :: Word -> Word -> Word -> Word -> Maybe Word
    go01 :: Word -> Word -> Word -> Word -> Maybe Word
go01 !Word
r !Word
s !Word
r' !Word
s'
      | Word -> Bool
even Word
s = let (# Word
hr, Word
hs #) = Word -> Word -> (# Word, Word #)
doHalf Word
r Word
s in Word -> Word -> Word -> Word -> Maybe Word
go01 Word
hr Word
hs Word
r' Word
s'
      | Bool
otherwise = Word -> Word -> Word -> Word -> Maybe Word
go11 Word
r Word
s Word
r' Word
s'

    -- Both s and s' are odd
    go11 :: Word -> Word -> Word -> Word -> Maybe Word
    go11 :: Word -> Word -> Word -> Word -> Maybe Word
go11 !Word
r !Word
s !Word
r' !Word
s' = case Word
s forall a. Ord a => a -> a -> Ordering
`compare` Word
s' of
      Ordering
EQ -> if Word
s forall a. Eq a => a -> a -> Bool
== Word
1 then forall a. a -> Maybe a
Just Word
r else forall a. Maybe a
Nothing
      Ordering
LT -> let newR' :: Word
newR' = Word
r' forall a. Num a => a -> a -> a
- Word
r forall a. Num a => a -> a -> a
+ (Word
r Word -> Word -> Word
`ge` Word
r') forall a. Num a => a -> a -> a
* Word
m in
            let newS' :: Word
newS' = Word
s' forall a. Num a => a -> a -> a
- Word
s in
            let (# Word
hr', Word
hs' #) = Word -> Word -> (# Word, Word #)
doHalf Word
newR' Word
newS' in
            Word -> Word -> Word -> Word -> Maybe Word
go10 Word
r Word
s Word
hr' Word
hs'
      Ordering
GT -> let newR :: Word
newR = Word
r forall a. Num a => a -> a -> a
- Word
r' forall a. Num a => a -> a -> a
+ (Word
r' Word -> Word -> Word
`ge` Word
r) forall a. Num a => a -> a -> a
* Word
m in
            let newS :: Word
newS = Word
s forall a. Num a => a -> a -> a
- Word
s' in
            let (# Word
hr, Word
hs #) = Word -> Word -> (# Word, Word #)
doHalf Word
newR Word
newS in
            Word -> Word -> Word -> Word -> Maybe Word
go01 Word
hr Word
hs Word
r' Word
s'

    doHalf :: Word -> Word -> (# Word, Word #)
    doHalf :: Word -> Word -> (# Word, Word #)
doHalf Word
r Word
s = (# Word -> Word
half Word
r forall a. Num a => a -> a -> a
+ (Word
r forall a. Bits a => a -> a -> a
.&. Word
1) forall a. Num a => a -> a -> a
* Word
halfMp1, Word -> Word
half Word
s #)
    {-# INLINE doHalf #-}

-- | ge x y returns 1 is x >= y and 0 otherwise.
ge :: Word -> Word -> Word
ge :: Word -> Word -> Word
ge (W# Word#
x) (W# Word#
y) = Word# -> Word
W# (Int# -> Word#
int2Word# (Word#
x Word# -> Word# -> Int#
`geWord#` Word#
y))

even :: Word -> Bool
even :: Word -> Bool
even Word
x = (Word
x forall a. Bits a => a -> a -> a
.&. Word
1) forall a. Eq a => a -> a -> Bool
== Word
0
{-# INLINE even #-}

half :: Word -> Word
half :: Word -> Word
half Word
x = Word
x forall a. Bits a => a -> Int -> a
`shiftR` Int
1
{-# INLINE half #-}

-- | Drop-in replacement for 'Prelude.^' with a bit 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 modulus.
--
-- >>> :set -XDataKinds
-- >>> 3 ^% 4 :: Mod 10    -- 3 ^ 4 = 81 ≡ 1 (mod 10)
-- 1
-- >>> 3 ^% (-1) :: Mod 10 -- 3 * 7 = 21 ≡ 1 (mod 10)
-- 7
-- >>> 4 ^% (-1) :: Mod 10 -- 4 and 10 are not coprime
-- (*** Exception: divide by zero
(^%) :: (KnownNat m, Integral a) => Mod m -> a -> Mod m
mx :: Mod m
mx@(Mod !Word
x) ^% :: forall (m :: Nat) a.
(KnownNat m, Integral a) =>
Mod m -> a -> Mod m
^% a
a = case forall (n :: Nat) (proxy :: Nat -> *). KnownNat n => proxy n -> Nat
natVal Mod m
mx of
  NatJ#{} -> forall a. a
tooLargeModulus
  m :: Nat
m@(NatS# Word#
_)
    | a
a forall a. Ord a => a -> a -> Bool
< a
0 -> case forall (m :: Nat). KnownNat m => Mod m -> Maybe (Mod m)
invertMod Mod m
mx of
      Maybe (Mod m)
Nothing      -> forall a e. Exception e => e -> a
throw ArithException
DivideByZero
      Just (Mod Word
y) -> forall (m :: Nat). Word -> Mod m
Mod forall a b. (a -> b) -> a -> b
$ Word -> a -> Word -> Word
f Word
y (-a
a) Word
1
    | Bool
otherwise    -> forall (m :: Nat). Word -> Mod m
Mod forall a b. (a -> b) -> a -> b
$ Word -> a -> Word -> Word
f Word
x a
a Word
1
    where
      f :: Word -> a -> Word -> Word
f !Word
_ a
0 Word
acc = Word
acc
      f Word
b  a
e Word
acc = Word -> a -> Word -> Word
f (Nat -> Word -> Word -> Word
mulMod Nat
m Word
b Word
b) (a
e forall a. Integral a => a -> a -> a
`P.quot` a
2) (if forall a. Integral a => a -> Bool
odd a
e then Nat -> Word -> Word -> Word
mulMod Nat
m Word
b Word
acc else Word
acc)
{-# 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/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 ^%

#ifdef MIN_VERSION_vector

newtype instance U.MVector s (Mod m) = MV_Mod (P.MVector s Word)
newtype instance U.Vector    (Mod m) = V_Mod  (P.Vector    Word)

-- | No validation checks are performed;
-- reading untrusted data may corrupt internal invariants.
instance U.Unbox (Mod m)

-- | No validation checks are performed;
-- reading untrusted data may corrupt internal invariants.
instance 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 :: forall s. MVector s (Mod m) -> Int
basicLength (MV_Mod MVector s Word
v) = forall (v :: * -> * -> *) a s. MVector v a => v s a -> Int
M.basicLength MVector s Word
v
  basicUnsafeSlice :: forall s. Int -> Int -> MVector s (Mod m) -> MVector s (Mod m)
basicUnsafeSlice Int
i Int
n (MV_Mod MVector s Word
v) = forall s (m :: Nat). MVector s Word -> MVector s (Mod m)
MV_Mod forall a b. (a -> b) -> a -> b
$ forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> Int -> v s a -> v s a
M.basicUnsafeSlice Int
i Int
n MVector s Word
v
  basicOverlaps :: forall s. MVector s (Mod m) -> MVector s (Mod m) -> Bool
basicOverlaps (MV_Mod MVector s Word
v1) (MV_Mod MVector s Word
v2) = forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> Bool
M.basicOverlaps MVector s Word
v1 MVector s Word
v2
  basicUnsafeNew :: forall s. Int -> ST s (MVector s (Mod m))
basicUnsafeNew Int
n = forall s (m :: Nat). MVector s Word -> MVector s (Mod m)
MV_Mod forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (v :: * -> * -> *) a s. MVector v a => Int -> ST s (v s a)
M.basicUnsafeNew Int
n
  basicInitialize :: forall s. MVector s (Mod m) -> ST s ()
basicInitialize (MV_Mod MVector s Word
v) = forall (v :: * -> * -> *) a s. MVector v a => v s a -> ST s ()
M.basicInitialize MVector s Word
v
  basicUnsafeReplicate :: forall s. Int -> Mod m -> ST s (MVector s (Mod m))
basicUnsafeReplicate Int
n Mod m
x = forall s (m :: Nat). MVector s Word -> MVector s (Mod m)
MV_Mod forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> a -> ST s (v s a)
M.basicUnsafeReplicate Int
n (forall (m :: Nat). Mod m -> Word
unMod Mod m
x)
  basicUnsafeRead :: forall s. MVector s (Mod m) -> Int -> ST s (Mod m)
basicUnsafeRead (MV_Mod MVector s Word
v) Int
i = forall (m :: Nat). Word -> Mod m
Mod forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> ST s a
M.basicUnsafeRead MVector s Word
v Int
i
  basicUnsafeWrite :: forall s. MVector s (Mod m) -> Int -> Mod m -> ST s ()
basicUnsafeWrite (MV_Mod MVector s Word
v) Int
i Mod m
x = forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> a -> ST s ()
M.basicUnsafeWrite MVector s Word
v Int
i (forall (m :: Nat). Mod m -> Word
unMod Mod m
x)
  basicClear :: forall s. MVector s (Mod m) -> ST s ()
basicClear (MV_Mod MVector s Word
v) = forall (v :: * -> * -> *) a s. MVector v a => v s a -> ST s ()
M.basicClear MVector s Word
v
  basicSet :: forall s. MVector s (Mod m) -> Mod m -> ST s ()
basicSet (MV_Mod MVector s Word
v) Mod m
x = forall (v :: * -> * -> *) a s. MVector v a => v s a -> a -> ST s ()
M.basicSet MVector s Word
v (forall (m :: Nat). Mod m -> Word
unMod Mod m
x)
  basicUnsafeCopy :: forall s. MVector s (Mod m) -> MVector s (Mod m) -> ST s ()
basicUnsafeCopy (MV_Mod MVector s Word
v1) (MV_Mod MVector s Word
v2) = forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> ST s ()
M.basicUnsafeCopy MVector s Word
v1 MVector s Word
v2
  basicUnsafeMove :: forall s. MVector s (Mod m) -> MVector s (Mod m) -> ST s ()
basicUnsafeMove (MV_Mod MVector s Word
v1) (MV_Mod MVector s Word
v2) = forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> ST s ()
M.basicUnsafeMove MVector s Word
v1 MVector s Word
v2
  basicUnsafeGrow :: forall s. MVector s (Mod m) -> Int -> ST s (MVector s (Mod m))
basicUnsafeGrow (MV_Mod MVector s Word
v) Int
n = forall s (m :: Nat). MVector s Word -> MVector s (Mod m)
MV_Mod forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> ST s (v s a)
M.basicUnsafeGrow MVector s Word
v Int
n

-- | No validation checks are performed;
-- reading untrusted data may corrupt internal invariants.
instance G.Vector U.Vector (Mod m) where
  {-# INLINE basicUnsafeFreeze #-}
  {-# INLINE basicUnsafeThaw #-}
  {-# INLINE basicLength #-}
  {-# INLINE basicUnsafeSlice #-}
  {-# INLINE basicUnsafeIndexM #-}
  {-# INLINE elemseq #-}
  basicUnsafeFreeze :: forall s. Mutable Vector s (Mod m) -> ST s (Vector (Mod m))
basicUnsafeFreeze (MV_Mod MVector s Word
v) = forall (m :: Nat). Vector Word -> Vector (Mod m)
V_Mod forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (v :: * -> *) a s. Vector v a => Mutable v s a -> ST s (v a)
G.basicUnsafeFreeze MVector s Word
v
  basicUnsafeThaw :: forall s. Vector (Mod m) -> ST s (Mutable Vector s (Mod m))
basicUnsafeThaw (V_Mod Vector Word
v) = forall s (m :: Nat). MVector s Word -> MVector s (Mod m)
MV_Mod forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (v :: * -> *) a s. Vector v a => v a -> ST s (Mutable v s a)
G.basicUnsafeThaw Vector Word
v
  basicLength :: Vector (Mod m) -> Int
basicLength (V_Mod Vector Word
v) = forall (v :: * -> *) a. Vector v a => v a -> Int
G.basicLength Vector Word
v
  basicUnsafeSlice :: Int -> Int -> Vector (Mod m) -> Vector (Mod m)
basicUnsafeSlice Int
i Int
n (V_Mod Vector Word
v) = forall (m :: Nat). Vector Word -> Vector (Mod m)
V_Mod forall a b. (a -> b) -> a -> b
$ forall (v :: * -> *) a. Vector v a => Int -> Int -> v a -> v a
G.basicUnsafeSlice Int
i Int
n Vector Word
v
  basicUnsafeIndexM :: Vector (Mod m) -> Int -> Box (Mod m)
basicUnsafeIndexM (V_Mod Vector Word
v) Int
i = forall (m :: Nat). Word -> Mod m
Mod forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (v :: * -> *) a. Vector v a => v a -> Int -> Box a
G.basicUnsafeIndexM Vector Word
v Int
i
  basicUnsafeCopy :: forall s. Mutable Vector s (Mod m) -> Vector (Mod m) -> ST s ()
basicUnsafeCopy (MV_Mod MVector s Word
mv) (V_Mod Vector Word
v) = forall (v :: * -> *) a s.
Vector v a =>
Mutable v s a -> v a -> ST s ()
G.basicUnsafeCopy MVector s Word
mv Vector Word
v
  elemseq :: forall b. Vector (Mod m) -> Mod m -> b -> b
elemseq Vector (Mod m)
_ = seq :: forall a b. a -> b -> b
seq

#endif