Prolog "opening_uniform"

Admin User, erstellt 01. Apr. 2024
         
/**
* Warranty & Liability
* To the extent permitted by applicable law and unless explicitly
* otherwise agreed upon, XLOG Technologies AG makes no warranties
* regarding the provided information. XLOG Technologies AG assumes
* no liability that any problems might be solved with the information
* provided by XLOG Technologies AG.
*
* Rights & License
* All industrial property rights regarding the information - copyright
* and patent rights in particular - are the sole property of XLOG
* Technologies AG. If the company was not the originator of some
* excerpts, XLOG Technologies AG has at least obtained the right to
* reproduce, change and translate the information.
*
* Reproduction is restricted to the whole unaltered document. Reproduction
* of the information is only allowed for non-commercial uses. Selling,
* giving away or letting of the execution of the library is prohibited.
* The library can be distributed as part of your applications and libraries
* for execution provided this comment remains unchanged.
*
* Restrictions
* Only to be distributed with programs that add significant and primary
* functionality to the library. Not to be distributed with additional
* software intended to replace any components of the library.
*
* Trademarks
* Jekejeke is a registered trademark of XLOG Technologies AG.
*/
:- ensure_loaded('../example22/problems.p').
:- ensure_loaded('../example22/sudoku_shuffle.p').
:- ensure_loaded(library(lists)).
/**
* opening(N):
* The predicate succeeds in a new problem.
*/
% opening(-Matrice)
opening(N) :-
repeat,
trial(N), !.
% trial(-Matrice)
trial(N) :-
problem(0, M), sudoku(M, [], L), random_label(L), !,
filter(34, M, N), sudoku(N, [], R), \+ (random_label(R), M\==N).
/*******************************************************************/
/* Uniform Reveal */
/*******************************************************************/
% filter(+Integer, +Matrice, -Matrice)
filter(U, M, N) :-
flat(M, L, []),
filter_list(U, L, R),
template(M, N),
flat(N, R, []).
% filter_list(+Integer, +List, -List)
filter_list(0, L, R) :- !,
length(L, N),
length(R, N).
filter_list(U, L, R) :-
length(L, N),
random(K),
I is floor(K*N),
nth0(I, L, X, H),
V is U-1,
filter_list(V, H, J),
nth0(I, R, X, J).
/*******************************************************************/
/* Matrice Helpers */
/*******************************************************************/
% flat(+Matrice, +List, -List)
flat([]) --> [].
flat([H|T]) -->
flat_row(H),
flat(T).
% flat_row(+List, +List, -List)
flat_row([]) --> [].
flat_row([H|T]) -->
[H],
flat_row(T).
% template(+Matrice, -Matrice)
template([], []).
template([X|L], [Y|R]) :-
template_row(X, Y),
template(L, R).
% template_row(+List, -List)
template_row([], []).
template_row([_|L], [_|R]) :-
template_row(L, R).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% Dogelog Player for Java, 1.2.0
% ?- between(1,10,_), time(opening(_)), fail.
% % Zeit 951 ms, GC 0 ms, Lips 7714523, Uhr 01.04.2024 17:08
% % Zeit 102 ms, GC 0 ms, Lips 9019000, Uhr 01.04.2024 17:08
% % Zeit 1942 ms, GC 0 ms, Lips 8324226, Uhr 01.04.2024 17:08
% % Zeit 428 ms, GC 0 ms, Lips 8554420, Uhr 01.04.2024 17:08
% % Zeit 209 ms, GC 0 ms, Lips 8742416, Uhr 01.04.2024 17:08
% % Zeit 660 ms, GC 0 ms, Lips 8472698, Uhr 01.04.2024 17:08
% % Zeit 1463 ms, GC 0 ms, Lips 8340434, Uhr 01.04.2024 17:08
% % Zeit 772 ms, GC 0 ms, Lips 8535177, Uhr 01.04.2024 17:08
% % Zeit 760 ms, GC 0 ms, Lips 8488661, Uhr 01.04.2024 17:08
% % Zeit 320 ms, GC 0 ms, Lips 8552571, Uhr 01.04.2024 17:08
% fail.
% ?- time((between(1,50,_), opening(_), fail; true)).
% % Zeit 68221 ms, GC 0 ms, Lips 8467362, Uhr 01.04.2024 17:11
% true.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
% SWI-Prolog, 9.3.2
% ?- between(1,10,_), time(opening(_)), fail.
% % 2,826,103 inferences, 0.234 CPU in 0.243 seconds (96% CPU, 12058039 Lips)
% % 4,580,161 inferences, 0.391 CPU in 0.379 seconds (103% CPU, 11725212 Lips)
% % 8,634,104 inferences, 0.719 CPU in 0.732 seconds (98% CPU, 12012666 Lips)
% % 3,852,530 inferences, 0.312 CPU in 0.327 seconds (96% CPU, 12328096 Lips)
% % 8,643,479 inferences, 0.734 CPU in 0.734 seconds (100% CPU, 11769844 Lips)
% % 7,343,947 inferences, 0.625 CPU in 0.618 seconds (101% CPU, 11750315 Lips)
% % 6,464,959 inferences, 0.547 CPU in 0.541 seconds (101% CPU, 11821639 Lips)
% % 3,005,421 inferences, 0.250 CPU in 0.249 seconds (100% CPU, 12021684 Lips)
% % 3,884,599 inferences, 0.328 CPU in 0.328 seconds (100% CPU, 11838778 Lips)
% % 10,681,666 inferences, 0.891 CPU in 0.902 seconds (99% CPU, 11993450 Lips)
% false.
% ?- time((between(1,50,_), opening(_), fail; true)).
% % 329,083,860 inferences, 27.672 CPU in 27.662 seconds (100% CPU, 11892359 Lips)
% true.