d21p1
This commit is contained in:
47
21/part1.pl
Normal file
47
21/part1.pl
Normal file
@@ -0,0 +1,47 @@
|
||||
:- use_module(library(pio)).
|
||||
:- use_module(library(dcg/basics)).
|
||||
:- initialization(main, main).
|
||||
|
||||
main([FileName|_]) :-
|
||||
input(FileName, Map, Starting),
|
||||
nsteps(Map, 64, [Starting], Ends), length(Ends, Answer),
|
||||
write(Answer), nl.
|
||||
|
||||
nsteps(Map, N, Starts, Reachables) :-
|
||||
length(Range, N),
|
||||
foldl({Map}/[_, SIn, SOut]>>(step(Map, SIn, SOut)), Range, Starts, Reachables).
|
||||
|
||||
step(Map, CurrentCells, NextCells) :-
|
||||
maplist(neighbors(Map), CurrentCells, NeighborsOfCells),
|
||||
foldl(
|
||||
[Neighbors, SetIn, SetOut]>>(
|
||||
list_to_ord_set(Neighbors, NeighborsSet),
|
||||
ord_union(SetIn, NeighborsSet, SetOut)),
|
||||
NeighborsOfCells, [], NextCells).
|
||||
|
||||
neighbors(Map, X-Y, Neighbors) :-
|
||||
findall(X1-Y1, neighbor(Map, X-Y, X1-Y1), Neighbors).
|
||||
|
||||
neighbor(Map, X-Y, X1-Y1) :-
|
||||
( X1 is X, Y1 is Y+1; X1 is X, Y1 is Y-1;
|
||||
X1 is X+1, Y1 is Y; X1 is X-1, Y1 is Y ),
|
||||
nth0(X1, Map, Row), nth0(Y1, Row, '.').
|
||||
|
||||
replace(I, List, E, NewList) :- nth0(I, List, _, R), nth0(I, NewList, E, R).
|
||||
|
||||
% input parsing stuff below
|
||||
input(FileName, Map, StartX-StartY) :-
|
||||
phrase_from_file(lines(MapS), FileName),
|
||||
nth0(StartX, MapS, Row), nth0(StartY, Row, s),
|
||||
select(s, Row, '.', NewRow), replace(StartX, MapS, NewRow, Map).
|
||||
|
||||
lines([]) --> eos, !.
|
||||
lines([Line|Lines]) --> line(Line), lines(Lines).
|
||||
|
||||
line([]) --> "\n"; eos.
|
||||
line([s|Chars]) --> "S", line(Chars).
|
||||
line(['.'|Chars]) --> ".", line(Chars).
|
||||
line(['#'|Chars]) --> "#", line(Chars).
|
||||
|
||||
% Debug stuff
|
||||
print(Map) :- maplist([X]>>(atomics_to_string(X, XStr), write(XStr), nl), Map).
|
Reference in New Issue
Block a user