Module Euler.Modular

Modular arithmetic.

This module defines modular arithmetic operations, that is, operations on elements of the ring ℤ∕mℤ where m is a positive integer, called the modulus. All operations take m as a named parameter ~modulo. Elements of ℤ∕mℤ are represented by their canonical representatives between 0 and m−1 (included), of type int. All functions may assume that the modulus is positive and that canonical representatives are used, and may raise Assert_failure if that is not the case.

The modulus can also be set globally, and not repeated for each individual operation, by giving it as a parameter to the functor Make. This provides unary and binary operators.

val opp : modulo:int -> int -> int

Modular opposite. opp ~modulo:m a is the unique element a' of ℤ∕mℤ such that a'+a = 0.

val inv : modulo:int -> int -> int

Modular inverse. inv ~modulo:m a is the unique element a' of ℤ∕mℤ such that a'×a = 1, if it exists. Complexity: 𝒪(log(a)) = 𝒪(log(m)) (a being under canonical form).

  • raises Division_by_zero

    when a is not invertible.

val add : modulo:int -> int -> int -> int

Modular addition.

val sub : modulo:int -> int -> int -> int

Modular subtraction.

val mul : modulo:int -> int -> int -> int

Modular multiplication. Complexity: 𝒪(log(min(a,b))) = 𝒪(log(m)) (a and b being under canonical forms).

val div : modulo:int -> int -> int -> int

Modular division. div ~modulo:m a b is the unique element c of ℤ∕mℤ such that c×b = a, if it exists. Complexity: 𝒪(log(b)) = 𝒪(log(m)) (b being under canonical form).

  • raises Division_by_zero

    when b is not invertible.

val div_nonunique : modulo:int -> int -> int -> int

A more general modular division, which does not assume its right operand to be invertible. div_nonunique ~modulo:m a b is an element c such that c×b = a, if there exists one. There exists such an element iff a is a multiple of gcd(m, b), in which case the result is defined modulo m ∕ gcd(m, b); it is unique only when b is invertible. For example, modulo 10, 3×4 = 8×4 = 2, so 2 divided by 4 may be 3 or 8 (this example shows that the division 2 ∕ 4 cannot be simplified to 1 ∕ 2). Complexity: 𝒪(log(b)) = 𝒪(log(m)) (b being under canonical form).

  • raises Division_by_zero

    when there is no such element.

exception Factor_found of int
val inv_factorize : modulo:int -> int -> int

A version of the modular inverse specialized for factorization purposes. inv_factorize ~modulo:m a is similar to inv ~modulo:m a but handles more precisely the cases when a is not invertible. Complexity: 𝒪(log(a)) = 𝒪(log(m)) (a being under canonical form).

  • raises Division_by_zero

    when a is zero.

  • raises Factor_found

    when a is non‐zero and not invertible; in this case, gcd(m,a) is a non‐trivial factor of m, which is returned as the parameter of the exception Factor_found.

val pow : modulo:int -> int -> int -> int

Modular exponentiation. When n is non‐negative, pow ~modulo:m a n is an in the ring ℤ∕mℤ; when n is negative, it is a'n where a' is the modular inverse of a. Complexity: 𝒪(log(m)×log(|n|)).

  • raises Division_by_zero

    when n is negative and a is not invertible.

val rand : modulo:int -> unit -> int

rand ~modulo:m () draws a random element of the ring ℤ∕mℤ, with the uniform distribution.

Functorial interface

module Make (_ : sig ... end) : sig ... end

The functor application Make (M) defines modular arithmetic operations with a fixed, non‐zero modulus M.modulo. Because the modulus needs not be repeated for each individual operation, meaningful unary and binary operators can be defined. Operations in the resulting module follow the same specifications as those in module Modular, with respect to return values, exceptions raised, and time costs.