1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 2/* Nan.Numerics.Prime 3 A simple prime number library 4 Copyright 2016 Julio P. Di Egidio 5 <mailto:julio@diegidio.name> 6 <http://julio.diegidio.name/Projects/Nan.Numerics.Prime/> 7 8 This file is part of Nan.Numerics.Prime. 9 10 Nan.Numerics.Prime is free software: you can redistribute it and/or modify 11 it under the terms of the GNU General Public License as published by 12 the Free Software Foundation, either version 3 of the License, or 13 (at your option) any later version. 14 15 Nan.Numerics.Prime is distributed in the hope that it will be useful, 16 but WITHOUT ANY WARRANTY; without even the implied warranty of 17 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the 18 GNU General Public License for more details. 19 20 You should have received a copy of the GNU General Public License 21 along with Nan.Numerics.Prime. If not, see <http://www.gnu.org/licenses/>. 22*/ 23%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 24 25% (SWI-Prolog 7.3.25) 26 27% TODO: Implement test error estimates? 28% TODO: Implement option for num. of iterations? 29 30:- module(prime_prb, []). 31 32:- public 33 test_/2, % +N:posint, -Cert:boolean 34 det_max_/1, % -Max:posint 35 prb_mul_/1. % -Mul:posint
56:- use_module(library(random)). 57 58%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
Cert is true
if N is certainly prime, otherwise it is false
.
66test_(2, true) :- !. 67test_(N, Cert) :- 68 N > 2, 69 test_as_(N, As, Cert), 70 \+ comp_as_(N, As). 71 72test_as_(N, As, true) :- 73 det_as_(N, As), !. 74test_as_(N, As, false) :- 75 prb_as_(N, As). 76 77%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 78 79% comp_as_(+N:posint +As:list(prime)) is semidet. 80 81comp_as_(N, As) :- 82 calc_n0sd_(N, N0, S0, D), 83 comp_as_(As, N0, S0, D). 84 85comp_as_([A| _], N0, S0, D) :- 86 comp_a_(A, N0, S0, D), !. 87comp_as_([_| As], N0, S0, D) :- 88 comp_as_(As, N0, S0, D). 89 90comp_a_(A, N0, S0, D) :- 91 X is powm(A, D, N0 + 1), 92 X =\= 1, X =\= N0, 93 forall( 94 between(1, S0, R), 95 ( D2 is 1 << R, 96 X2 is powm(X, D2, N0 + 1), 97 X2 =\= N0 98 ) 99 ). 100 101calc_n0sd_(N, N0, S0, D) :- 102 N0 is N - 1, 103 calc_n0sd___do(N0, 0, S, D), 104 S0 is S - 1. 105 106calc_n0sd___do(N0, A0, S, D) :- 107 N0 /\ 1 =:= 0, !, 108 N1 is N0 >> 1, 109 A1 is A0 + 1, 110 calc_n0sd___do(N1, A1, S, D). 111calc_n0sd___do(D, S, S, D). 112 113%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
119det_max_(3317044064679887385961980).
125prb_mul_(20). % TODO: Review this. #### 126 127% prb_as_(+N:posint, -As:list(prime)) is semidet. 128 129prb_as_(N, As) :- 130 N2 is N - 2, 131 findall(A, 132 ( between(1, 20/*mul*/, _), 133 random(2, N2, A) 134 ), As). 135 136% det_as_(+N:posint, -As:list(prime)) is semidet. 137 138det_as_(N, As) :- 139 det_sas_(Max, As), N < Max, !. 140 141det_sas_(2047, [2]). 142det_sas_(1373653, [2, 3]). 143det_sas_(25326001, [2, 3, 5]). 144det_sas_(3215031751, [2, 3, 5, 7]). 145det_sas_(2152302898747, [2, 3, 5, 7, 11]). 146det_sas_(3474749660383, [2, 3, 5, 7, 11, 13]). 147det_sas_(341550071728321, [2, 3, 5, 7, 11, 13, 17]). 148det_sas_(3825123056546413051, [2, 3, 5, 7, 11, 13, 17, 19, 23]). 149det_sas_(318665857834031151167461, [2, 3, 5, 7, 11, 13, 17, 19, 23, 29, 31, 37]). 150det_sas_(3317044064679887385961981, [2, 3, 5, 7, 11, 13, 17, 19, 23, 29, 31, 37, 41]). 151 152%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
A simple prime number library :: probabilistic
Module
prime_prb
provides low-level predicates to test candidate primality of numbers based on a probabilistic primality test.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 at20
.NOTE: Predicates in this module are not meant for public use.