Prolog - jigoku solver - runtime

I am a complete newbie to Prolog (as in: I only did a Prolog chapter in 7 languages ​​in 7 weeks), so general comments on any of the codes below are very welcome.

First of all: what is jigoku? This is similar to Sudoku, except that you end up with an empty grid, and within each 3x3 block there are inequalities between adjacent slots. An example is here: http://krazydad.com/jigoku/books/KD_Jigoku_CH_8_v18.pdf . You still need to fill the grid so that each row, column and block contains the numbers 1-9.

I tried to implement a solver based on this sudoku solver: http://programmablelife.blogspot.co.uk/2012/07/prolog-sudoku-solver-explained.html . For debugging reasons, I started with a 4x4 example that works very well:

:- use_module(library(clpfd)).

small_jidoku(Rows, RowIneqs, ColIneqs) :-
  Rows = [A,B,C,D], 
  append(Rows, Vs), Vs ins 1..4,
  maplist(all_distinct, Rows),
  transpose(Rows, Columns),     
  maplist(all_distinct, Columns),
  blocks(A, B), blocks(C,D), 
  maplist(label, Rows),
  fake_check_ineqs(Rows, RowIneqs),
  fake_check_ineqs(Columns, ColIneqs),
  pretty_print([A,B,C,D]).      

blocks([], []).       
blocks([A,B|Bs1], [D,E|Bs2]) :-     
  all_distinct([A,B,D,E]),      
  blocks(Bs1, Bs2).

fake_check_ineqs([],[]).
fake_check_ineqs([Head|Tail], [Ineq1|TailIneqs]) :- 
    Head = [A,B,C,D],
    atom_chars(Ineq1, [X1,X2]),
    call(X1, A, B),
    call(X2, C, D),
    fake_check_ineqs(Tail, TailIneqs).

pretty_print([]).
pretty_print([Head | Tail]) :-
 print(Head),
 print('\n'),
 pretty_print(Tail).

      

Then I solve the following example:

time(small_jidoku([[A1,A2,A3,A4],[B1,B2,B3,B4],[C1,C2,C3,C4],[D1,D2,D3,D4]],[><,<>,<<,<<],[><,<<,<>,>>])).

      

This works for about 0.5 seconds. However, I also tried to solve this problem with

time(small_jidoku([A,B,C,D],[><,<>,<<,<<],[><,<<,<>,>>])).

      

and it seems to take a long time. Can someone explain why it takes the solver much longer when I do not specify that each row has 4 elements? My naive answer to this question is that Prolog, if not to say the actual format of my strings, will also try to investigate smaller / larger rows, so wasting time, for example, with 5 strings, but is that really true?

My second question is about the 9x9 version, which is very similar to 4x4, except that the blocks are of course larger and that more tests need to be done to check for inequality. Code below:

:- use_module(library(clpfd)).

jidoku(Rows, RowIneqs, ColIneqs) :-  
  Rows = [A,B,C,D,E,F,G,H,I],   
  append(Rows, Vs), Vs ins 1..9,
  maplist(all_distinct, Rows),
  transpose(Rows, Columns),     
  maplist(all_distinct, Columns),         
  blocks(A, B, C), blocks(D, E, F), blocks(G, H, I),     
  maplist(label, Rows),
  check_ineqs(Rows, RowIneqs),
  check_ineqs(Columns, ColIneqs),
  pretty_print([A,B,C,D,E,F,G,H,I]).      

blocks([], [], []).       
blocks([A,B,C|Bs1], [D,E,F|Bs2], [G,H,I|Bs3]) :-     
  all_distinct([A,B,C,D,E,F,G,H,I]),      
  blocks(Bs1, Bs2, Bs3).

check_ineqs([],[]).
check_ineqs([Head|Tail], [Ineq1|TailIneqs]) :- 
    Head = [A,B,C,D,E,F,G,H,I],
    atom_chars(Ineq1, [X1, X2, X3, X4, X5, X6]),
    call(X1, A, B),
    call(X2, B, C),
    call(X3, D, E),
    call(X4, E, F),
    call(X5, G, H),
    call(X6, H, I),
    check_ineqs(Tail, TailIneqs).

      

Test example:

    time(jidoku([[A1,A2,A3,A4,A5,A6,A7,A8,A9],
        [B1,B2,B3,B4,B5,B6,B7,B8,B9],
        [C1,C2,C3,C4,C5,C6,C7,C8,C9],
        [D1,D2,D3,D4,D5,D6,D7,D8,D9],
        [E1,E2,E3,E4,E5,E6,E7,E8,E9],
        [F1,F2,F3,F4,F5,F6,F7,F8,F9],
        [G1,G2,G3,G4,G5,G6,G7,G8,G9],
        [H1,H2,H3,H4,H5,H6,H7,H8,H9],
        [I1,I2,I3,I4,I5,I6,I7,I8,I9]], 
        [<>>><>,<<<>><,<<<><>,<><<><,>>><><,><>><>,<>>><>,<>><><,><<>>>], 
        [<<<><>,><<>>>,<><<><,><<<>>,><><<<,<><><>,<>>>><,><><><,<>><>>])).

      

and this one was launched overnight without reaching any conclusion and at the moment I don't know what is going on. I expected some scaling problems, but not this proportion!

It would be great if someone who really knows what they are doing can light this up! Thanks already!

+3


source to share


1 answer


Here is the version of your code that I had in mind (other predicates have not changed):

ineqs(Cells, Ineq) :-
        atom_chars(Ineq, Cs),
        maplist(primitive_declarative, Cs, Ds),
        ineqs_(Ds, Cells).

ineqs_([], _).
ineqs_([Op1,Op2|Ops], [A,B,C|Cells]) :-
        call(Op1, A, B),
        call(Op2, B, C),
        ineqs_(Ops, Cells).

primitive_declarative(<, #<).
primitive_declarative(>, #>).

      

Note that general fairness code does not require calling the predicate " check_...

", since the predicate claims to have and can be used in multiple ways: Yes, it can be used to check if constraints are constrained but it can also be used to indicate that constraints must be met for some variables. Therefore, I avoid imperatives and use more declarative names.

You use ineqs/2

in jidoku/3

with: maplist(ineqs, Rows, RowsIneqs)

etc.

Your example and result with a new version using SWI 7.3.2:



?- length(Rows, 9), maplist(same_length(Rows), Rows),
   time(jidoku(Rows,
   [<>>><>,<<<>><,<<<><>,<><<><,>>><><,><>><>,<>>><>,<>><><,><<>>>],
   [<<<><>,><<>>>,<><<><,><<<>>,><><<<,<><><>,<>>>><,><><><,<>><>>])),
   maplist(writeln, Rows).
% 2,745,471 inferences, 0.426 CPU in 0.432 seconds (99% CPU, 6442046 Lips)
[1,5,4,8,7,2,6,9,3]
[2,3,9,1,6,5,7,4,8]
[6,7,8,3,9,4,2,5,1]
[3,4,1,2,5,6,8,7,9]
[9,6,5,7,1,8,3,2,4]
[8,2,7,9,4,3,1,6,5]
[4,9,3,6,2,1,5,8,7]
[7,8,2,5,3,9,4,1,6]
[5,1,6,4,8,7,9,3,2]
Rows = [[1, 5, 4, 8, 7, 2, 6, 9|...], ...].

      

In fact, note that no labeling is required to compute a single solution in this particular case, because the constraint solver is strong enough to bring all domains down to single sets.

In your previous version, all the time was wasted naively generating permutations that were ultimately considered inconsistent. With the new version, the constraint solver has the ability to apply this knowledge earlier.

Therefore, it is recommended to first specify all restrictions and only then call labeling/2

to find specific solutions, as described in the CLP (FD) manual .

+3


source







All Articles