Search code examples
prologruntimesudokuclpfd

Prolog - jigoku solver - run time


I'm a total newbie to Prolog (as in: I've only done the Prolog chapter in 7 languages in 7 weeks), so general comments to any of the code below are very welcome.

First of all: What is a jigoku? It's like a sudoku, except that you get an empty grid, and within each 3x3 block, inequalities between adjacent slots are given. Example here: http://krazydad.com/jigoku/books/KD_Jigoku_CH_8_v18.pdf. You still need to fill up the grid such that each row, column and block contains the numbers 1-9.

I've 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 really 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).

I then solve the following example:

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

This runs in about 0.5 seconds tops. However, I've also tried to solve it with

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

and this seems to take ages. Can anyone explain why it takes the solver much longer when I don't specify that each row has 4 elements? My naive answer to this is that Prolog, if not told the actual format of my rows, will also try to explore smaller/bigger rows, hence wasting time on e.g. rows of length 5, but is this actually true?

My second question is about the 9x9 version, that is very much like the 4x4 except that the blocks are of course bigger and that there is more testing to be done when checking inequalities. The code is 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).

The 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 has been running overnight without reaching any conclusion and at this point, I have no clue whatsoever what is going wrong. I expected some scaling issues, but not of this proportion!

It would be great if someone who actually knows what they're doing could shine a light on this! Thanks already!


Solution

  • Here is the version of your code I had in mind (other predicates kept unchanged):

    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(>, #>).
    

    Notice that it does not do the generality of the code justice to call the predicate "check_...", because the predicate states what holds and can be used in several directions: Yes, it can be used to check if the constraints hold, but it can also be used to state that the constraints must hold for some variables. I therefore avoid imperatives and use more declarative names.

    You use ineqs/2 in jidoku/3 with: maplist(ineqs, Rows, RowsIneqs) etc.

    Your example and the result with the 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 at all is required to compute the unique solution in this particular case, because the constraint solver is strong enough to reduce all domains to singleton sets.

    In your previous version, all the time was needlessly wasted naively generating permutations that were eventually seen to be inconsistent. With the new version, the constraint solver has a chance to apply this knowledge earlier.

    It is therefore recommended to first state all constraints, and only then to invoke labeling/2 to search for concrete solutions, as explained in the CLP(FD) manual.