arithmoi-0.5.0.1: Efficient basic number-theoretic functions.

Copyright(c) 2011 Daniel Fischer
LicenseMIT
MaintainerDaniel Fischer <daniel.is.fischer@googlemail.com>
StabilityProvisional
PortabilityNon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Math.NumberTheory.Moduli

Contents

Description

Miscellaneous functions related to modular arithmetic.

Synopsis

Functions with input check

jacobi :: (Integral a, Bits a) => a -> a -> Int Source #

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 Integer Source #

Invert a number relative to a positive modulus. If number and modulus are coprime, the result is Just inverse where

   (number * inverse) `mod` modulus == 1
   0 <= inverse < modulus

If number mod modulus == 0 or gcd number modulus > 1, the result is Nothing.

powerMod :: (Integral a, Bits a) => Integer -> a -> Integer -> Integer Source #

Modular power.

powerMod base exponent modulus

calculates (base ^ exponent) `mod` modulus by repeated squaring and reduction. Modulus must be positive. 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.

powerModInteger :: Integer -> Integer -> Integer -> Integer Source #

Specialised version of powerMod for Integer exponents. Reduces the number of shifts of the exponent since shifting large Integers is expensive. Call this function directly if you don't want or can't rely on rewrite rules. Modulus must be positive.

chineseRemainder :: [(Integer, Integer)] -> Maybe Integer Source #

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 positive and pairwise coprime. Otherwise the result is Nothing regardless of whether a solution exists.

Partially checked input

sqrtModP :: Integer -> Integer -> Maybe Integer Source #

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 -> Int Source #

Jacobi symbol of two numbers without validity check of the "denominator".

powerMod' :: (Integral a, Bits a) => Integer -> a -> Integer -> Integer Source #

Modular power worker without input checking. Assumes all arguments strictly positive and modulus greater than 1.

powerModInteger' :: Integer -> Integer -> Integer -> Integer Source #

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 -> Integer Source #

sqrtModP' square prime finds a square root of square modulo prime. prime must be a (positive) prime, and square must be a positive quadratic residue modulo prime, i.e. 'jacobi square prime == 1. The precondition is not checked.

tonelliShanks :: Integer -> Integer -> Integer Source #

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 positive quadratic residue modulo prime, using the Tonelli-Shanks algorithm. No checks on the input are performed.

sqrtModPP :: Integer -> (Integer, Int) -> Maybe Integer Source #

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 Integer Source #

sqrtModF n primePowers calculates a square root of n modulo product [p^k | (p,k) <- primePowers] if one exists and all primes are distinct. The list must be non-empty, n must be coprime with all primes.

sqrtModFList :: Integer -> [(Integer, Int)] -> [Integer] Source #

sqrtModFList n primePowers calculates all square roots of n modulo product [p^k | (p,k) <- primePowers] if all primes are distinct. The list must be non-empty, n must be coprime with all primes.

chineseRemainder2 :: (Integer, Integer) -> (Integer, Integer) -> Integer Source #

chineseRemainder2 (r_1,m_1) (r_2,m_2) calculates the solution of

r ≡ r_k (mod m_k)

if m_1 and m_2 are coprime.