projetmbc
projetmbc

Reputation: 1452

Starting to solve a nonogram using `clpfd`

In the following code, my predicate constraint_connected_areas_rows breaks the search. What am I doing wrong ?

:- use_module(library(clpfd)).

% ----------------- %
% -- C.P. SOLVER -- %
% ----------------- %

domforentries([]).
domforentries([OneRow | OtherRows]):-
    OneRow ins 0..1,
    domforentries(OtherRows).

constraint_total_rows([], []).
constraint_total_rows(
    [OneRowInfos | OtherRowsInfos],
    [OneRowSol | OtherRowsSol] ):-
    sum(OneRowInfos, #=, NbOfOnes),
    sum(OneRowSol, #=, NbOfOnes),
    constraint_total_rows(OtherRowsInfos, OtherRowsSol).

constraint_connected_areas_rows([], []).
constraint_connected_areas_rows(
    [OneRowInfos | OtherRowsInfos],
    [OneRowSol | OtherRowsSol] ):-
    length(OneRowInfos, NbConnectedAreas_Wanted),
    nbconnectedareas(OneRowSol, NbConnectedAreas_Found, 0),
    NbConnectedAreas_Found #= NbConnectedAreas_Wanted,
    constraint_connected_areas_rows(OtherRowsInfos, OtherRowsSol).

% nbconnectedareas([1, 1, 0, 0, 0, 1], N, 0).
% N = 2
%
% nbconnectedareas([0, 1, 1, 0, 0, 0, 1, 0], N, 0).
% N = 2
%
% nbconnectedareas([1, 0, 1, 0, 0, 1], N, 0).
% N = 3
%
% nbconnectedareas([1, 1, 1, 1, 1, 1], N, 0).
% N = 1
nbconnectedareas([], 0, _):-
    !.
nbconnectedareas([FirstElt | OtherElts], NbConnectedAreas, LastCol):-
    FirstElt = LastCol,
    !,
    nbconnectedareas(OtherElts, NbConnectedAreas, LastCol).
nbconnectedareas([1 | OtherElts], NbConnectedAreas, 0):-
    nbconnectedareas(OtherElts, SubNbConnectedAreas, 1),
    NbConnectedAreas #= SubNbConnectedAreas + 1.
nbconnectedareas([0 | OtherElts], NbConnectedAreas, 1):-
    nbconnectedareas(OtherElts, NbConnectedAreas, 0).

% --------------- %
% -- MAIN PART -- %
% --------------- %

solve(Sol):-
    % Source:
    % https://www.researchgate.net/figure/A-small-Nonogram-and-its-unique-solution_fig2_228862924
    %
    % Grid = [[1, 1, 0, 0, 0, 1],
    %         [0, 1, 0, 1, 1, 1],
    %         [0, 1, 0, 1, 1, 0],
    %         [0, 1, 1, 1, 0, 0],
    %         [0, 1, 1, 1, 1, 0],
    %         [0, 0, 0, 1, 0, 0]]
    ColsInfos = [[1], [5], [2], [5], [2, 1], [2]],
    RowsInfos = [[2, 1], [1, 3], [1, 2], [3], [4], [1]],
% Shape of the solution.
    length(ColsInfos, NbCols),
    length(RowsInfos, NbRows),
% Internal version of the solution.
    same_length(RowsInfos, Grid),
    maplist(same_length(ColsInfos), Grid),
% Constraint on entries.
    domforentries(Grid),
% Constraint on rows.
    constraint_total_rows(RowsInfos, Grid),
    constraint_connected_areas_rows(RowsInfos, Grid),
% Constraint on cols.
    transpose(Grid, Dirg),
    constraint_total_rows(ColsInfos, Dirg),
    constraint_connected_areas_rows(ColsInfos, Dirg),
% Let's the magic plays...
    flatten(Grid, Sol),
    labeling([], Sol),
    print_sol(Sol, NbCols).

% ---------------------------- %
% -- PRINTING FOR DEBUGGING -- %
% ---------------------------- %

print_sol(Sol, NbCols):-
    print_sol(Sol, NbCols, 1).

print_sol([], _, _).
print_sol([OnePixel | OtherPixels], NbCols, NbPrinted):-
    Rem is NbPrinted mod NbCols,
    ((Rem = 1)
        -> writeln("")
        ;
        true
    ),
    write(OnePixel),
    NextNbPrinted is NbPrinted + 1,
    print_sol(OtherPixels, NbCols, NextNbPrinted).

Upvotes: 1

Views: 264

Answers (1)

projetmbc
projetmbc

Reputation: 1452

Thanks to the post of false above, here is the good way to obtain the solutions using a brute force approach which is neither tricky, nor efficient.

  • There is no need to count the total numbers of 1 in each row.
  • The predicate constraint_connected_areas_rows has been removed because it was not complete.
  • The predicate connectedareas has been added to solve the problem.
  • clpfd is just used for its transpose predicate.
% Just us the transpose from clpfd.
:- use_module(library(clpfd)).


% --------------- %
% -- MAIN PART -- %
% --------------- %

solve(Sol):-
    % Source:
    % https://www.researchgate.net/figure/A-small-Nonogram-and-its-unique-solution_fig2_228862924
    %
    % 110001
    % 010111
    % 010110
    % 011100
    % 011110
    % 000100
    %
    % ColsInfos = [[1], [5], [2], [5], [2, 1], [2]],
    % RowsInfos = [[2, 1], [1, 3], [1, 2], [3], [4], [1]],
    %
    % 0110001
    % 0010111
    % 0010110
    % 0011100
    % 0011110
    % 0000100
    %
    ColsInfos = [[0], [1], [5], [2], [5], [2, 1], [2]],
    RowsInfos = [[2, 1], [1, 3], [1, 2], [3], [4], [1]],
% Internal version of the solution.
    same_length(RowsInfos, Grid),
    maplist(same_length(ColsInfos), Grid),
% Constraint on rows.
    constraint_areas_rows(RowsInfos, Grid),
% Constraint on cols.
    transpose(Grid, Dirg),
    constraint_areas_rows(ColsInfos, Dirg),
% Let's the magic plays...
    flatten(Grid, Sol),
% Just print the solution.
    length(ColsInfos, NbCols),
    print_sol(Sol, NbCols).


% ------------ %
% -- SOLVER -- %
% ------------ %

constraint_areas_rows([], []).

constraint_areas_rows(
    [OneRowInfos | OtherRowsInfos],
    [OneRowSol | OtherRowsSol]
):-
    connectedareas(OneRowSol, AreasSizesFound),
    OneRowInfos = AreasSizesFound,
    constraint_areas_rows(OtherRowsInfos, OtherRowsSol).


% connectedareas([1, 1, 0, 0, 0, 1], A).
% A = [2, 1]
%
% connectedareas([0, 1, 1, 0, 0, 0, 1, 0], A).
% A = [2, 1]
%
% connectedareas([1, 0, 1, 0, 0, 1], A).
% A = [1, 1, 1]
%
% connectedareas([1, 1, 1, 1, 1, 1], A).
% A = [6]
%
% connectedareas([0, 0, 0, 0, 0, 0], A).
% A = [0]
connectedareas(Elts, AreasSizes):-
    connectedareas(Elts, AreasSizes, 0).

connectedareas([], [NbOfOnes], NbOfOnes).

connectedareas([], [], NbOfOnes):-
    NbOfOnes = 0.

connectedareas([OneElt | OtherElts], AreasSizes, NbOfOnes):-
    OneElt = 0,
    NbOfOnes = 0,
    connectedareas(OtherElts, AreasSizes, NbOfOnes).

connectedareas([OneElt | OtherElts], [NbOfOnes | SubAreasSizes], NbOfOnes):-
    OneElt = 0,
    NbOfOnes > 0,
    connectedareas(OtherElts, SubAreasSizes, 0).

connectedareas([OneElt | OtherElts], AreasSizes, NbOfOnes):-
    OneElt = 1,
    NextNbOfOnes is NbOfOnes + 1,
    connectedareas(OtherElts, AreasSizes, NextNbOfOnes).


% ---------------------------- %
% -- PRINTING FOR DEBUGGING -- %
% ---------------------------- %

print_sol(Sol, NbCols):-
    print_sol(Sol, NbCols, 1).

print_sol([], _, _).

print_sol([OnePixel | OtherPixels], NbCols, NbPrinted):-
    Rem is NbPrinted mod NbCols,
    ((Rem = 1)
        -> writeln("")
        ;
        true
    ),
    write(OnePixel),
    NextNbPrinted is NbPrinted + 1,
    print_sol(OtherPixels, NbCols, NextNbPrinted).

Upvotes: 2

Related Questions