aoc2022/abandoned/day15.m

335 lines
10 KiB
Mathematica

:- module day15.
:- interface.
:- import_module basics.
:- pred run(part::in, lines::in, answer::out) is cc_multi.
:- implementation.
:- import_module int.
:- import_module string.
:- import_module list.
:- import_module maybe.
:- import_module array2d.
:- import_module array.
:- import_module set_bbbtree.
:- type set(T) == set_bbbtree(T).
:- type cell ---> unknown; empty; sensor; beacon.
:- type data == array2d(cell).
:- type grid --->
g(start_x :: int, end_x :: int,
start_y :: int, end_y :: int,
data :: data).
:- inst grid for grid/0 ---> g(ground, ground, ground, ground, array2d).
:- mode grid_di == di(grid).
:- mode grid_uo == out(grid).
:- type point == {int, int}.
:- type sensor ---> s(self :: point, beacon :: point).
:- import_module parsing_utils.
:- pred line(src::in, sensor::out, ps::in, ps::out) is semidet.
line(Src, s(S, B)) -->
kws(["sensor", "at"], Src), point(Src, S), punct(":", Src, _),
kws(["closest", "beacon", "is", "at"], Src), point(Src, B), eof(Src, _).
:- pred point(src::in, point::out, ps::in, ps::out) is semidet.
point(Src, {X, Y}) -->
kw("x", Src), punct("=", Src, _), int_literal(Src, X), punct(",", Src, _),
kw("y", Src), punct("=", Src, _), int_literal(Src, Y).
:- pred kw(string::in, src::in, ps::in, ps::out) is semidet.
kw(K, Src) --> ikeyword("abcdefghijklmnopqrsuvwxyz", K, Src, _).
:- pred kws(list(string)::in, src::in, ps::in, ps::out) is semidet.
kws([], _) --> [].
kws([K | Ks], Src) --> kw(K, Src), kws(Ks, Src).
:- pred lines(lines::in, list(sensor)::out) is cc_multi.
lines(Lines, Sensors) :- map_index(line, Lines, Sensors).
:- pred line(int::in, string::in, sensor::out) is cc_multi.
line(Line, Str, Out) :-
parse(Str, line, Result),
from_result(Line, Result, Out).
from_result(_, ok(X), X).
from_result(Line, error(yes(Msg), _, Col), _) :-
die("%d:%d: %s", [i(Line), i(Col), s(Msg)]).
from_result(Line, error(no, _, Col), _) :-
die("%d:%d: unknown error lol", [i(Line), i(Col)]).
:- func distance(point, point) = int.
distance({X1, Y1}, {X2, Y2}) = abs(X1 - X2) + abs(Y1 - Y2).
:- func point + int = point.
{X, Y} + D = {X+D, Y+D}.
:- func point - int = point.
{X, Y} - D = {X-D, Y-D}.
:- pred in_bounds(grid::in, point::in) is semidet.
in_bounds(G, {X, Y}) :-
G^start_x =< X, X =< G^end_x,
G^start_y =< Y, Y =< G^end_y.
:- func get(grid, point) = cell.
get(G, {X, Y}) = G^data^elem(Y - G^start_y, X - G^start_x).
:- pred set_d(point::in, point::in, cell::in,
data::array2d_di, data::array2d_uo) is det.
set_d({StartX, StartY}, {X, Y}, A, !Data) :-
!Data^elem(Y - StartY, X - StartX) := A.
:- pred set(point::in, cell::in, grid::grid_di, grid::grid_uo) is det.
set(XY, A, !Grid) :- some [!Data] (
!:Data = !.Grid^data,
set_d({!.Grid^start_x, !.Grid^start_y}, XY, A, !Data),
!Grid^data := !.Data
).
:- type bounds ---> b(min :: point, max :: point).
:- func bounds(list(sensor)) = bounds.
bounds(Sensors) =
foldl(expand_bounds, points_all(Sensors), b({0, 0}, {0, 0})).
:- func points_all(list(sensor)) = list(point).
points_all(Sensors) =
foldr(func(S, Rest) = points(S) ++ Rest, Sensors, []).
:- func points(sensor) = list(point).
points(s(S, B)) = [S - D, S + D, S, B] :-
D = distance(S, B).
:- func expand_bounds(point, bounds) = bounds.
expand_bounds({X, Y}, b({LoX, LoY}, {HiX, HiY})) =
b({LoX `min` X, LoY `min` Y}, {HiX `max` X, HiY `max` Y}).
:- pred place_sensors(
point::in, list(sensor)::in, data::array2d_di, data::array2d_uo) is det.
place_sensors(_, [], !Data).
place_sensors(Start, [s(S, B) | Rest], !Data) :-
set_d(Start, S, sensor, !Data),
set_d(Start, B, beacon, !Data),
place_sensors(Start, Rest, !Data).
:- func grid_from_sensors(list(sensor)::in) = (grid::grid_uo) is det.
grid_from_sensors(Sensors) = !:G :-
b({StartX, StartY}, {EndX, EndY}) = bounds(Sensors),
Width = EndX - StartX + 1, Height = EndY - StartY + 1,
place_sensors({StartX, StartY}, Sensors,
init(Height, Width, unknown), Arr),
!:G = g(StartX, EndX, StartY, EndY, Arr),
set_empty_all(Sensors, !G).
:- pred make_grid(lines::in, grid::grid_uo) is cc_multi.
make_grid(Lines, grid_from_sensors(Sensors)) :-
lines(Lines, Sensors).
:- pred set_empty_all(list(sensor)::in, grid::grid_di, grid::grid_uo) is det.
set_empty_all([], !G).
set_empty_all([S | Ss], !G) :-
set_empty(S, !G), set_empty_all(Ss, !G).
:- pred set_empty(sensor::in, grid::grid_di, grid::grid_uo) is det.
set_empty(s(S, B), !G) :-
D = distance(S, B) + 1,
up(S, D, !G), down(S, D, !G).
:- func up(point) = point.
up({X, Y}) = {X, Y-1}.
:- func down(point) = point.
down({X, Y}) = {X, Y+1}.
:- func left(point) = point.
left({X, Y}) = {X-1, Y}.
:- func right(point) = point.
right({X, Y}) = {X+1, Y}.
:- pred go_v((func(point) = point)::(func(in) = out is det),
point::in, int::in, grid::grid_di, grid::grid_uo) is det.
go_v(F, XY, D, !G) :-
if D = 0 ; not in_bounds(!.G, XY) then true else
set_unknown(XY, empty, !G),
go_v(F, F(XY), D-1, !G),
left(left(XY), D-1, !G),
right(right(XY), D-1, !G).
:- pred go_h((func(point) = point)::(func(in) = out is det),
point::in, int::in, grid::grid_di, grid::grid_uo) is det.
go_h(F, XY, D, !G) :-
if D = 0 ; not in_bounds(!.G, XY) then true else
set_unknown(XY, empty, !G),
go_h(F, F(XY), D-1, !G).
:- pred set_unknown(point::in, cell::in, grid::grid_di, grid::grid_uo) is det.
set_unknown(XY, C, !G) :-
if get(!.G, XY) = unknown then set(XY, C, !G) else true.
:- pred up(point::in, int::in, grid::grid_di, grid::grid_uo) is det.
up(XY, D, !G) :- go_v(up, XY, D, !G).
:- pred down(point::in, int::in, grid::grid_di, grid::grid_uo) is det.
down(XY, D, !G) :- go_v(down, XY, D, !G).
:- pred left(point::in, int::in, grid::grid_di, grid::grid_uo) is det.
left(XY, D, !G) :- go_h(left, XY, D, !G).
:- pred right(point::in, int::in, grid::grid_di, grid::grid_uo) is det.
right(XY, D, !G) :- go_h(right, XY, D, !G).
:- func draw(grid) = lines.
draw(G) = map(func(L) = from_char_list(map(to_char, L)), lists(G^data)).
to_char(unknown) = '·'.
to_char(empty) = ' '.
to_char(sensor) = ''.
to_char(beacon) = ''.
:- func row(int::in, grid::in) = (array(cell)::array_uo).
row(J, G) = Arr :-
Size = G^end_x - G^start_x + 1,
Arr = generate(Size, func(I) = get(G, {I + G^start_x, J})).
:- func count(pred(T)::(pred(in) is semidet), array(T)::in) = (int::out).
count(P, Arr) =
foldl(func(X, Acc) = ite((pred) is semidet :- P(X), 1+Acc, Acc), Arr, 0).
:- pred maybe_beacon(cell::in) is semidet.
maybe_beacon(beacon).
maybe_beacon(unknown).
/*
:- func expand(list(list(point))) = set(point).
expand(Points) = from_list(condense(map(expand1, Points))).
:- func expand1(list(point)) = list(point).
expand1([]) = [].
expand1([P]) = [P].
expand1([P, Q | Rest]) = expand(P, Q) ++ expand1([Q | Rest]).
:- func expand(point, point) = list(point).
expand({X1, Y1}, {X2, Y2}) = List :-
if X1 = X2 then List = map(func(Y) = {X1, Y}, between(Y1, Y2))
else if Y1 = Y2 then List = map(func(X) = {X, Y1}, between(X1, X2))
else die("expand/2: non-orthogonal line").
:- func between(int, int) = list(int).
between(I, J) = to_sorted_list(range(min(I, J), max(I, J))).
:- func bounds(set(point)) = {point, point}.
bounds(Points) = {{LoX, LoY}, {HiX, HiY}} :-
Points0 = insert(Points, hole),
Xs = to_sorted_list(map(func({X, _}) = X, Points0)),
Ys = to_sorted_list(map(func({_, Y}) = Y, Points0)),
LoX = det_head(Xs), det_last(Xs, HiX),
LoY = det_head(Ys), det_last(Ys, HiY).
:- func add_floor(set(point)) = set(point).
add_floor(Points) = insert_list(Points, Floor) :-
{_, {_, Lo}} = bounds(Points),
FloorY = Lo + 2, Start = holeX - FloorY, End = holeX + FloorY,
Floor = map(func(X) = {X, FloorY}, between(Start, End)).
:- func get(grid, point) = cell.
get(G, {X, Y}) = G^data^elem(Y - G^start_y, X - G^start_x).
:- pred set_d(point::in, point::in, cell::in,
data::array2d_di, data::array2d_uo) is det.
set_d({StartX, StartY}, {X, Y}, A, !Data) :-
!Data^elem(Y - StartY, X - StartX) := A.
:- pred set(point::in, cell::in, grid::grid_di, grid::grid_uo) is det.
set(XY, A, !Grid) :- some [!Data] (
!:Data = !.Grid^data,
set_d({!.Grid^start_x, !.Grid^start_y}, XY, A, !Data),
!Grid^data := !.Data
).
:- pred in_bounds(grid::in, point::in) is semidet.
in_bounds(G, {X, Y}) :-
G^start_x =< X, X =< G^end_x,
G^start_y =< Y, Y =< G^end_y.
:- pred place_rocks(point::in, list(point)::in,
data::array2d_di, data::array2d_uo) is det.
place_rocks(_, [], !Data).
place_rocks(Start, [XY | Rest], !Data) :-
set_d(Start, XY, rock, !Data),
place_rocks(Start, Rest, !Data).
:- func grid_from_set(set(point)) = grid.
:- mode grid_from_set(in) = grid_uo.
grid_from_set(Points) = G :-
{{StartX, StartY}, {EndX, EndY}} = bounds(Points),
Width = EndX - StartX + 1, Height = EndY - StartY + 1,
place_rocks({StartX, StartY}, to_sorted_list(Points),
init(Height, Width, empty), Arr),
G = g(StartX, EndX, StartY, EndY, Arr).
:- func make_grid(lines) = grid.
:- mode make_grid(in) = grid_uo is semidet.
make_grid(Lines) = grid_from_set(expand(Points)) :-
lines(Lines, Points).
:- func make_floor_grid(lines) = grid.
:- mode make_floor_grid(in) = grid_uo is semidet.
make_floor_grid(Lines) = grid_from_set(add_floor(expand(Points))) :-
lines(Lines, Points).
:- type fall ---> stop(point); overflow.
:- pred move(point::in, fall::out, grid::grid_di, grid::grid_uo) is semidet.
move({X, Y}, B, !Grid) :-
if not in_bounds(!.Grid, {X, Y}) then B = overflow
else if get(!.Grid, {X, Y}) \= empty then fail
else if move({X, Y+1}, B0, !Grid) then B = B0
else if move({X-1, Y+1}, B0, !Grid) then B = B0
else if move({X+1, Y+1}, B0, !Grid) then B = B0
else set({X, Y}, sand, !Grid), B = stop({X, Y}).
:- pred fill(int::out, grid::grid_di, grid::grid_uo) is det.
fill(N, !Grid) :-
if move(hole, stop(_), !Grid) then fill(N0, !Grid), N = N0 + 1
else N = 0.
:- pragma no_determinism_warning(run/3).
run(one, Lines, int(Res)) :-
if Grid = make_grid(Lines) then fill(Res, Grid, _)
else die("bad input").
run(two, Lines, int(Res)) :-
if Grid = make_floor_grid(Lines) then fill(Res, Grid, _)
else die("bad input").
*/
:- import_module std_util.
run(_, Lines, Out) :-
make_grid(Lines, Grid),
Out = lines(draw(Grid) ++
[string([Grid^start_x, Grid^start_y, Grid^end_x, Grid^end_y]),
string(count(isnt(maybe_beacon), row(2_000_000, Grid)))]).