aoc23/16/part1.pl

71 lines
2.2 KiB
Perl
Raw Permalink Normal View History

2023-12-16 01:23:19 -06:00
:- use_module(library(pio)).
:- initialization(main, main).
main([FileName|_]) :-
input(FileName, Map),
propagate(Map, [0-0-3], FinalMap),
count(FinalMap, Answer),
write(Answer), nl.
count(Map, X) :-
findall(1, (nth0(_, Map, Row), nth0(_, Row, _-D), \+ D = [0,0,0,0]), Ls),
length(Ls, X).
% propagate(Map, Queue, NewMap). 'Dir' is 0/1/2/3 == light coming from N/E/S/W.
propagate(Map, [], Map).
propagate(Map, [X-Y-Dir|Queue], FinalMap) :-
( (nth0(X, Map, Row), nth0(Y, Row, Cell-Done), nth0(Dir, Done, 0))
-> replace(Dir, Done, 1, NewDone),
replace(Y, Row, Cell-NewDone, NewRow),
replace(X, Map, NewRow, NewMap),
call(Cell, X, Y, Dir, NewCells),
append(Queue, NewCells, NewQueue)
; NewQueue = Queue,
NewMap = Map
),
propagate(NewMap, NewQueue, FinalMap).
'.'(X, Y, 0, [NewX-Y-0]) :- NewX is X + 1.
'.'(X, Y, 1, [X-NewY-1]) :- NewY is Y - 1.
'.'(X, Y, 2, [NewX-Y-2]) :- NewX is X - 1.
'.'(X, Y, 3, [X-NewY-3]) :- NewY is Y + 1.
'/'(X, Y, 0, [X-NewY-1]) :- NewY is Y - 1.
'/'(X, Y, 1, [NewX-Y-0]) :- NewX is X + 1.
'/'(X, Y, 2, [X-NewY-3]) :- NewY is Y + 1.
'/'(X, Y, 3, [NewX-Y-2]) :- NewX is X - 1.
'\\'(X, Y, 0, [X-NewY-3]) :- NewY is Y + 1.
'\\'(X, Y, 1, [NewX-Y-2]) :- NewX is X - 1.
'\\'(X, Y, 2, [X-NewY-1]) :- NewY is Y - 1.
'\\'(X, Y, 3, [NewX-Y-0]) :- NewX is X + 1.
'|'(X, Y, 0, NewCells) :- '.'(X, Y, 0, NewCells).
'|'(X, Y, 2, NewCells) :- '.'(X, Y, 2, NewCells).
'|'(X, Y, 3, NewCells) :- '|'(X, Y, 1, NewCells).
'|'(X, Y, 1, [X1-Y-0, X2-Y-2]) :- X1 is X + 1, X2 is X - 1.
'-'(X, Y, 1, NewCells) :- '.'(X, Y, 1, NewCells).
'-'(X, Y, 3, NewCells) :- '.'(X, Y, 3, NewCells).
'-'(X, Y, 2, NewCells) :- '-'(X, Y, 0, NewCells).
'-'(X, Y, 0, [X-Y1-1, X-Y2-3]) :- Y1 is Y - 1, Y2 is Y + 1.
replace(I, List, Elem, NewList) :-
nth0(I, List, _, Rest),
nth0(I, NewList, Elem, Rest).
% Input stuff. Cell-(N,E,S,W) indicating which direction was already handled
input(Name, Map) :- phrase_from_file(lines(Map), Name).
lines([]) --> eos, !.
lines([Line|Lines]) --> line(Line), lines(Lines).
line([]) --> ("\n"; eos), !.
line([Char-[0,0,0,0]|Chars]) --> [C], line(Chars), {char_code(Char, C)}.
eos([], []).
% Debug stuff
print(Map) :- maplist([X]>>(write(X), nl), Map), nl.