d23p2
This commit is contained in:
parent
69e2bc3b20
commit
b8c59949e9
75
23/part2.pl
75
23/part2.pl
@ -1,36 +1,75 @@
|
|||||||
:- use_module(library(pio)).
|
:- use_module(library(pio)).
|
||||||
:- use_module(library(dcg/basics)).
|
:- use_module(library(dcg/basics)).
|
||||||
:- initialization(main, main).
|
:- initialization(main, main).
|
||||||
:- table neighbor/3.
|
:- op(700, xfx, is_key_of).
|
||||||
|
|
||||||
main([FileName|_]) :-
|
main([FileName|_]) :-
|
||||||
input(FileName, Map),
|
input(FileName, Map, Start, End),
|
||||||
nth1(1, Map, Row1), nth1(StartY, Row1, '.'),
|
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(
|
findall(
|
||||||
N,
|
Key-Dists,
|
||||||
(route(Map, visited{}, 1-StartY, N), format('~w, ', [N]), flush_output),
|
( member(Node, Nodes),
|
||||||
Ns),
|
dists_from(Map, Nodes, Node, Dists),
|
||||||
max_list(Ns, Answer),
|
Key is_key_of Node),
|
||||||
nl, format('Answer = ~w', [Answer]), nl.
|
GraphList),
|
||||||
|
dict_pairs(Graph, edge, GraphList).
|
||||||
|
|
||||||
route(Map, _, X-_, 0) :- length(Map, Height), X =:= Height.
|
branch_points(Map, Points) :- findall(Point, branch_point(Map, Point), Points).
|
||||||
route(Map, Visiteds, X-Y, N) :-
|
branch_point(Map, X-Y) :-
|
||||||
Key is X*1000 + Y, NextVisiteds = Visiteds.put(Key, true),
|
nth1(X, Map, Row), nth1(Y, Row, Cell), Cell = '.',
|
||||||
neighbor(Map, X-Y, X1-Y1),
|
findall(X1-Y1, cell_neighbor(Map, 0-0, X-Y, X1-Y1), Neighbors),
|
||||||
NeighborKey is X1*1000 + Y1, \+ _= Visiteds.get(NeighborKey),
|
length(Neighbors, N), N > 2.
|
||||||
route(Map, NextVisiteds, X1-Y1, N1),
|
|
||||||
N is N1 + 1.
|
|
||||||
|
|
||||||
neighbor(Map, X-Y, X1-Y1) :-
|
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 is X - 1, Y1 = Y;
|
X1 is X - 1, Y1 = Y;
|
||||||
X1 = X, Y1 is Y + 1;
|
X1 = X, Y1 is Y + 1;
|
||||||
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 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([]) --> eos, !.
|
||||||
lines([Line|Lines]) --> line(Line), lines(Lines).
|
lines([Line|Lines]) --> line(Line), lines(Lines).
|
||||||
|
Loading…
Reference in New Issue
Block a user