Portability | Non-portable (GHC extensions) |
---|---|
Stability | Provisional |
Maintainer | Daniel Fischer <daniel.is.fischer@googlemail.com> |
Safe Haskell | None |
Miscellaneous functions related to modular arithmetic.
- jacobi :: (Integral a, Bits a) => a -> a -> Int
- invertMod :: Integer -> Integer -> Maybe Integer
- powerMod :: (Integral a, Bits a) => Integer -> a -> Integer -> Integer
- powerModInteger :: Integer -> Integer -> Integer -> Integer
- chineseRemainder :: [(Integer, Integer)] -> Maybe Integer
- sqrtModP :: Integer -> Integer -> Maybe Integer
- jacobi' :: (Integral a, Bits a) => a -> a -> Int
- powerMod' :: (Integral a, Bits a) => Integer -> a -> Integer -> Integer
- powerModInteger' :: Integer -> Integer -> Integer -> Integer
- sqrtModPList :: Integer -> Integer -> [Integer]
- sqrtModP' :: Integer -> Integer -> Integer
- tonelliShanks :: Integer -> Integer -> Integer
- sqrtModPP :: Integer -> (Integer, Int) -> Maybe Integer
- sqrtModPPList :: Integer -> (Integer, Int) -> [Integer]
- sqrtModF :: Integer -> [(Integer, Int)] -> Maybe Integer
- sqrtModFList :: Integer -> [(Integer, Int)] -> [Integer]
- chineseRemainder2 :: (Integer, Integer) -> (Integer, Integer) -> Integer
Functions with input check
jacobi :: (Integral a, Bits a) => a -> a -> IntSource
Jacobi symbol of two numbers. The "denominator" must be odd and positive, this condition is checked.
If both numbers have a common prime factor, the result
is 0
, otherwise it is ±1.
invertMod :: Integer -> Integer -> Maybe IntegerSource
Invert a number relative to a modulus.
If number
and modulus
are coprime, the result is
Just inverse
where
(number * inverse) `mod` (abs modulus) == 1 0 <= inverse < abs modulus
unless modulus == 0
and abs number == 1
, in which case the
result is Just number
.
If gcd number modulus > 1
, the result is Nothing
.
powerMod :: (Integral a, Bits a) => Integer -> a -> Integer -> IntegerSource
Modular power.
powerMod base exponent modulus
calculates (base ^ exponent) `mod` modulus
by repeated squaring and reduction.
If exponent < 0
and base
is invertible modulo modulus
, (inverse ^ |exponent|) `mod` modulus
is calculated. This function does some input checking and sanitation before calling the unsafe worker.
chineseRemainder :: [(Integer, Integer)] -> Maybe IntegerSource
Given a list [(r_1,m_1), ..., (r_n,m_n)]
of (residue,modulus)
pairs, chineseRemainder
calculates the solution to the simultaneous
congruences
r ≡ r_k (mod m_k)
if all moduli are pairwise coprime. If not all moduli are
pairwise coprime, the result is Nothing
regardless of whether
a solution exists.
Partially checked input
sqrtModP :: Integer -> Integer -> Maybe IntegerSource
sqrtModP n prime
calculates a modular square root of n
modulo prime
if that exists. The second argument must be a (positive) prime, otherwise
the computation may not terminate and if it does, may yield a wrong result.
The precondition is not checked.
If prime
is a prime and n
a quadratic residue modulo prime
, the result
is Just r
where r^2 ≡ n (mod prime)
, if n
is a quadratic nonresidue,
the result is Nothing
.
Unchecked functions
jacobi' :: (Integral a, Bits a) => a -> a -> IntSource
Jacobi symbol of two numbers without validity check of the "denominator".
powerMod' :: (Integral a, Bits a) => Integer -> a -> Integer -> IntegerSource
Modular power worker without input checking. Assumes all arguments strictly positive and modulus greater than 1.
powerModInteger' :: Integer -> Integer -> Integer -> IntegerSource
Specialised worker without input checks. Makes the same assumptions
as the general version powerMod'
.
sqrtModPList :: Integer -> Integer -> [Integer]Source
sqrtModPList n prime
computes the list of all square roots of n
modulo prime
. prime
must be a (positive) prime.
The precondition is not checked.
sqrtModP' :: Integer -> Integer -> IntegerSource
sqrtModP' square prime
finds a square root of square
modulo
prime. prime
must be a (positive) prime, and sqaure
must be a
quadratic residue modulo prime
, i.e. 'jacobi square prime == 1
.
The precondition is not checked.
tonelliShanks :: Integer -> Integer -> IntegerSource
tonelliShanks square prime
calculates a square root of square
modulo prime
, where prime
is a prime of the form 4*k + 1
and
square
is a quadratic residue modulo prime
, using the
Tonelli-Shanks algorithm.
No checks on the input are performed.
sqrtModPP :: Integer -> (Integer, Int) -> Maybe IntegerSource
sqrtModPP n (prime,expo)
calculates a square root of n
modulo prime^expo
if one exists. prime
must be a
(positive) prime. expo
must be positive, n
must be coprime
to prime
sqrtModPPList :: Integer -> (Integer, Int) -> [Integer]Source
sqrtModPPList n (prime,expo)
calculates the list of all
square roots of n
modulo prime^expo
. The same restriction
as in sqrtModPP
applies to the arguments.
sqrtModF :: Integer -> [(Integer, Int)] -> Maybe IntegerSource
sqrtModF n primePowers
calculates a square root of n
modulo
product [p^k | (p,k) <- primePowers]
if one exists and all primes
are distinct.