Compare commits
No commits in common. "b8c59949e92e3c440f119cf95b492f37e1762c30" and "e0a1757e9e69fe4a19c01da50f6b25b807335c59" have entirely different histories.
b8c59949e9
...
e0a1757e9e
90
23/part2.pl
90
23/part2.pl
@ -1,90 +0,0 @@
|
||||
:- use_module(library(pio)).
|
||||
:- use_module(library(dcg/basics)).
|
||||
:- initialization(main, main).
|
||||
:- op(700, xfx, is_key_of).
|
||||
|
||||
main([FileName|_]) :-
|
||||
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(
|
||||
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.
|
||||
|
||||
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).
|
||||
|
||||
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, '.'),
|
||||
\+ (X1 = FromX, Y1 = FromY).
|
||||
|
||||
% input parsing stuff below. Brick indexing is for debugging.
|
||||
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).
|
||||
|
||||
line([]) --> ("\n"; eos), !.
|
||||
line(['#'|Chars]) --> "#", line(Chars).
|
||||
line(['.'|Chars]) --> ("."; ">"; "v"), line(Chars).
|
||||
|
||||
% debug
|
||||
print(Map) :-
|
||||
findall(
|
||||
X,
|
||||
( nth1(X, Map, Line),
|
||||
format('~3d', [X]), write(" "),
|
||||
atomic_list_concat(Line, Str), write(Str), nl
|
||||
),
|
||||
_),
|
||||
nl.
|
Loading…
Reference in New Issue
Block a user