aoc23/14/part2.pl

90 lines
2.7 KiB
Perl
Raw Normal View History

:- use_module(library(pio)).
:- use_module(library(clpfd)).
:- initialization(main, main).
main([FileName|_]) :-
input(FileName, Input),
concurrent_maplist(row_weight, Rocks, Weights),
sum_list(Weights, W),
writef('%t\n', [W]).
row_weight(Row, Weight) :-
phrase(rock_counts(Rocks), Row),
convlist([N-z-_, N]>>(true), Rocks, RockCounts),
sum_list(RockCounts, Weight).
% North is to the left
roll(Map, NewMap) :-
concurrent_maplist(collapse, Map, NorthCollapsed),
rotate(NorthCollapsed, West),
concurrent_maplist(collapse, West, WestCollapsed),
rotate(WestCollapsed, South),
concurrent_maplist(collapse, South, SouthCollapsed),
rotate(SouthCollapsed, East),
concurrent_maplist(collapse, East, EastCollapsed),
rotate(EastCollapsed, NewMap).
rotate(Map, NewMap) :-
transpose(Map, X),
concurrent_maplist(reverse, X, NewMap).
print(Map) :-
rotate(Map, RotMap),
append([[_|RealMap], [_]], RotMap),
maplist([X]>>(
append([_|Y], [_], X),
atomics_to_string(Y, S),
writef('%t\n', [S])), RealMap),
write('\n').
collapse(Row, NewRow) :-
% abolish_private_tables,
% table(rock_counts/3), table(condense/3), table(reexpand/3),
phrase(rock_counts(Counts), Row),
phrase(condense(Zs), Counts),
phrase(reexpand(Zs), NewRow),
% NewRow = Zs,
true.
reexpand([]) --> eos.
reexpand([N-Next|Rocks]) --> ['#'], stack(N, Next), reexpand(Rocks).
stack(0, 0) --> [], !.
stack(0, Z) --> {NextZ is Z - 1}, ['.'], stack(0, NextZ), !.
stack(N, Z) --> {NextZ is Z - 1, NextN is N - 1}, ['O'], stack(NextN, NextZ).
condense([]) --> [0-0-0].
condense([N-Next|Rocks]) --> [0-I-I, N-z-Next], condense(Rocks), !.
condense(Rocks) --> [_-_-_], condense(Rocks).
rock_counts([0-0-0]) --> [].
rock_counts([LastN-I-LastZ, LastN-LastI-LastZ|Rocks]) -->
['.'], rock_counts([LastN-LastI-LastZ|Rocks]),
{I is LastI + 1}.
rock_counts([N-I-LastZ, LastN-LastI-LastZ|Rocks]) -->
['O'], rock_counts([LastN-LastI-LastZ|Rocks]),
{I is LastI + 1, N is LastN + 1}.
rock_counts([0-I-I, LastN-z-Len, LastN-LastI-LastZ|Rocks]) -->
['#'], rock_counts([LastN-LastI-LastZ|Rocks]),
{I is LastI + 1, Len is I - LastZ - 1}.
% North is to the left
input(FileName, Input) :-
phrase_from_file(lines(Raw), FileName),
concurrent_maplist(pad, Raw, PaddedInput),
concurrent_maplist(reverse, PaddedInput, Reversed),
transpose(Reversed, Rotated),
concurrent_maplist(pad, Rotated, Input).
pad(Row, Rowx) :- append(['#'|Row], ['#'], Rowx).
lines([]) --> eos, !.
lines([Line|Lines]) --> line(Line), lines(Lines).
line([]) --> "\n"; eos.
line(['O'|Chars]) --> "O", line(Chars).
line(['.'|Chars]) --> ".", line(Chars).
line(['#'|Chars]) --> "#", line(Chars).
eos([], []).