This commit is contained in:
Dory 2023-12-25 02:26:26 -08:00
parent 69e2bc3b20
commit b8c59949e9

View File

@ -1,36 +1,75 @@
:- use_module(library(pio)).
:- use_module(library(dcg/basics)).
:- initialization(main, main).
:- table neighbor/3.
:- op(700, xfx, is_key_of).
main([FileName|_]) :-
input(FileName, Map),
nth1(1, Map, Row1), nth1(StartY, Row1, '.'),
input(FileName, Map, Start, End),
graph(Map, Start, End, Graph),
StartKey is_key_of Start, EndKey is_key_of End,
findall(Dist, walk(Graph, visited{}, StartKey, EndKey, Dist), Dists),
max_list(Dists, Answer),
write(Answer), nl.
walk(_, _, Node, Node, 0).
walk(Graph, Visited, Start, End, Dist) :-
member(Next-NextDist, Graph.get(Start)), \+ _ = Visited.get(Next),
NextVisited = Visited.put(Next, true),
walk(Graph, NextVisited, Next, End, RemainingDist),
Dist is NextDist + RemainingDist.
graph(Map, Start, End, Graph) :-
branch_points(Map, Branches), Nodes = [Start, End|Branches],
findall(
N,
(route(Map, visited{}, 1-StartY, N), format('~w, ', [N]), flush_output),
Ns),
max_list(Ns, Answer),
nl, format('Answer = ~w', [Answer]), nl.
Key-Dists,
( member(Node, Nodes),
dists_from(Map, Nodes, Node, Dists),
Key is_key_of Node),
GraphList),
dict_pairs(Graph, edge, GraphList).
branch_points(Map, Points) :- findall(Point, branch_point(Map, Point), Points).
branch_point(Map, X-Y) :-
nth1(X, Map, Row), nth1(Y, Row, Cell), Cell = '.',
findall(X1-Y1, cell_neighbor(Map, 0-0, X-Y, X1-Y1), Neighbors),
length(Neighbors, N), N > 2.
route(Map, _, X-_, 0) :- length(Map, Height), X =:= Height.
route(Map, Visiteds, X-Y, N) :-
Key is X*1000 + Y, NextVisiteds = Visiteds.put(Key, true),
neighbor(Map, X-Y, X1-Y1),
NeighborKey is X1*1000 + Y1, \+ _= Visiteds.get(NeighborKey),
route(Map, NextVisiteds, X1-Y1, N1),
N is N1 + 1.
dists_from(Map, Nodes, N1, Dists) :-
findall(
Key-Dist, (
member(N2, Nodes), \+ N1 = N2,
nobranch_dist(Map, 0-0, N1, N2, Dist),
Key is_key_of N2),
Dists).
neighbor(Map, X-Y, X1-Y1) :-
is_key_of(Key, X-Y) :- Key is X*1000 + Y.
% nobranch_dist(X1-Y1, X2-Y2, Dist) :- true.
nobranch_dist(_, _, X-Y, X-Y, 0).
nobranch_dist(Map, FromX-FromY, X1-Y1, X2-Y2, Dist) :-
findall(Xn-Yn, cell_neighbor(Map, FromX-FromY, X1-Y1, Xn-Yn), Neighbors),
length(Neighbors, NeighborCount),
\+ (NeighborCount =\= 1, FromX =\= 0), % on a route or at beginning
member(Neighbor, Neighbors),
nobranch_dist(Map, X1-Y1, Neighbor, X2-Y2, NextDist),
Dist is NextDist + 1.
% cell_neighbor finds an adjacent neighbor
cell_neighbor(Map, FromX-FromY, X-Y, X1-Y1) :-
( X1 is X + 1, Y1 = Y;
X1 is X - 1, Y1 = Y;
X1 = X, Y1 is Y + 1;
X1 = X, Y1 is Y - 1
),
nth1(X1, Map, Row1), nth1(Y1, Row1, '.').
nth1(X1, Map, Row1), nth1(Y1, Row1, '.'),
\+ (X1 = FromX, Y1 = FromY).
% input parsing stuff below. Brick indexing is for debugging.
input(FileName, Map) :- phrase_from_file(lines(Map), FileName).
input(FileName, Map, 1-StartY, EndX-EndY) :-
phrase_from_file(lines(Map), FileName),
length(Map, EndX),
nth1(1, Map, StartRow), nth1(StartY, StartRow, '.'),
nth1(EndX, Map, EndRow), nth1(EndY, EndRow, '.').
lines([]) --> eos, !.
lines([Line|Lines]) --> line(Line), lines(Lines).