Module Euler.Primes

Prime numbers and integer factorization.

type factorization = (int * int) list

The type of the factorized form of an integer. The factorization of n is a list [ (p1, k1) ; … ; (pℓ, kℓ) ] such that n = p1k1 × … × pℓkℓ and p1 < … < pℓ are prime.

Prime number count

The number π(x) of prime numbers less than x is asymptotically equivalent to x ∕ ln(x). It is also equivalent to li(x), where li is the logarithmic integral function, which gives a much more precise estimation.

val li : ?precision:float -> float -> float

The logarithmic integral function. It is defined only for numbers (strictly) greater than 1.0.

  • parameter precision

    The series summation stops as soon as the increment becomes smaller than precision.

val overestimate_number_of_primes : int -> int

overestimate_number_of_primes nmax gives a relatively precise upper bound on the number of prime numbers below nmax.

First prime numbers

val primes_under_100 : int array

The twenty‐five prime numbers less than 100, in ascending order.

val primes_under_10_000 : int array

The prime numbers less than 10 000, in ascending order.

val primes : int -> do_prime:(int -> unit) -> unit

primes nmax ~do_prime:f calls f on all prime numbers in ascending order from 2 to slightly more than nmax, as soon as they are found. This is useful to iterate on prime numbers and stop when some condition is met. Complexity: time 𝒪(nmax×log(log(nmax))), space 𝒪(π(√nmax)) = 𝒪(√nmax ∕ log(nmax)).

val prime_seq : int -> int Stdlib.Seq.t

The sequence of prime numbers up to a specified bound. This is significantly slower than primes (about 50 times slower for nmax = 1_000_000_000), but has the advantage that advancing through the sequence is controlled by the consumer, This is a purely functional algorithm, hence the produced sequence is persistent. Complexity: time 𝒪(nmax×log(nmax)×log(log(nmax))), space 𝒪(√nmax ∕ log(nmax)).

val factorizing_sieve : int -> do_factors:(factorization -> int -> unit) -> factorization array

Extended prime sieve. factorizing_sieve nmax ~do_factors:f computes the factorization of all numbers up to nmax (included). The result is an array s such that s.(n) is the factorization of n. The function also calls f on the factorization of each number from 2 to nmax, in order. This is useful to iterate on the factorized form of (small) numbers and stop when some condition is met. Note that this is costly both in time and in space, so nmax is bridled with an internal upper bound. Complexity: time 𝒪(nmax×log(log(nmax))), space 𝒪(nmax×log(log(nmax))).

Primality testing

val is_prime : int -> bool

Primality test. is_prime n is true if and only if n is a prime number. Note that this is a deterministic test. Complexity: 𝒪(fast).

Integer factorization

val factors : ?tries:int -> ?max_fact:int -> int -> factorization

Integer factorization. This uses Lenstra’s elliptic‐curve algorithm for finding factors (as of 2018, it is the most efficient known algorithm for 64‐bit numbers). Complexity: 𝒪(terrible).

  • parameter tries

    The number of elliptic curves to try before resigning.

  • parameter max_fact

    The “small exponents” tried by Lenstra’s algorithm are the factorial numbers up to the factorial of max_fact.

  • returns

    the prime factorization of the given number. It may contain non‐prime factors d, if their factorization failed within the allowed time; this is signaled by negating their value, as in (−d, 1). This is highly unlikely with default parameters.

  • raises Assert_failure

    when the number to factorize is not positive.

Usual functions

Some functions defined in this section can be computed efficiently when the factorization of their argument is known. Hence they take an optional argument ?factors which is expected to be the factorization of their main argument. If absent, those functions resort to computing the factorization themselves, or another inefficient algorithm.

val eulerphi : ?factors:factorization -> int -> int

Euler’s totient function. eulerphi n, often noted φ(n), is the number of integers between 1 and n which are coprime with n, provided that n is positive.

val eulerphi_from_file : int -> int array

eulerphi_from_file nmax loads precomputed values of φ from a file on disk.

  • returns

    an array phi such that phi.(n) = φ(n) for all 1 ≤ nnmax.

val number_of_divisors : ?factors:factorization -> int -> int

number_of_divisors n is the number of divisors of n (including 1 and n itself), provided that n is positive.

val divisors : ?factors:factorization -> int -> int list

divisors n is the list of all divisors of n (including 1 and n itself) in ascending order, provided that n is positive.

val gen_divisor_pairs : ?factors:factorization -> int -> (int * int) Stdlib.Seq.t

gen_divisor_pairs n returns all pairs (d, n/d) where d divides n and 1 ≤ d ≤ √n, provided that n is positive. Pairs are presented in ascending order of d. When n is a perfect square, the pair (√n, √n) is presented only once.