Advertisement
Moortiii

Neighbors - CLPFD Revised

Nov 16th, 2019
486
0
Never
Not a member of Pastebin yet? Sign Up, it unlocks many cool features!
Prolog 5.38 KB | None | 0 0
  1. outputFile('./neighbours_solved.txt').
  2. inputFile('./neighbours_unsolved.txt').
  3.  
  4. /********************* dummy solution algorithms -> fill your correct algorithm here */
  5. :- use_module(library(clpfd)).
  6.  
  7. valid_neighbors([_]).
  8.  
  9. % If two numbers are neighbors, they must be within +1 of each other
  10. valid_neighbors([A, N, B|T]):-
  11.     N #= 1,
  12.     abs(A-B) #= 1, A #\= B,
  13.     valid_neighbors([B|T]).
  14.  
  15. % If two numbers are not neighbors, they cannot be within +1 of each other
  16. valid_neighbors([A, N, B|T]):-
  17.     N #= 0,
  18.     abs(A-B) #\= 1, A #\= B,
  19.     valid_neighbors([B|T]).
  20.  
  21. valid_numbers(Size, [H]):-
  22.   H in 1..Size.
  23.  
  24. valid_numbers(Size, [H, _|T]):-
  25.   H in 1..Size,
  26.   valid_numbers(Size, T).
  27.  
  28. % Remove every other element of a list.
  29. r([], []).
  30. r([X], [X]).
  31. r([X,_|Xs], [X|Ys]):- r(Xs, Ys).
  32.  
  33. % Use constraint propagation in order to create / solve boards
  34. % Inspired by the techniques used at https://www.swi-prolog.org/pldoc/man?section=clpfd-sudoku
  35. solve(Size, Grid):-
  36.   % A board with size 4 needs three extra lines for the neighbor rows.
  37.   % A board of size N needs N * 2 - 1 lines to accommodate for the neighbor rows.
  38.   N #= Size * 2 - 1, length(Grid, N),
  39.   maplist(same_length(Grid), Grid),
  40.  
  41.   % Remove the neighbor rows so that we can write the solution easily
  42.   removeNeighbours(Grid, Solution),
  43.  
  44.   % Transpose the grid in order to apply the same rules to the columns
  45.   transpose(Grid, Transposed),
  46.  
  47.   % Every other line of the grid is a value row
  48.   removeNeighbourLine(Grid, VRows),
  49.  
  50.   % The rules of the neighbor relations need to be upheld for the rows
  51.   maplist(valid_neighbors, VRows),
  52.  
  53.   % Every other element of the value rows are values
  54.   maplist(r, VRows, RowValues),
  55.  
  56.   % Each value can only appear once on every row
  57.   maplist(all_distinct, RowValues),
  58.  
  59.   % Ensure all numbers on a line are valid.
  60.   maplist(valid_numbers(Size), VRows),
  61.  
  62.   % Every other row of the columns is a value column
  63.   removeNeighbourLine(Transposed, VColumns),
  64.  
  65.   % The rules of the neighbor relations need to be upheld for the columns
  66.   maplist(valid_neighbors, VColumns),
  67.  
  68.   % Ensure all numbers on a line are valid.
  69.   maplist(valid_numbers(Size), VColumns),
  70.  
  71.   % Every other element of a value column is a value
  72.   maplist(r, VColumns, Columns),
  73.  
  74.   % Each value can only appear once on every column
  75.   maplist(all_distinct, Columns),
  76.  
  77.   % Assign a value from the available ones to each element of the rows
  78.   maplist(label, Solution).
  79.  
  80. doSolve(neighbours(size(Size),grid(Problem)),neighbours(size(Size),grid(Solution))):-
  81.   solve(Size, Problem),
  82.   removeNeighbours(Problem, Solution).
  83.  
  84. removeNeighbours([P],[S]):- removeNeighbourLine(P,S).
  85. removeNeighbours([P,_|PT],[S|ST]):- removeNeighbourLine(P,S), removeNeighbours(PT,ST).
  86.  
  87. removeNeighbourLine([P],[P]).
  88. removeNeighbourLine([P,_|PT],[P|ST]):- removeNeighbourLine(PT,ST).
  89.  
  90. /********************* writing the result */
  91. writeFullOutput(neighbours(size(N),grid(Grid))):-
  92.   write('size '), write(N), write('x'), write(N), nl, writeGrid(Grid).
  93.  
  94. writeGrid([]).
  95. writeGrid([E|R]):- writeGridLine(E), writeGrid(R).
  96.  
  97. writeGridLine([]):- nl.
  98. writeGridLine([E|R]):- E=0, !, write(E), write(' '), writeGridLine(R).
  99. writeGridLine([E|R]):- write(E), write(' '), writeGridLine(R).
  100.  
  101. /********************** reading the input */
  102. readProblem(neighbours(size(N),grid(Grid))):-
  103.   findKW(size), readInt(N), readInt(M), M=N, GridLength is N*2-1, length(Grid,GridLength),
  104.   readGridLines(GridLength,Grid).
  105.  
  106. findKW(KW):- string_codes(KW,[H|T]), peek_code(H), readKW([H|T]), !.
  107. findKW(_):- peek_code(-1), !, fail.
  108. findKW(KW):- get_code(_), findKW(KW).
  109.  
  110. readKW([]):- get_code(_).
  111. readKW([H|T]):- get_code(H), readKW(T).
  112.  
  113. readGridLines(N,[A]):- length(A,N), readGridLine(A).
  114. readGridLines(N,[A,B|T]):- length(A,N), readGridLine(A), length(B,N), readNeighborLine(B), readGridLines(N,T).
  115.  
  116. readGridLine([N]):- readInt(I), makeHint(I,N).
  117. readGridLine([N,X|T]):- readInt(I), makeHint(I,N), get_code(M), translate(M,X), !, readGridLine(T).
  118.  
  119. readNeighborLine([X]):- get_code(M), translate(M,X), !.
  120. readNeighborLine([X,o|T]):- get_code(M), translate(M,X), get_code(_), get_code(_), get_code(_), !, readNeighborLine(T).
  121.  
  122. makeHint(X,X):- X>0.
  123. makeHint(0,_).
  124.  
  125. translate(-1,'ERROR: EOF').
  126. translate(120,1).
  127. translate(32,0).
  128. translate(X,X).
  129. translate(X,E):- whitespace(X), get_code(Y), translate(Y,E).
  130. translate(X,E):- string_codes(E,[X]).
  131.  
  132. whitespace(10). whitespace(12). whitespace(32).
  133.  
  134. readInt(N):- get_code(M), handleCode(M,N).
  135.  
  136. handleCode(M,N):- is_number_code(M,N1), !, continueInt(N1,N).
  137. handleCode(-1,_):- !, fail. /* EOF */
  138. handleCode(_,N):- readInt(N).
  139.  
  140. continueInt(O,N):- get_code(M), is_number_code(M,M1), !, H is 10*O+M1, continueInt(H,N).
  141. continueInt(N,N).
  142.  
  143. is_number_code(N, N1):- N>=48, N<58, N1 is N-48.
  144. is_number_code(95,0).
  145.  
  146. /*********************** global control: starting the algorithm and the reading */
  147. run:- inputFile(IF), see(IF), outputFile(F), tell(F), findKW(puzzles), readInt(N),  write('puzzles '), write(N), nl, statistics(walltime, [_ | [_]]), solveProblems(N), told, seen,  statistics(walltime, [_ | [ExecutionTime]]),
  148.   write('Total execution took '), write(ExecutionTime), write(' ms.'), nl, !.
  149. run:- told, seen. /* close the files */
  150.  
  151. solveProblems(0).
  152. solveProblems(N):- N>0, readProblem(P), doSolve(P, S), writeFullOutput(S), !, N1 is N-1, solveProblems(N1).
  153.  
  154. :- nl,nl,write(' try running "?- run."'), nl,nl,nl.
Advertisement
Add Comment
Please, Sign In to add comment
Advertisement