This repository has been archived by the owner on Mar 19, 2022. It is now read-only.
-
Notifications
You must be signed in to change notification settings - Fork 0
/
battleship.pl
68 lines (62 loc) · 2.12 KB
/
battleship.pl
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
:- use_module(library(clpfd)).
battleship(Ships, RowCl, ColCl, Rows) :-
same_length(RowCl, Rows), maplist(same_length(ColCl), Rows),
append(Rows, Vs), Vs ins 0..1,
transpose(Rows, Cols),
% row and col ship segment
maplist(sum_eq, Rows, RowCl),
maplist(sum_eq, Cols, ColCl),
% number of ships constraint
sum_eq(Ships, SegC),
length(Ones, SegC), maplist(=(1), Ones),
append(Ones, Ships, ShipsAug),
lines(Rows, RowSh), lines(Cols, ColSh), append(RowSh, ColSh, Sh),
msort(Sh, SortedSh), msort(ShipsAug, SortedSh),
% no adjacent ship
same_length(ZeroR, Cols), maplist(=(0), ZeroR),
append([[ZeroR], Rows, [ZeroR]], TempR),
transpose(TempR, TempC),
same_length(ZeroC, TempR), maplist(=(0), ZeroC),
append([[ZeroC], TempC, [ZeroC]], ColZ),
transpose(ColZ, RowZ),
adjacency(RowZ), adjacency(ColZ).
sum_eq(L, S) :- sum(L, #=, S).
lines([], []).
lines([H|T], C) :- lines(T, Ct), line(H, Ch), append(Ct, Ch, C).
line([], []).
line([1], [1]).
line([0|T], A) :- line(T, A).
line([1,0|T], [1|B]) :- line(T, B).
line([1,1|T], [A|B]) :- line([1|T], [At|B]), A #= At+1.
surrounds([_,_],
[_,_],
[_,_]).
surrounds([_,H11,H12|T1],
[_, 0,H22|T2],
[_,H31,H32|T3]) :- surrounds([H11,H12|T1],
[ 0,H22|T2],
[H31,H32|T3]).
surrounds([0,H1,0|T1],
[0, 1,0|T2],
[0,H3,0|T3]) :- surrounds([H1,0|T1],
[ 1,0|T2],
[H3,0|T3]).
surrounds([0,0,0|T1],
[0,1,1|T2],
[0,0,0|T3]) :- surrounds([0,0|T1],
[1,1|T2],
[0,0|T3]).
surrounds([0,0,0|T1],
[1,1,0|T2],
[0,0,0|T3]) :- surrounds([0,0|T1],
[1,0|T2],
[0,0|T3]).
surrounds([0,0,0|T1],
[1,1,1|T2],
[0,0,0|T3]) :- surrounds([0,0|T1],
[1,1|T2],
[0,0|T3]).
adjacency([_,_]).
adjacency([As,Bs,Cs|T]) :-
surrounds(As, Bs, Cs),
adjacency([Bs,Cs|T]).