Chernick's Carmichael numbers: Difference between revisions

m (Formatting.)
Line 1,056:
</pre>
 
=={{header|Prolog}}==
SWI Prolog is too slow to solve for a(10), even with optimizing by increasing the multiplier and implementing a trial division check. (actually, my implementation of Miller-Rabin in Prolog already starts with a trial division by small primes.)
<lang Prolog>
?- use_module(library(primality)).
 
u(3, M, A * B * C) :-
A is 6*M + 1, B is 12*M + 1, C is 18*M + 1, !.
u(N, M, U0 * D) :-
succ(Pn, N), u(Pn, M, U0),
D is 9*(1 << (N - 2))*M + 1.
 
prime_factorization(A*B) :- prime(B), prime_factorization(A), !.
prime_factorization(A) :- prime(A).
 
step(N, 1) :- N < 5, !.
step(5, 2) :- !.
step(N, K) :- K is 5*(1 << (N - 4)).
 
a(N, Factors) :- % due to backtracking nature of Prolog, a(n) will return all chernick-carmichael numbers.
N > 2, !,
step(N, I),
between(1, infinite, J), M is I * J,
u(N, M, Factors),
prime_factorization(Factors).
 
main :-
forall(
(between(3, 9, K), once(a(K, Factorization)), N is Factorization),
format("~w: ~w = ~w~n", [K, Factorization, N])),
halt.
 
?- main.
</lang>
isprime predicate:
<lang Prolog>
prime(N) :-
integer(N),
N > 1,
divcheck(
N,
[ 2, 3, 5, 7, 11, 13, 17, 19, 23, 29, 31,
37, 41, 43, 47, 53, 59, 61, 67, 71, 73, 79,
83, 89, 97, 101, 103, 107, 109, 113, 127, 131, 137,
139, 149],
Result),
((Result = prime, !); miller_rabin_primality_test(N)).
 
divcheck(_, [], unknown) :- !.
divcheck(N, [P|_], prime) :- P*P > N, !.
divcheck(N, [P|Ps], State) :- N mod P =\= 0, divcheck(N, Ps, State).
 
miller_rabin_primality_test(N) :-
bases(Bases, N),
forall(member(A, Bases), strong_fermat_pseudoprime(N, A)).
 
miller_rabin_precision(16).
 
bases([31, 73], N) :- N < 9_080_191, !.
bases([2, 7, 61], N) :- N < 4_759_123_141, !.
bases([2, 325, 9_375, 28_178, 450_775, 9_780_504, 1_795_265_022], N) :-
N < 18_446_744_073_709_551_616, !. % 2^64
bases(Bases, N) :-
miller_rabin_precision(T), RndLimit is N - 2,
length(Bases, T), maplist(random_between(2, RndLimit), Bases).
 
strong_fermat_pseudoprime(N, A) :- % miller-rabin strong pseudoprime test with base A.
succ(Pn, N), factor_2s(Pn, S, D),
X is powm(A, D, N),
((X =:= 1, !); \+ composite_witness(N, S, X)).
 
composite_witness(_, 0, _) :- !.
composite_witness(N, K, X) :-
X =\= N-1,
succ(Pk, K), X2 is (X*X) mod N, composite_witness(N, Pk, X2).
 
factor_2s(N, S, D) :- factor_2s(0, N, S, D).
factor_2s(S, D, S, D) :- D /\ 1 =\= 0, !.
factor_2s(S0, D0, S, D) :-
succ(S0, S1), D1 is D0 >> 1,
factor_2s(S1, D1, S, D).
</lang>
{{Out}}
<pre>
3: 7*13*19 = 1729
4: 7*13*19*37 = 63973
5: 2281*4561*6841*13681*27361 = 26641259752490421121
6: 2281*4561*6841*13681*27361*54721 = 1457836374916028334162241
7: 4681921*9363841*14045761*28091521*56183041*112366081*224732161 = 24541683183872873851606952966798288052977151461406721
8: 5703361*11406721*17110081*34220161*68440321*136880641*273761281*547522561 = 53487697914261966820654105730041031613370337776541835775672321
9: 5703361*11406721*17110081*34220161*68440321*136880641*273761281*547522561*1095045121 = 58571442634534443082821160508299574798027946748324125518533225605795841
</pre>
=={{header|Raku}}==
(formerly Perl 6)
357

edits