aoc23/13/part2.pl

56 lines
1.7 KiB
Perl
Raw Normal View History

2023-12-13 02:29:06 -06:00
:- use_module(library(pio)).
:- use_module(library(clpfd)).
:- initialization(main, main).
main([FileName|_]) :-
input(FileName, Blocks),
convlist(almost_reflect, Blocks, Vs), sum_list(Vs, V),
maplist(transpose, Blocks, TBlocks),
convlist(almost_reflect, TBlocks, Hs), sum_list(Hs, H),
Answer is 100*V + H,
writef('Answer=%t\n', [Answer]).
almost_reflect(Items, N) :- almost_perfect_reflect(Items, N).
almost_reflect(Items, N) :-
append(SubItems, [_|_], Items),
almost_perfect_reflect(SubItems, N).
almost_reflect(Items, N) :-
append(Prefix, SubItems, Items),
almost_perfect_reflect(SubItems, SubN),
length(Prefix, Len), N is SubN + Len.
almost_perfect_reflect([A, B], 1) :- diff(A, B, 1).
almost_perfect_reflect(Items, N) :-
append([[A], OtherItems, [A]], Items),
almost_perfect_reflect(OtherItems, N_sub1),
N is N_sub1 + 1.
almost_perfect_reflect(Items, N) :-
append([[A], OtherItems, [B]], Items),
diff(A, B, 1),
perfect_reflect(OtherItems, N_sub1),
N is N_sub1 + 1.
% reflect right down the middle. N is half list length.
perfect_reflect([A, A], 1).
perfect_reflect(Items, N) :-
append([[Item], OtherItems, [Item]], Items),
perfect_reflect(OtherItems, N_sub1),
N is N_sub1 + 1.
diff(L1, L2, N) :-
foldl([A, B, Prev, Curr]>>(Curr is Prev + abs(A - B)), L1, L2, 0, N).
input(FileName, Blocks) :- phrase_from_file(blocks(Blocks), FileName).
blocks([]) --> eos, !.
blocks([Block|Blocks]) --> block(Block), blocks(Blocks).
block([Line]) --> line(Line), ("\n"; eos), !.
block([Line|Lines]) --> line(Line), block(Lines).
line([]) --> ("\n"; eos), !.
line([1|Chars]) --> "#", line(Chars).
line([0|Chars]) --> ".", line(Chars).
eos([], []).