Did you know ... Search Documentation:
Pack nan_numerics_prime -- prolog/nan_numerics_prime.pl
PublicShow source

library(nan_numerics_prime)

Module prime provides predicates to test (positive integer) numbers for primality, find divisors and factor numbers, generate prime numbers in some interval, find consecutive prime numbers, and save/load all prime numbers up to some value to/from a file or stream.

All predicates in module prime are safe, i.e. validate input arguments and ensure steadfastness. For maximum performance, user code can directly call the unsafe public (not exported) predicates in module prime_lgc.

Implements a variant of the Miller-Rabin primality test that is deterministic for numbers up to 3317044064679887385961980, otherwise it is probabilistic with the number of iterations fixed at 20.

For better performance, leverages a prime wheel of level 4, i.e. generated by the first 4 consecutive prime numbers, and the memoization of pairs of consecutive prime numbers.

NOTE: Since the primality test in use is probabilistic in general, this module is not suitable for cryptographic applications.

This library was developed and tested with: SWI-Prolog 7.3.25 - http://www.swi-prolog.org/

Usage example:

?- pack_install(nan_numerics_prime).
true.

?- use_module(library(nan_numerics_prime)).
true.

?- time(prime_right(1234567891012345678901234567890123456789011111, P)).
% 1,205 inferences, 0.000 CPU in 0.000 seconds (?% CPU, Infinite Lips)
P = 1234567891012345678901234567890123456789011139.

?- time(prime_lgc:right_(1234567891012345678901234567890123456789011111, P)).
% 1,197 inferences, 0.000 CPU in 0.000 seconds (?% CPU, Infinite Lips)
P = 1234567891012345678901234567890123456789011139.
author
- Julio P. Di Egidio
version
- 1.2.5-beta
license
- GNU GPLv3
To be done
- Implement prime counting/n-th prime functions.
- Implement probabilitic test error estimates?
- Implement deterministic tests (elliptic curves)?
- Implement dynamic wheel with option for level?
- Implement option for num. of probabilistic iterations?
- Improve compatibility with other Prolog systems.
 prime_test(+N:posint) is semidet
True if N is a prime number.

The corresponding unsafe predicate is prime_lgc:test_/1.

 prime_div(+N:posint, -P:prime) is semidet
True if N is a composite number with P its smallest prime divisor.

The corresponding unsafe predicate is prime_lgc:div_/2.

 prime_div_rev(+N:posint, -P:prime) is semidet
True if N is a composite number with P its greatest prime divisor.

The corresponding unsafe predicate is prime_lgc:div_rev_/2.

 prime_fact(+N:posint, -PFs:list(pfact)) is det
PFs is the list of all prime factors of N in ascending order of the prime divisors.

Elements of PFs are of the form P^F with P the prime divisor and F the corresponding power.

If N is equal to 1 or if N is a prime number, PFs is [N^1].

The corresponding unsafe predicate is prime_lgc:fact_/2.

 prime_gen(-P:prime) is multi
 prime_gen(+Inf:posint, -P:prime) is multi
 prime_gen(+Inf:posint, +Sup:posint, -P:prime) is nondet
Generates in ascending order all prime numbers P, greater than or equal to Inf in the variants with arity 2 and 3, and less than or equal to Sup in the variant with arity 3. Fails if the prime to the left of Sup is less than the prime to the right of Inf.

The corresponding unsafe predicates are prime_lgc:gen_/2-3, and prime_lgc:gen_p_/2-3 if the bounds are definitely prime.

 prime_gen_rev(+Sup:posint, -P:prime) is nondet
 prime_gen_rev(+Inf:posint, +Sup:posint, -P:prime) is nondet
Generates in descending order all prime numbers P less than or equal to Sup, and greater than or equal to Inf in the variant with arity 3. Fails if Sup is equal to 1 or if the prime to the left of Sup is less than the prime to the right of Inf.

The corresponding unsafe predicates are prime_lgc:gen_rev_/2-3, and prime_lgc:gen_rev_p_/2-3 if the bounds are definitely prime.

 prime_next(+N:posint, -P:prime) is det
P is the smallest prime number greater than N.

The corresponding unsafe predicates are prime_lgc:next_/2, and prime_lgc:next_p_/2 if N is definitely prime.

 prime_prev(+N:posint, -P:prime) is semidet
P is the greatest prime number less than N. Fails if N is less than or equal to 2.

The corresponding unsafe predicates are prime_lgc:prev_/2, and prime_lgc:prev_p_/2 if N is definitely prime.

 prime_right(+N:posint, -P:prime) is det
P is the smallest prime number greater than or equal to N.

The corresponding unsafe predicate is prime_lgc:right_/2.

 prime_left(+N:posint, -P:prime) is semidet
P is the greatest prime number less than or equal to N. Fails if N is equal to 1.

The corresponding unsafe predicate is prime_lgc:left_/2.

 prime_mem_clear is det
Clears all memoization.
 prime_mem_fill(+Sup:posint) is det
Ensures that all pairs of consecutive prime numbers less than or equal to Sup have been memoized.
 prime_mem_count(-Count:nonneg) is det
Count is the current number of memoized pairs of consecutive prime numbers.
 prime_det_max(-Max:posint) is det
Max is the maximum number for which the primality test is still deterministic.
 prime_prb_mul(-Mul:posint) is det
Mul is the number of iterations for the probabilistic primality test.
 prime_whl_lev(-Lev:posint) is det
Lev is the number of consecutive prime numbers starting from 2 that generate the underlying prime wheel.
 prime_load_file(+File:file) is det
 prime_load_file(+File:file, +Sup:posint) is semidet
Fills the memoization table with the prime numbers read from File, to the end-of-file, or until a prime number greater than Sup is encountered in the variant with arity 2. Fails if Sup is equal to 1.

The accepted file format is a comma-separated list of the consecutive prime numbers starting from 2 and terminated by a period. The file must not be empty.

Encoding of file is ascii, type is text, stream buffer size is 1024.

NOTE: Clears the memoization table before loading.

Errors
- syntax_error(invalid_format) Input format is invalid.
- syntax_error(invalid_start) Input values must start at 2.
- syntax_error(invalid_value) Input values must be posint.
- syntax_error(invalid_consec) Input values must be consecutive primes.
- Errors from open/4.
- Errors from read/2.
To be done
- Improve parse errors?
 prime_save_file(+File:file, +Sup:posint) is semidet
Writes to File all consecutive prime numbers starting from 2 and less than or equal to Sup. Fails if Sup is equal to 1.

The produced file format is a comma-separated list of the consecutive prime numbers starting from 2 and terminated by a period.

Encoding of file is ascii, type is text, buffering is full, stream buffer size is 1024.

Errors
- Errors from open/4.
- Errors from write/2.
 prime_load_stream(+Stream:stream) is det
 prime_load_stream(+Stream:stream, +Sup:posint) is semidet
Fills the memoization table with the prime numbers read from Stream, to the end-of-stream, or until a prime number greater than Sup is encountered in the variant with arity 2. Fails if Sup is equal to 1.

The accepted file format is a comma-separated list of the consecutive prime numbers starting from 2 and terminated by a period. The file must not be empty.

Encoding of stream is ascii, type is text, buffer size is 1024.

NOTE: Clears the memoization table before loading.

Errors
- syntax_error(invalid_format) Input format is invalid.
- syntax_error(invalid_start) Input values must start at 2.
- syntax_error(invalid_value) Input values must be posint.
- syntax_error(invalid_consec) Input values must be consecutive.
- Errors from read/2.
To be done
- Improve parse errors?
 prime_save_stream(+Stream:stream, +Sup:posint) is semidet
Writes to Stream all consecutive prime numbers starting from 2 and less than or equal to Sup. Fails if Sup is equal to 1.

The produced file format is a comma-separated list of the consecutive prime numbers starting from 2 and terminated by a period.

Encoding of stream is ascii, type is text, buffering is full, buffer size is 1024.

Errors
- Errors from write/2.
 error:has_type(+Type:atom, @Term:any) is semidet[multifile]
True if Term satisfies Type.

Extends library(error) with the following types:

primePrime number
pfactP^F with P prime and F posint
filefname or fpipe
fnametext
fpipeatom or string
streamStream identifier
posintpositive_integer
arith(Type)Arithmetic expr. that evaluates to Type
var(Type)var or Type
or(Type1, Type2)Type1 or Type2
See also
- library(error)

Undocumented predicates

The following predicates are exported, but not or incorrectly documented.

 prime_gen(Arg1, Arg2)
 prime_gen(Arg1, Arg2, Arg3)
 prime_gen_rev(Arg1, Arg2, Arg3)
 prime_load_file(Arg1, Arg2)
 prime_load_stream(Arg1, Arg2)