Compare commits

..

5 Commits

Author SHA1 Message Date
03c8e7d0ec omg I never committed d24p2 2024-12-12 22:17:04 -08:00
fd48bea516 d25p1 2023-12-25 16:45:25 -08:00
95261557ea d24p2 2023-12-25 13:20:40 -08:00
b8c59949e9 d23p2 2023-12-25 02:26:26 -08:00
69e2bc3b20 d23p2 naive 2023-12-24 23:40:09 -08:00
7 changed files with 1476 additions and 0 deletions

90
23/part2.pl Normal file
View File

@@ -0,0 +1,90 @@
:- use_module(library(pio)).
:- use_module(library(dcg/basics)).
:- initialization(main, main).
:- op(700, xfx, is_key_of).
main([FileName|_]) :-
input(FileName, Map, Start, End),
graph(Map, Start, End, Graph),
StartKey is_key_of Start, EndKey is_key_of End,
findall(Dist, walk(Graph, visited{}, StartKey, EndKey, Dist), Dists),
max_list(Dists, Answer),
write(Answer), nl.
walk(_, _, Node, Node, 0).
walk(Graph, Visited, Start, End, Dist) :-
member(Next-NextDist, Graph.get(Start)), \+ _ = Visited.get(Next),
NextVisited = Visited.put(Next, true),
walk(Graph, NextVisited, Next, End, RemainingDist),
Dist is NextDist + RemainingDist.
graph(Map, Start, End, Graph) :-
branch_points(Map, Branches), Nodes = [Start, End|Branches],
findall(
Key-Dists,
( member(Node, Nodes),
dists_from(Map, Nodes, Node, Dists),
Key is_key_of Node),
GraphList),
dict_pairs(Graph, edge, GraphList).
branch_points(Map, Points) :- findall(Point, branch_point(Map, Point), Points).
branch_point(Map, X-Y) :-
nth1(X, Map, Row), nth1(Y, Row, Cell), Cell = '.',
findall(X1-Y1, cell_neighbor(Map, 0-0, X-Y, X1-Y1), Neighbors),
length(Neighbors, N), N > 2.
dists_from(Map, Nodes, N1, Dists) :-
findall(
Key-Dist, (
member(N2, Nodes), \+ N1 = N2,
nobranch_dist(Map, 0-0, N1, N2, Dist),
Key is_key_of N2),
Dists).
is_key_of(Key, X-Y) :- Key is X*1000 + Y.
% nobranch_dist(X1-Y1, X2-Y2, Dist) :- true.
nobranch_dist(_, _, X-Y, X-Y, 0).
nobranch_dist(Map, FromX-FromY, X1-Y1, X2-Y2, Dist) :-
findall(Xn-Yn, cell_neighbor(Map, FromX-FromY, X1-Y1, Xn-Yn), Neighbors),
length(Neighbors, NeighborCount),
\+ (NeighborCount =\= 1, FromX =\= 0), % on a route or at beginning
member(Neighbor, Neighbors),
nobranch_dist(Map, X1-Y1, Neighbor, X2-Y2, NextDist),
Dist is NextDist + 1.
% cell_neighbor finds an adjacent neighbor
cell_neighbor(Map, FromX-FromY, X-Y, X1-Y1) :-
( X1 is X + 1, Y1 = Y;
X1 is X - 1, Y1 = Y;
X1 = X, Y1 is Y + 1;
X1 = X, Y1 is Y - 1
),
nth1(X1, Map, Row1), nth1(Y1, Row1, '.'),
\+ (X1 = FromX, Y1 = FromY).
% input parsing stuff below. Brick indexing is for debugging.
input(FileName, Map, 1-StartY, EndX-EndY) :-
phrase_from_file(lines(Map), FileName),
length(Map, EndX),
nth1(1, Map, StartRow), nth1(StartY, StartRow, '.'),
nth1(EndX, Map, EndRow), nth1(EndY, EndRow, '.').
lines([]) --> eos, !.
lines([Line|Lines]) --> line(Line), lines(Lines).
line([]) --> ("\n"; eos), !.
line(['#'|Chars]) --> "#", line(Chars).
line(['.'|Chars]) --> ("."; ">"; "v"), line(Chars).
% debug
print(Map) :-
findall(
X,
( nth1(X, Map, Line),
format('~3d', [X]), write(" "),
atomic_list_concat(Line, Str), write(Str), nl
),
_),
nl.

20
24/lol.txt Normal file

File diff suppressed because one or more lines are too long

35
24/part2.pl Normal file
View File

@@ -0,0 +1,35 @@
:- use_module(library(pio)).
:- use_module(library(dcg/basics)).
:- initialization(main, main).
main([FileName|_]) :-
input(FileName, Hails),
maplist(xyline, Hails, Lines),
findall(
[N1, N2, X, Y], (
member(N1-L1-X1assert, Lines), member(N2-L2-X2assert, Lines), N1 < N2,
intersect(L1, L2, X-Y), call(X1assert, X), call(X2assert, X),
X >= 200000000000000, X =< 400000000000000,
Y >= 200000000000000, Y =< 400000000000000),
Intersects),
length(Intersects, Answer),
write(Answer), nl.
intersect(A1-B1-C1, A2-B2-C2, X-Y) :-
Det is A1*B2 - A2*B1, Det =\= 0,
X is (B2*C1 - B1*C2) / Det,
Y is (-A2*C1 + A1*C2) / Det.
xyline(N-(X-Y-_-Dx-Dy-_), N-(A-B-C)-Xassert) :-
A = Dy, B is -Dx, C is X*Dy - Y*Dx,
( Dx >= 0 -> Xassert = =<(X); Xassert = >=(X) ).
% input parsing stuff below. Brick indexing is for debugging.
% assumption: no same hail. There are parallels, but no same
input(FileName, Hails) :- phrase_from_file(hails(0, Hails), FileName).
hails(_, []) --> eos, !.
hails(N, [N-(X-Y-Z-Dx-Dy-Dz)|Hails]) -->
blanks, number(X), ",", blanks, number(Y), ",", blanks, number(Z), " @",
blanks, number(Dx), ",", blanks, number(Dy), ",", blanks, number(Dz), "\n",
{NextN is N + 1}, hails(NextN, Hails).

View File

@@ -3,3 +3,25 @@
20, 25, 34 @ -2, -2, -4
12, 31, 28 @ -1, -2, -1
20, 19, 15 @ 1, -5, -3
Using first 3 rays
x + a*t1 = 19 - 2t1, y + b*t1 = 13 + t1, z + c*t1 = 30 - 2t1,
x + a*t2 = 18 - t2, y + b*t2 = 19 - t2, z + c*t2 = 22 - 2t2,
x + a*t3 = 20 - 2t3, y + b*t3 = 25 - 2t3, z + c*t3 = 34 - 4t3
9 eqs, 9 unks, thus solution in 3 points.
--> a = -3, b = 1, c = 2, t1 = 5, t2 = 3, t3 = 4, x = 24, y = 13, z = 10
x+a*t1 == 320870677764563-40*t1, y+b*t1 == 335750934489987-24*t1, z+c*t1 == 282502845957937+10*t1,
x+a*t2 == 219235623600942+127*t2, y+b*t2 == 408022798608755-45*t2, z+c*t2 == 245679379684914+66*t2,
x+a*t3 == 171834827764229-122*t3, y+b*t3 == 225154401936948-521*t3, z+c*t3 == 232302441670972+95*t3
sage: x, y, z, a, b, c, t1, t2, t3 = var('x, y, z, a, b, c, t1, t2, t3')
sage: solve([
....: x+a*t1 == 320870677764563-40*t1, y+b*t1 == 335750934489987-24*t1, z+c*t1 == 282502845957937+10*t1,
....: x+a*t2 == 219235623600942+127*t2, y+b*t2 == 408022798608755-45*t2, z+c*t2 == 245679379684914+66*t2,
....: x+a*t3 == 171834827764229-122*t3, y+b*t3 == 225154401936948-521*t3, z+c*t3 == 232302441670972+95*t3],
....: x,y,z,a,b,c,t1,t2,t3)
[[x == 149412455352770, y == 174964385672289, z == 233413147425100, a == 201, b == 202, c == 79, t1 == 711444906273, t2 == 943556327678, t3 == 69419109633]]
sage: 149412455352770+174964385672289+233413147425100
557789988450159

1205
25/input.txt Normal file

File diff suppressed because it is too large Load Diff

91
25/part1.pl Normal file
View File

@@ -0,0 +1,91 @@
% This needs more stack. Try --stack_limit=4G
:- use_module(library(pio)).
:- use_module(library(dcg/basics)).
:- initialization(main, main).
main([FileName|_]) :-
input(FileName, Conns),
dict_pairs(Conns, _, ConnsList),
length(ConnsList, NNodes),
findnsols(
1, PartitionSize, (
_ = Conns.StartNode,
iterate(StartNode, EndNode, Conns, _),
atom_length(EndNode, NodeSize3),
PartitionSize is NodeSize3 / 3),
[Side1]),
Side2 is NNodes - Side1,
Answer is Side1*Side2,
write(Answer), nl.
iterate(Node, Node, Graph, Graph) :- length(Graph.Node, 3), !.
iterate(Node0, Node, Graph0, Graph) :-
countall(Graph0.Node0, NeighborCounts),
NeighborCounts = [_-Max|_],
member(Neighbor-Max, NeighborCounts),
combine(Node0, Neighbor, Node1, Graph0, Graph1),
iterate(Node1, Node, Graph1, Graph).
% combine 2 nodes into one, keep all outbound connections
combine(Node1, Node2, Node12, Graph0, Graph) :-
% delete N1 -> N2's and N2 -> N1's
del_dict(Node1, Graph0, OldN1Outs, Graph1),
del_dict(Node2, Graph1, OldN2Outs, Graph2),
remove_all(Node2, OldN1Outs, N1Outs),
remove_all(Node1, OldN2Outs, N2Outs),
% replace N1 -> X and N2 -> Y with N12 -> [X|Y]
atom_concat(Node1, Node2, Node12),
append(N1Outs, N2Outs, N12Outs),
Graph3 = Graph2.put(Node12, N12Outs),
% replace X -> N1 or X -> N2 with X -> N12 (twice if needed)
foldl(replace_outbound_node(Node1, Node12), N1Outs, Graph3, Graph4),
foldl(replace_outbound_node(Node2, Node12), N2Outs, Graph4, Graph).
replace_outbound_node(Node1, Node2, Node, Graph0, Graph) :-
replace_all(Node1, Graph0.Node, Node2, NewList),
Graph = Graph0.put(Node, NewList).
% List has all items in List but with all ItemOut instances replaced with ItemIn
replace_all(_, [], _, []).
replace_all(ItemOut, [ItemOut|List0], ItemIn, [ItemIn|List]) :-
replace_all(ItemOut, List0, ItemIn, List).
replace_all(ItemOut, [X|List0], ItemIn, [X|List]) :-
\+ X = ItemOut,
replace_all(ItemOut, List0, ItemIn, List).
remove_all(_, [], []).
remove_all(X, [X|List], ListOut) :- remove_all(X, List, ListOut).
remove_all(X, [Y|List], [Y|ListOut]) :- \+ X = Y, remove_all(X, List, ListOut).
% countall means Counts is pairs of Item-Count where Item in List, sorted >
countall(List, Counts) :-
foldl(increment, List, count{}, CountsMap),
dict_pairs(CountsMap, _, CountsList),
sort(2, @>=, CountsList, Counts).
increment(X, Ns0, Ns) :- Next is Ns0.get(X, 0) + 1, Ns = Ns0.put(X, Next).
% input parsing stuff below.
input(FileName, Conns) :-
phrase_from_file(conns(ConnsList), FileName),
to_bidi_graph(ConnsList, Conns).
conns([]) --> eos, !.
conns([From-Tos|Conns]) --> node(From), ": ", tos(Tos), conns(Conns).
tos([To]) --> node(To), "\n".
tos([To|Tos]) --> node(To), " ", tos(Tos).
node(Node) --> string_without(": \n", NodeStr), {atom_codes(Node, NodeStr)}.
to_bidi_graph(ConnsList, BidiConnsGraph) :-
dict_pairs(Graph0, conn, ConnsList),
foldl(add_reverse_conns_for, ConnsList, Graph0, BidiConnsGraph).
add_reverse_conns_for(Node-Outbounds, Conns0, Conns1) :-
foldl(add_conn(Node), Outbounds, Conns0, Conns1).
add_conn(ToNode, FromNode, Conns0, Conns1) :-
Current = Conns0.get(FromNode, []),
Conns1 = Conns0.put(FromNode, [ToNode|Current]).
% debug
print(Graph) :- dict_pairs(Graph, _, Lines), maplist(format('~w~n'), Lines).

13
25/test.txt Normal file
View File

@@ -0,0 +1,13 @@
jqt: rhn xhk nvd
rsh: frs pzl lsr
xhk: hfx
cmg: qnr nvd lhk bvb
rhn: xhk bvb hfx
bvb: xhk hfx
pzl: lsr hfx nvd
qnr: nvd
ntq: jqt hfx bvb xhk
nvd: lhk
lsr: lhk
rzs: qnr cmg lsr rsh
frs: qnr lhk lsr