Compare commits
9 Commits
6aa76ea842
...
main
Author | SHA1 | Date | |
---|---|---|---|
03c8e7d0ec | |||
fd48bea516 | |||
95261557ea | |||
b8c59949e9 | |||
69e2bc3b20 | |||
e0a1757e9e | |||
5204bf0d60 | |||
0064376377 | |||
6d19325d59 |
1479
22/input.txt
Normal file
1479
22/input.txt
Normal file
File diff suppressed because it is too large
Load Diff
100
22/part1.pl
Normal file
100
22/part1.pl
Normal file
@@ -0,0 +1,100 @@
|
|||||||
|
:- use_module(library(pio)).
|
||||||
|
:- use_module(library(dcg/basics)).
|
||||||
|
:- op(700, xfx, [supports, is_way_above]).
|
||||||
|
:- initialization(main, main).
|
||||||
|
|
||||||
|
main([FileName|_]) :-
|
||||||
|
input(FileName, Bricks),
|
||||||
|
stack(Bricks, Stacked),
|
||||||
|
support_listing(Stacked, LookDown, LookUp),
|
||||||
|
max_member(MaxN-_-_-_, Bricks),
|
||||||
|
findall(N, (between(0, MaxN, N), can_remove(N, LookDown, LookUp)), Ns),
|
||||||
|
length(Ns, Answer),
|
||||||
|
write(Answer), nl.
|
||||||
|
|
||||||
|
can_remove(N, LookDown, LookUp) :-
|
||||||
|
BeingSupporteds = LookUp.N,
|
||||||
|
write(N), write("("), write(LookDown.N), write(") supporting "),
|
||||||
|
write(BeingSupporteds), nl,
|
||||||
|
maplist(supported_by_more_than_one(LookDown), BeingSupporteds).
|
||||||
|
|
||||||
|
supported_by_more_than_one(LookDown, N) :- LookDown.N > 1.
|
||||||
|
|
||||||
|
% StackedBricks is sorted by decreasing top edge
|
||||||
|
support_listing(StackedBricks, SupportedCount, SupportingMap) :-
|
||||||
|
findall(
|
||||||
|
N=SupportedListLen,
|
||||||
|
( append(_, [Brick1|Belows], StackedBricks),
|
||||||
|
supported_by(Brick1, Belows, SupportedList),
|
||||||
|
length(SupportedList, SupportedListLen),
|
||||||
|
Brick1 = N-_-_-_),
|
||||||
|
SupportedLists),
|
||||||
|
SupportedCount = brick{}.put(SupportedLists),
|
||||||
|
sort(2, @=<, StackedBricks, StackSortedByBottoms),
|
||||||
|
findall(
|
||||||
|
M=SupportingList,
|
||||||
|
( append(_, [Brick2|Aboves], StackSortedByBottoms),
|
||||||
|
supporting(Brick2, Aboves, SupportingList),
|
||||||
|
Brick2 = M-_-_-_),
|
||||||
|
SupportingLists),
|
||||||
|
SupportingMap = brick{}.put(SupportingLists).
|
||||||
|
|
||||||
|
% Aboves need to be sorted by increasing bot edge
|
||||||
|
supporting(_Brick, [], []).
|
||||||
|
supporting(Brick, [Above|_], []) :- Above is_way_above Brick, !.
|
||||||
|
supporting(Brick, [Above|Aboves], Supportings) :-
|
||||||
|
supporting(Brick, Aboves, NextSupportings),
|
||||||
|
( Brick supports Above
|
||||||
|
-> Above = N-_-_-_, Supportings = [N|NextSupportings]
|
||||||
|
; Supportings = NextSupportings).
|
||||||
|
|
||||||
|
% Belows need to be sorted decreasing by top edge
|
||||||
|
supported_by(_Brick, [], []).
|
||||||
|
supported_by(Brick, [Below|_], []) :- Brick is_way_above Below, !.
|
||||||
|
supported_by(Brick, [Below|Belows], SupportedBy) :-
|
||||||
|
supported_by(Brick, Belows, NextSupportedBy),
|
||||||
|
( Below supports Brick
|
||||||
|
-> Below = N-_-_-_, SupportedBy = [N|NextSupportedBy]
|
||||||
|
; SupportedBy = NextSupportedBy).
|
||||||
|
|
||||||
|
is_way_above(_-_-_-(Z2bot-_), _-_-_-(_-Z1top)) :- Z2bot > Z1top + 1.
|
||||||
|
supports(Brick1, Brick2) :-
|
||||||
|
overlap(Brick1, Brick2),
|
||||||
|
Brick1 = _-_-_-(_-Z1top), Brick2 = _-_-_-(Z2bot-_), Z2bot =:= Z1top + 1.
|
||||||
|
|
||||||
|
stack(Bricks, StackedBricks) :-
|
||||||
|
empty_heap(H0), foldl(stack1, Bricks, H0, Heap),
|
||||||
|
heap_to_list(Heap, HeapList),
|
||||||
|
maplist([_-Brick, Brick]>>(true), HeapList, StackedBricks).
|
||||||
|
|
||||||
|
stack1(Brick, Heap, NewHeap) :-
|
||||||
|
( max_of_heap(Heap, OldZtop, OldTop), overlap(Brick, OldTop)
|
||||||
|
; empty_heap(Heap), OldZtop is 0),
|
||||||
|
Brick = N-X-Y-(Zbot-Ztop),
|
||||||
|
NewZbot is OldZtop + 1, NewZtop is NewZbot + (Ztop - Zbot),
|
||||||
|
add_to_maxheap(Heap, NewZtop, N-X-Y-(NewZbot-NewZtop), NewHeap),
|
||||||
|
!.
|
||||||
|
stack1(Brick, Heap, NewHeap) :-
|
||||||
|
get_from_maxheap(Heap, LastZtop, LastTopBrick, HeapWithoutTop),
|
||||||
|
stack1(Brick, HeapWithoutTop, NewHeapWithoutTop),
|
||||||
|
add_to_maxheap(NewHeapWithoutTop, LastZtop, LastTopBrick, NewHeap).
|
||||||
|
|
||||||
|
overlap(_-(Xa1-Xa2)-(Ya1-Ya2)-_, _-(Xb1-Xb2)-(Yb1-Yb2)-_) :-
|
||||||
|
Xa1 =< Xb2, Xa2 >= Xb1, Ya1 =< Yb2, Ya2 >= Yb1.
|
||||||
|
|
||||||
|
% input parsing stuff below. Brick indexing is for debugging.
|
||||||
|
input(FileName, SortedBricks) :-
|
||||||
|
phrase_from_file(bricks(0, Bricks), FileName),
|
||||||
|
sort(2, @=<, Bricks, SortedBricks).
|
||||||
|
bricks(_, []) --> eos, !.
|
||||||
|
bricks(N, [Line|Lines]) --> {Next is N+1}, brick(N, Line), bricks(Next, Lines).
|
||||||
|
brick(N, N-(X1-X2)-(Y1-Y2)-(Z1-Z2)) -->
|
||||||
|
number(X1), ",", number(Y1), ",", number(Z1), "~",
|
||||||
|
number(X2), ",", number(Y2), ",", number(Z2), "\n".
|
||||||
|
|
||||||
|
% maxheap wrapper. PriX = -Pri, which is the Ztop
|
||||||
|
max_of_heap(H, Pri, Key) :- min_of_heap(H, PriX, Key), Pri is -PriX.
|
||||||
|
add_to_maxheap(H0, Pri, Key, H) :- PriX is -Pri, add_to_heap(H0, PriX, Key, H).
|
||||||
|
get_from_maxheap(H0, Pri, Key, H) :- get_from_heap(H0, PriX, Key, H), Pri is -PriX.
|
||||||
|
|
||||||
|
% Can probably do 2 maps, one by top edges and one by bottom edges and lookup
|
112
22/part2.pl
Normal file
112
22/part2.pl
Normal file
@@ -0,0 +1,112 @@
|
|||||||
|
:- use_module(library(pio)).
|
||||||
|
:- use_module(library(dcg/basics)).
|
||||||
|
:- op(700, xfx, [supports, is_way_above]).
|
||||||
|
:- initialization(main, main).
|
||||||
|
|
||||||
|
main([FileName|_]) :-
|
||||||
|
input(FileName, Bricks),
|
||||||
|
stack(Bricks, StackedBricks),
|
||||||
|
support_listing(StackedBricks, Supporters, SupportMap),
|
||||||
|
length(Bricks, Len), TopBrick is Len - 1,
|
||||||
|
findall(
|
||||||
|
Goners,
|
||||||
|
( between(0, TopBrick, Brick),
|
||||||
|
remove(SupportMap, [Brick], Supporters, Goners)),
|
||||||
|
GonerCounts),
|
||||||
|
sum_list(GonerCounts, Answer),
|
||||||
|
write(Answer), nl.
|
||||||
|
|
||||||
|
remove(_, [], _, -1).
|
||||||
|
remove(SupportMap, [N|ToKills], Supporters, Goners) :-
|
||||||
|
SupportedByN = SupportMap.N,
|
||||||
|
foldl(decrement_supporter_count, SupportedByN, Supporters, NewSupporters),
|
||||||
|
convlist({NewSupporters}/[X, X]>>(is_goner(NewSupporters, X)),
|
||||||
|
SupportedByN, ToKillMore),
|
||||||
|
append(ToKills, ToKillMore, ToKillNext),
|
||||||
|
remove(SupportMap, ToKillNext, NewSupporters, NextGoners),
|
||||||
|
Goners is NextGoners + 1.
|
||||||
|
|
||||||
|
is_goner(Supporters, M) :- Supporters.M =< 0.
|
||||||
|
|
||||||
|
decrement_supporter_count(M, Supporters, NewSupporters) :-
|
||||||
|
NewCount is Supporters.M - 1,
|
||||||
|
NewSupporters = Supporters.put(M, NewCount).
|
||||||
|
|
||||||
|
% StackedBricks is sorted by decreasing top edge
|
||||||
|
support_listing(StackedBricks, SupportedCount, SupportingMap) :-
|
||||||
|
findall(
|
||||||
|
N=SupportedListLen,
|
||||||
|
( append(_, [Brick1|Belows], StackedBricks),
|
||||||
|
supported_by(Brick1, Belows, SupportedList),
|
||||||
|
length(SupportedList, SupportedListLen),
|
||||||
|
Brick1 = N-_-_-_),
|
||||||
|
SupportedLists),
|
||||||
|
SupportedCount = brick{}.put(SupportedLists),
|
||||||
|
sort(2, @=<, StackedBricks, StackSortedByBottoms),
|
||||||
|
findall(
|
||||||
|
M=SupportingList,
|
||||||
|
( append(_, [Brick2|Aboves], StackSortedByBottoms),
|
||||||
|
supporting(Brick2, Aboves, SupportingList),
|
||||||
|
Brick2 = M-_-_-_),
|
||||||
|
SupportingLists),
|
||||||
|
SupportingMap = brick{}.put(SupportingLists).
|
||||||
|
|
||||||
|
% Aboves need to be sorted by increasing bot edge
|
||||||
|
supporting(_Brick, [], []).
|
||||||
|
supporting(Brick, [Above|_], []) :- Above is_way_above Brick, !.
|
||||||
|
supporting(Brick, [Above|Aboves], Supportings) :-
|
||||||
|
supporting(Brick, Aboves, NextSupportings),
|
||||||
|
( Brick supports Above
|
||||||
|
-> Above = N-_-_-_, Supportings = [N|NextSupportings]
|
||||||
|
; Supportings = NextSupportings).
|
||||||
|
|
||||||
|
% Belows need to be sorted decreasing by top edge
|
||||||
|
supported_by(_Brick, [], []).
|
||||||
|
supported_by(Brick, [Below|_], []) :- Brick is_way_above Below, !.
|
||||||
|
supported_by(Brick, [Below|Belows], SupportedBy) :-
|
||||||
|
supported_by(Brick, Belows, NextSupportedBy),
|
||||||
|
( Below supports Brick
|
||||||
|
-> Below = N-_-_-_, SupportedBy = [N|NextSupportedBy]
|
||||||
|
; SupportedBy = NextSupportedBy).
|
||||||
|
|
||||||
|
is_way_above(_-_-_-(Z2bot-_), _-_-_-(_-Z1top)) :- Z2bot > Z1top + 1.
|
||||||
|
supports(Brick1, Brick2) :-
|
||||||
|
overlap(Brick1, Brick2),
|
||||||
|
Brick1 = _-_-_-(_-Z1top), Brick2 = _-_-_-(Z2bot-_), Z2bot =:= Z1top + 1.
|
||||||
|
|
||||||
|
stack(Bricks, StackedBricks) :-
|
||||||
|
empty_heap(H0), foldl(stack1, Bricks, H0, Heap),
|
||||||
|
heap_to_list(Heap, HeapList),
|
||||||
|
maplist([_-Brick, Brick]>>(true), HeapList, StackedBricks).
|
||||||
|
|
||||||
|
stack1(Brick, Heap, NewHeap) :-
|
||||||
|
( max_of_heap(Heap, OldZtop, OldTop), overlap(Brick, OldTop)
|
||||||
|
; empty_heap(Heap), OldZtop is 0),
|
||||||
|
Brick = N-X-Y-(Zbot-Ztop),
|
||||||
|
NewZbot is OldZtop + 1, NewZtop is NewZbot + (Ztop - Zbot),
|
||||||
|
add_to_maxheap(Heap, NewZtop, N-X-Y-(NewZbot-NewZtop), NewHeap),
|
||||||
|
!.
|
||||||
|
stack1(Brick, Heap, NewHeap) :-
|
||||||
|
get_from_maxheap(Heap, LastZtop, LastTopBrick, HeapWithoutTop),
|
||||||
|
stack1(Brick, HeapWithoutTop, NewHeapWithoutTop),
|
||||||
|
add_to_maxheap(NewHeapWithoutTop, LastZtop, LastTopBrick, NewHeap).
|
||||||
|
|
||||||
|
overlap(_-(Xa1-Xa2)-(Ya1-Ya2)-_, _-(Xb1-Xb2)-(Yb1-Yb2)-_) :-
|
||||||
|
Xa1 =< Xb2, Xa2 >= Xb1, Ya1 =< Yb2, Ya2 >= Yb1.
|
||||||
|
|
||||||
|
% input parsing stuff below. Brick indexing is for debugging.
|
||||||
|
input(FileName, SortedBricks) :-
|
||||||
|
phrase_from_file(bricks(0, Bricks), FileName),
|
||||||
|
sort(2, @=<, Bricks, SortedBricks).
|
||||||
|
bricks(_, []) --> eos, !.
|
||||||
|
bricks(N, [Line|Lines]) --> {Next is N+1}, brick(N, Line), bricks(Next, Lines).
|
||||||
|
brick(N, N-(X1-X2)-(Y1-Y2)-(Z1-Z2)) -->
|
||||||
|
number(X1), ",", number(Y1), ",", number(Z1), "~",
|
||||||
|
number(X2), ",", number(Y2), ",", number(Z2), "\n".
|
||||||
|
|
||||||
|
% maxheap wrapper. PriX = -Pri, which is the Ztop
|
||||||
|
max_of_heap(H, Pri, Key) :- min_of_heap(H, PriX, Key), Pri is -PriX.
|
||||||
|
add_to_maxheap(H0, Pri, Key, H) :- PriX is -Pri, add_to_heap(H0, PriX, Key, H).
|
||||||
|
get_from_maxheap(H0, Pri, Key, H) :- get_from_heap(H0, PriX, Key, H), Pri is -PriX.
|
||||||
|
|
||||||
|
% Can probably do 2 maps, one by top edges and one by bottom edges and lookup
|
7
22/test.txt
Normal file
7
22/test.txt
Normal file
@@ -0,0 +1,7 @@
|
|||||||
|
1,0,1~1,2,1
|
||||||
|
0,0,2~2,0,2
|
||||||
|
0,2,3~2,2,3
|
||||||
|
0,0,4~0,2,4
|
||||||
|
2,0,5~2,2,5
|
||||||
|
0,1,6~2,1,6
|
||||||
|
1,1,8~1,1,9
|
141
23/input.txt
Normal file
141
23/input.txt
Normal file
@@ -0,0 +1,141 @@
|
|||||||
|
#.###########################################################################################################################################
|
||||||
|
#...###...#...#...#...###.....#...#...#.................#...#.......#.......###.....#.......#...#.....#####...#...#.....#.....###.....#.....#
|
||||||
|
###.###.#.#.#.#.#.#.#.###.###.#.#.#.#.#.###############.#.#.#.#####.#.#####.###.###.#.#####.#.#.#.###.#####.#.#.#.#.###.#.###.###.###.#.###.#
|
||||||
|
#...#...#.#.#.#.#.#.#.#...#...#.#.#.#.#...........#.....#.#.#.#.....#...#...#...#...#...#...#.#.#.#...#.....#...#.#.#...#...#.#...#...#...#.#
|
||||||
|
#.###.###.#.#.#.#.#.#.#.###.###.#.#.#.###########.#.#####.#.#.#.#######.#.###.###.#####.#.###.#.#.#.###.#########.#.#.#####.#.#.###.#####.#.#
|
||||||
|
#...#.#...#.#.#.#.#.#.#...#.#...#...#.#...###...#.#.....#.#...#.....#...#.#...#...###...#...#.#.#.#.###.......#...#.#.....#.#.#...#.#.....#.#
|
||||||
|
###.#.#.###.#v#.#.#.#.###.#.#.#######.#.#.###.#.#.#####.#.#########.#.###.#.###.#####.#####.#.#.#.#.#########.#.###.#####.#.#.###.#.#.#####.#
|
||||||
|
###...#.#...#.>.#.#.#.#...#...#.......#.#.#...#.#...#...#.....#.....#...#.#...#...#...#.....#.#.#.#.#.....#...#.#...#.....#.#.#...#...#.....#
|
||||||
|
#######.#.###v###.#.#.#.#######.#######.#.#.###.###.#.#######.#.#######.#.###.###.#.###.#####.#.#.#.#.###.#.###.#.###.#####.#.#.#######.#####
|
||||||
|
###...#...#...###.#.#.#.#.......#...###.#.#...#.###.#...#.....#...###...#.#...#...#...#.#...#.#.#.#.#...#.#...#.#...#.#...#.#.#.....#...#...#
|
||||||
|
###.#.#####.#####.#.#.#.#.#######.#.###.#.###.#.###.###.#.#######.###.###.#.###.#####.#.#.#.#.#.#.#.###.#.###.#.###.#.#.#.#.#.#####.#.###.#.#
|
||||||
|
#...#.......#...#.#.#...#...>.>.#.#.#...#.#...#...#.#...#.#.....#...#.#...#...#.....#.#.#.#.#.#.#.#.>.>.#.....#.#...#.#.#.#.#...#...#.###.#.#
|
||||||
|
#.###########.#.#.#.#########v#.#.#.#.###.#.#####.#.#.###.#.###.###.#.#.#####.#####.#.#.#.#.#.#.#.###v#########.#.###.#.#.#.###.#.###.###.#.#
|
||||||
|
#.............#.#.#...#.......#...#.#.#...#...#...#.#.###...#...#...#.#...#...#...#...#.#.#...#.#.###.#...#...#...#...#.#.#.#...#.###...#.#.#
|
||||||
|
###############.#.###.#.###########.#.#.#####.#.###.#.#######.###.###.###.#.###.#.#####.#.#####.#.###.#.#.#.#.#####.###.#.#.#.###.#####.#.#.#
|
||||||
|
#...............#.....#.......#.....#.#...#...#...#.#.#.>.>.#...#.###.#...#...#.#.....#.#.#.....#.#...#.#.#.#...#...#...#.#.#.....#...#...#.#
|
||||||
|
#.###########################.#.#####.###.#.#####.#.#.#.#v#.###.#.###.#.#####.#.#####.#.#.#.#####.#.###.#.#.###.#.###.###.#.#######.#.#####.#
|
||||||
|
#.....................#...#...#...#...#...#...###.#.#...#.#.#...#...#.#.#.>.>.#.#.....#.#.#.#...#.#...#.#.#.#...#.#...###.#.#.......#.......#
|
||||||
|
#####################.#.#.#.#####.#.###.#####.###.#.#####.#.#.#####.#.#.#.#v###.#.#####.#.#.#.#.#.###.#.#.#.#.###.#.#####.#.#.###############
|
||||||
|
#.....................#.#.#.....#.#...#.#...#.#...#.#.....#...###...#.#.#.#.#...#.....#...#...#...###...#...#...#...#...#...#...............#
|
||||||
|
#.#####################.#.#####.#.###.#.#.#.#.#.###.#.###########.###.#.#.#.#.#######.#########################.#####.#.###################.#
|
||||||
|
#...................#...#.......#.#...#...#...#.....#.........#...#...#.#.#.#.#.....#.......#...#...###.........#...#.#.###.......#.........#
|
||||||
|
###################.#.###########.#.#########################.#.###.###.#.#.#.#.###.#######.#.#.#.#.###.#########.#.#.#.###.#####.#.#########
|
||||||
|
#...#...............#...........#...#...#...###...#...........#.....###...#.#.#...#.........#.#.#.#...#...........#...#...#...#...#.........#
|
||||||
|
#.#.#.#########################.#####.#.#.#.###.#.#.#######################.#.###.###########.#.#.###.###################.###.#.###########.#
|
||||||
|
#.#.#...#.........#.....#.......###...#.#.#.#...#.#.....#.....#...#...#...#...###...#...#...#.#.#...#.#...................#...#...#...#.....#
|
||||||
|
#.#.###.#.#######.#.###.#.#########.###.#.#.#.###.#####.#.###.#.#.#.#.#.#.#########.#.#.#.#.#.#.###.#.#.###################.#####.#.#.#.#####
|
||||||
|
#.#...#...#...#...#...#.#.........#...#.#.#.#.#...#...#.#.#...#.#.#.#.#.#.#...#...#...#.#.#.#.#.....#.#.........#...###...#...#...#.#.#.....#
|
||||||
|
#.###.#####.#.#.#####.#.#########.###.#.#.#.#.#.###.#.#v#.#.###.#.#.#.#.#.#.#.#.#.#####v#.#.#.#######.#########.#.#.###.#.###.#.###.#.#####.#
|
||||||
|
#...#...#...#...###...#...........#...#.#.#.#.#...#.#.>.>.#...#.#...#.#.#.#.#...#.....>.>.#...#.......#...#.....#.#...#.#.#...#...#.#.#.....#
|
||||||
|
###.###.#.#########.###############.###.#.#.#.###.#.###v#####.#.#####.#.#.#.###########v#######.#######.#.#.#####.###.#.#.#.#####.#.#.#.#####
|
||||||
|
###...#.#.........#.#.............#...#...#...###...###.....#...#.....#.#...#.....#...#.#.......#.....#.#.#.....#...#.#.#.#...#...#.#.#...###
|
||||||
|
#####.#.#########.#.#.###########.###.#####################.#####.#####.#####.###.#.#.#.#.#######.###.#.#.#####.###.#.#.#.###.#.###.#.###v###
|
||||||
|
#.....#...........#...#...........###.......#.............#.....#.#...#.#.....###...#.#.#...#...#...#.#.#.###...#...#...#.#...#...#.#...>.###
|
||||||
|
#.#####################.###################.#.###########.#####.#.#.#.#.#.###########.#.###.#.#.###.#.#.#.###v###.#######.#.#####.#.#####v###
|
||||||
|
#.................#...#...#.......#...#.....#.#.....#...#...#...#...#...#.........#...#.#...#.#.#...#.#.#.#.>.>...###.....#...###.#.#.....###
|
||||||
|
#################.#.#.###.#.#####.#.#.#.#####.#.###.#.#.###.#.###################.#.###.#.###.#.#.###.#.#.#.#v#######.#######.###.#.#.#######
|
||||||
|
#.................#.#.#...#.#.....#.#...#...#.#.#...#.#...#...#.....#.............#.....#.#...#.#.#...#.#...#.....#...#.....#...#...#.......#
|
||||||
|
#.#################.#.#.###.#.#####.#####.#.#.#.#.###.###.#####.###.#.###################.#.###.#.#.###.#########.#.###.###.###.###########.#
|
||||||
|
#.....#.....###...#.#.#.....#.....#.......#.#.#.#.#...###...###.#...#...#...............#.#.#...#.#...#.###.....#.#...#...#...#.#...........#
|
||||||
|
#####.#.###v###.#.#.#.###########.#########.#.#.#.#.#######.###.#.#####.#.#############.#.#.#.###.###.#.###.###.#.###.###.###.#.#.###########
|
||||||
|
#####...###.>.#.#.#.#.#...###.....#.........#...#...#...###...#.#.....#.#.#.............#...#.....###...#...###.#.#...#...###...#...........#
|
||||||
|
###########v#.#.#.#.#.#.#.###v#####.#################.#.#####.#.#####.#.#.#.#############################.#####.#.#.###.###################.#
|
||||||
|
###...#...#.#.#.#.#.#.#.#.#.>.>.....#.....#...#...###.#.#...#...#.....#...#.........#.......###...........#####.#.#...#.#...........#.......#
|
||||||
|
###.#.#.#.#.#.#.#.#.#.#.#.#.#v#######.###.#.#.#.#.###.#.#.#.#####.#################.#.#####.###.###############.#.###.#.#.#########.#.#######
|
||||||
|
#...#...#...#...#...#...#...#.###...#...#...#.#.#.....#...#.......#...###.........#...#.....#...#.............#...###...#.........#.#...#####
|
||||||
|
#.###########################.###.#.###.#####.#.###################.#.###.#######.#####.#####.###.###########.###################.#.###.#####
|
||||||
|
#...#.........#...#...#.....#...#.#.#...#...#.#.........#...........#...#.....###.#...#...###.....#.........#.....#...............#...#.....#
|
||||||
|
###.#.#######.#.#.#.#.#.###.###.#.#.#.###.#.#.#########.#.#############.#####.###.#.#.###.#########.#######.#####.#.#################.#####.#
|
||||||
|
#...#.#.......#.#.#.#.#...#...#...#...#...#...###...###...#...#.........#...#...#...#.....#.....###.......#.#...#.#...#.....#.......#.......#
|
||||||
|
#.###.#.#######.#.#.#.###.###.#########.#########.#.#######.#.#.#########.#.###.###########.###.#########.#.#.#.#.###.#.###.#.#####.#########
|
||||||
|
#.....#.....###.#.#.#.###.#...#...#...#...###...#.#.###...#.#.#...###...#.#.#...#...###...#...#.#.........#...#...###...#...#.#.....#.......#
|
||||||
|
###########v###.#.#.#.###.#.###.#.#.#.###v###.#.#.#.###.#.#.#.###v###.#.#.#.#.###.#.###.#.###.#.#.#######################.###.#.#####.#####.#
|
||||||
|
#.........#.>.#.#.#.#...#.#.#...#.#.#...>.>.#.#.#.#.#...#.#.#...>.>.#.#.#.#...#...#...#.#.#...#.#.............#.........#.....#.....#.#.....#
|
||||||
|
#.#######.#v#.#.#.#.###.#.#.#.###.#.#####v#.#.#.#.#.#.###.#.#####v#.#.#.#.#####.#####.#.#.#.###.#############.#.#######.###########.#.#.#####
|
||||||
|
#...#...#...#...#.#.###.#.#.#.###...#...#.#.#.#...#.#.###.#.#.....#.#.#.#.....#.#.....#.#.#...#.###...........#.#.......#.......###...#...###
|
||||||
|
###.#.#.#########.#.###.#.#.#.#######.#.#.#.#.#####.#.###.#.#.#####.#.#.#####.#.#.#####.#.###.#.###v###########.#.#######.#####.#########.###
|
||||||
|
###.#.#...###.....#...#...#...###...#.#.#.#.#.....#.#.###...#.....#...#.#...#.#.#.#.....#.#...#...>.>.....#.....#.###...#.....#.........#...#
|
||||||
|
###.#.###.###.#######.###########.#.#.#.#.#.#####.#.#.###########.#####.#.#.#v#.#.#.#####.#.#######v#####.#.#####.###.#.#####.#########.###.#
|
||||||
|
###...###...#.....#...#.......#...#.#.#.#.#.#...#.#...#...#...###.#...#...#.>.>.#.#...#...#.....###.#.....#...#...#...#...###.........#.....#
|
||||||
|
###########.#####.#.###.#####.#.###.#.#.#.#.#.#.#.#####.#.#.#.###.#.#.#######v###.###.#.#######.###.#.#######.#.###.#####.###########.#######
|
||||||
|
#...#.......#...#...###.....#.#...#.#.#...#...#...#.....#...#.....#.#.......#...#.....#...#...#.#...#...#...#.#...#...#...#...#.......#...###
|
||||||
|
#.#.#.#######.#.###########.#.###.#.#.#############.###############.#######.###.#########.#.#.#.#.#####.#.#.#.###.###.#.###.#.#.#######.#.###
|
||||||
|
#.#.#.........#.....#...#...#.....#...#...........#.#...#...........#.......###.........#.#.#...#...#...#.#.#...#...#.#.###.#.#.........#...#
|
||||||
|
#.#.###############.#.#.#.#############.#########.#.#.#.#.###########.#################.#.#.#######.#.###.#.###.###.#.#.###.#.#############.#
|
||||||
|
#.#.........#.......#.#.#.............#...#.......#.#.#...###.........#...............#.#...#...#...#.###.#.###.#...#.#.###.#.#####.........#
|
||||||
|
#.#########.#.#######.#.#############.###.#.#######.#.#######.#########.#############.#.#####.#.#.###.###.#.###.#.###.#.###.#.#####v#########
|
||||||
|
#.#.......#.#...#...#.#.....#.......#.#...#.....###...###...#.........#.............#...#.....#.#...#.....#...#.#...#.#.#...#...#.>.#.......#
|
||||||
|
#.#.#####.#.###.#.#.#.#####.#.#####.#.#.#######.#########.#.#########.#############.#####.#####.###.#########.#.###.#.#.#.#####.#.#v#.#####.#
|
||||||
|
#...#.....#.....#.#...#.....#.....#...#...#.....#...#.....#...#.......#.......#...#...###...#...###.#...#...#...###...#.#.#...#.#.#.#.#.....#
|
||||||
|
#####.###########.#####.#########.#######.#.#####.#.#.#######.#.#######.#####.#.#.###.#####.#.#####.#.#.#.#.###########.#.#.#.#.#.#.#.#.#####
|
||||||
|
#.....#.........#.....#.#.........#...###.#.#...#.#.#.....#...#.......#.....#.#.#.....#...#.#.#.....#.#.#.#...#...#...#...#.#.#...#...#.....#
|
||||||
|
#.#####.#######.#####.#.#.#########.#.###.#.#.#.#.#.#####.#.#########.#####.#.#.#######.#.#.#.#.#####.#.#.###.#.#.#.#.#####.#.#############.#
|
||||||
|
#.....#.#.......#...#.#.#.......###.#.#...#...#.#.#.#...#.#.#.........#...#.#...###.....#.#.#.#.....#.#.#.#...#.#.#.#.#...#.#.....#.......#.#
|
||||||
|
#####.#.#.#######.#.#.#.#######v###.#.#.#######.#.#.#.#.#.#.#.#########.#.#.#######.#####.#.#.#####.#.#.#.#.###.#.#.#.#.#.#v#####.#.#####.#.#
|
||||||
|
#.....#.#...###...#.#.#...#...>.>.#.#.#.....#...#.#.#.#.#.#.#.......###.#...#.....#.....#.#.#.#...#.#.#.#.#...#.#.#.#...#.>.#...#.#.....#.#.#
|
||||||
|
#.#####.###.###.###.#.###.#.###v#.#.#.#####.#.###.#.#.#.#.#.#######v###.#####.###.#####.#.#.#.#.#.#v#.#.#.###.#.#.#.#######v#.#.#.#####.#.#.#
|
||||||
|
#.......#...#...###.#.###...#...#...#.....#.#.#...#.#.#.#.#.......>.>.#.......###.#...#.#...#.#.#.>.>.#...#...#.#.#.......#...#.#.......#...#
|
||||||
|
#########v###.#####.#.#######.###########.#.#.#.###.#.#.#.#########v#.###########.#.#.#.#####.#.###v#######.###.#.#######.#####.#############
|
||||||
|
###...###.>.#.....#.#...#.....#...###.....#.#...###...#.#.#.........#.....###...#.#.#.#.#.....#.#...###...#...#.#.#.....#.#.....###.....#...#
|
||||||
|
###.#.###v#.#####.#.###.#.#####.#.###.#####.###########.#.#.#############.###.#.#v#.#.#.#.#####.#.#####.#.###.#.#.#.###.#.#.#######.###.#.#.#
|
||||||
|
#...#.....#.......#.#...#...#...#...#.....#.........###...#.............#...#.#.>.>.#...#...#...#.......#...#.#.#.#...#.#.#.......#.#...#.#.#
|
||||||
|
#.#################.#.#####.#.#####.#####.#########.###################.###.#.###v#########.#.#############.#.#.#.###.#.#.#######.#.#.###.#.#
|
||||||
|
#...#...#.........#.#.#...#...#####.....#...#.....#.#.........#...#.....###.#...#...###...#...###...........#...#.#...#.#.#.......#.#...#.#.#
|
||||||
|
###.#.#.#.#######.#.#.#.#.#############.###.#.###.#.#.#######.#.#.#.#######.###.###.###.#.#######.###############.#.###.#.#.#######.###.#.#.#
|
||||||
|
###...#.#.#.......#...#.#...............###...#...#.#.......#...#...#.....#.....###.....#.....#...#.............#...###...#.......#.#...#.#.#
|
||||||
|
#######.#.#.###########.#######################.###.#######.#########.###.###################.#.###.###########.#################.#.#.###.#.#
|
||||||
|
#.....#...#...........#.......................#.....#.......#.....#...#...#...............#...#.....#...........###.....###...###...#.....#.#
|
||||||
|
#.###.###############.#######################.#######.#######.###.#.###.###.#############.#.#########.#############.###.###.#.#############.#
|
||||||
|
#...#.............#...###...............#...#.###...#.#.....#.#...#.#...###.............#.#.#.........#...#...#.....#...#...#...............#
|
||||||
|
###.#############.#.#####.#############.#.#.#.###.#.#.#.###.#.#.###.#.#################.#.#.#.#########.#.#.#.#.#####.###.###################
|
||||||
|
#...#...........#.#.#...#.............#.#.#.#.#...#.#...###...#.....#...#...#...........#...#...#.....#.#.#.#...#...#.#...#...#.............#
|
||||||
|
#.###.#########.#.#.#.#.#############.#.#.#.#.#.###.###################.#.#.#.#################.#.###.#.#.#.#####.#.#.#.###.#.#.###########.#
|
||||||
|
#.....#.........#...#.#.###...........#...#...#...#.....###...#...#...#...#.#.................#...###...#...#...#.#...#.....#...#...........#
|
||||||
|
#######.#############.#.###.#####################.#####.###.#.#.#.#.#.#####.#################.###############.#.#.###############.###########
|
||||||
|
###...#...........#...#...#...#.......###...#...#.....#...#.#.#.#...#.#...#.#.................###.............#.#.#...#...#...###...........#
|
||||||
|
###.#.###########.#.#####.###.#.#####.###.#.#.#.#####.###.#.#.#.#####.#.#.#.#.###################.#############.#.#.#.#.#.#.#.#############.#
|
||||||
|
#...#...#...#.....#...#...###.#.#.....#...#...#.#...#...#.#.#.#.#...#...#...#...............#...#.......#.....#...#.#.#.#.#.#.###...#.......#
|
||||||
|
#.#####.#.#.#v#######.#.#####.#.#.#####.#######.#.#.###.#.#.#.#v#.#.#######################.#.#.#######.#.###.#####.#.#.#.#.#.###.#.#.#######
|
||||||
|
#...#...#.#.#.>.#...#.#.....#...#.....#.#.......#.#.###.#.#.#.>.>.#.#.......#...#.........#.#.#.#.....#...###.....#.#.#.#.#.#.#...#...#.....#
|
||||||
|
###.#.###.#.#v#.#.#.#.#####.#########.#.#.#######.#.###.#.#.###v###.#.#####.#.#.#.#######.#.#.#.#.###.###########.#.#.#.#.#.#.#.#######.###.#
|
||||||
|
#...#...#.#.#.#.#.#...#.....#.........#.#.......#.#.#...#...#...###...#...#.#.#.#.......#...#.#.#...#...#.........#.#.#.#.#.#.#.......#.#...#
|
||||||
|
#.#####.#.#.#.#.#.#####.#####.#########.#######.#.#.#.#######.#########.#.#.#.#.#######.#####.#.###.###.#.#########.#.#.#.#.#.#######.#.#.###
|
||||||
|
#.....#...#.#.#.#.#.....#...#...#.....#.#.......#.#.#.......#.....#.....#...#.#.........#...#.#.###.#...#.....#...#.#.#.#...#.......#...#...#
|
||||||
|
#####.#####.#.#.#.#.#####.#.###.#.###.#.#.#######.#.#######.#####.#.#########.###########.#.#.#.###.#.#######v#.#.#.#.#.###########.#######.#
|
||||||
|
#.....#...#...#.#.#.#...#.#...#.#...#...#...#...#.#.#.......###...#.#.......#.......#...#.#.#.#.#...#...#...>.>.#.#.#.#.......#.....#...#...#
|
||||||
|
#.#####.#.#####.#.#.#.#.#.###.#.###.#######.#.#.#.#.#.#########.###.#.#####.#######.#.#.#.#.#.#.#.#####.#.###v###.#.#.#######.#.#####.#.#v###
|
||||||
|
#.......#.....#...#...#.#.#...#.....#.......#.#...#.#...#.......#...#.#.....#.......#.#...#.#.#.#.#...#...#...#...#.#.#...#...#...#...#.>.###
|
||||||
|
#############.#########.#.#.#########.#######.#####.###.#.#######.###.#.#####.#######.#####.#.#.#.#.#.#####.###.###.#.#.#.#.#####.#.#####v###
|
||||||
|
#...#.....#...###.......#.#.....#...#.......#.....#.#...#.......#...#.#.#...#.......#.....#...#.#.#.#.....#.#...#...#.#.#.#...#...#.#.....###
|
||||||
|
#.#.#.###.#.#####.#######.#####.#.#.#######.#####.#.#.#########.###.#.#.#.#.#######v#####.#####.#.#.#####.#.#.###.###.#.#.###.#.###.#.#######
|
||||||
|
#.#.#...#...#.....#.....#.#.....#.#.#...#...#...#.#.#.#.........###.#.#.#.#.#...#.>.>.....#.....#.#.....#.#.#...#.###.#.#.#...#.....#.....###
|
||||||
|
#.#.###.#####.#####.###.#.#.#####.#.#.#.#v###.#.#.#.#.#.###########.#.#.#.#.#.#.#.#v#######.#####.#####.#.#.###.#.###.#.#.#.#############.###
|
||||||
|
#.#.....#...#...#...#...#.#...#...#...#.>.>...#...#...#...........#.#.#.#.#.#.#...#.......#.#...#.#.....#.#.###.#...#...#...###...###...#...#
|
||||||
|
#.#######.#.###.#.###.###.###.#.#########v#######################.#.#.#.#.#.#.###########.#.#.#.#.#.#####.#.###.###.###########.#.###.#.###.#
|
||||||
|
#.........#...#.#...#...#.#...#.###.....#.........#.......#.......#...#...#...#...........#...#.#.#.....#.#...#.....#.....#...#.#.#...#...#.#
|
||||||
|
#############.#.###.###.#.#.###.###.###.#########.#.#####.#.###################.###############.#.#####.#.###.#######.###.#.#.#.#.#.#####.#.#
|
||||||
|
#.............#...#.###...#.....#...###.#.........#.....#.#...#...#.....#.....#...............#.#.#.....#...#...#...#.#...#.#.#.#...#####.#.#
|
||||||
|
#.###############.#.#############.#####.#.#############.#.###.#.#.#.###.#.###.###############.#.#.#.#######.###.#.#.#.#.###.#.#.#########.#.#
|
||||||
|
#...............#.#.#...#...#.....#...#.#.....#.........#.....#.#.#...#...#...#...........#...#...#.......#.....#.#...#.#...#.#.........#...#
|
||||||
|
###############.#.#.#.#.#.#.#.#####.#.#.#####.#.###############.#.###.#####.###.#########.#.#############.#######.#####.#.###.#########.#####
|
||||||
|
#.........#.....#...#.#.#.#.#.....#.#.#.......#.........#.....#.#.#...#.....###.........#...###...........###...#...#...#.#...#...#.....#...#
|
||||||
|
#.#######.#.#########.#.#.#.#####.#.#.#################.#.###.#.#.#.###.###############.#######.#############.#.###.#.###.#.###.#.#v#####.#.#
|
||||||
|
#.#...###...#...###...#.#.#...#...#.#.#.....#...#...#...#...#.#.#.#...#.#...#...#####...#.....#...........#...#...#.#.#...#...#.#.>.#...#.#.#
|
||||||
|
#.#.#.#######.#.###.###.#.###.#.###.#.#.###.#.#.#.#.#.#####.#.#.#.###.#.#.#.#.#.#####v###.###.###########.#.#####.#.#.#.#####.#.###v#.#.#.#.#
|
||||||
|
#...#.....#...#.....#...#.#...#.###.#.#...#.#.#.#.#.#...###.#.#.#.#...#.#.#.#.#...#.>.>.#.#...#...#.......#.....#...#.#...###.#.#...#.#.#.#.#
|
||||||
|
#########.#.#########.###.#.###v###.#.###.#.#.#.#.#.###v###.#.#.#.#.###.#.#.#.###.#.###.#.#.###.#.#.###########.#####.###.###.#.#.###.#.#.#.#
|
||||||
|
#...#.....#.........#...#.#.#.>.>.#.#...#.#.#.#.#.#.#.>.>.#.#.#.#.#.#...#.#.#...#.#...#...#...#.#.#.....#.....#.....#...#.#...#.#.#...#...#.#
|
||||||
|
#.#.#.#############.###.#.#.#.###.#.###.#.#.#.#.#.#.#.###.#.#.#.#.#.#.###.#.###.#.###.#######.#.#.#####v#.###.#####.###.#.#.###.#.#.#######.#
|
||||||
|
#.#.#.......#...###...#...#.#.#...#...#.#.#.#.#.#.#.#.###.#.#.#.#.#.#...#.#.#...#.#...#.......#.#...#.>.>.###...#...###.#.#...#.#.#.#.......#
|
||||||
|
#.#.#######.#.#.#####.#####.#.#.#####.#.#.#.#.#.#.#.#.###.#.#.#.#.#.###.#.#.#.###.#.###.#######.###.#.#########.#.#####.#.###.#.#.#.#.#######
|
||||||
|
#.#.........#.#.#...#.....#...#...#...#...#.#.#...#.#.#...#.#.#.#.#.#...#.#.#...#.#.###.#...#...#...#...#.......#.....#.#.#...#.#.#.#.#...###
|
||||||
|
#.###########.#.#.#.#####.#######.#.#######.#.#####.#.#.###.#.#.#.#.#.###.#.###.#.#.###.#.#.#.###.#####.#.###########.#.#.#.###.#.#.#.#.#.###
|
||||||
|
#.#...#...#...#.#.#.#...#.......#.#.....#...#.....#.#.#...#.#.#.#.#.#...#.#.#...#.#...#.#.#.#.###...#...#.......#.....#...#...#.#...#...#...#
|
||||||
|
#.#.#.#.#.#.###.#.#.#.#.#######.#.#####.#.#######.#.#.###.#.#.#.#.#.###.#.#.#.###.###.#.#.#.#.#####.#.#########.#.###########.#.###########.#
|
||||||
|
#.#.#.#.#.#...#.#.#.#.#.#.......#.#.....#.#...#...#.#...#.#.#.#.#.#.###.#.#.#...#...#.#.#.#.#...#...#.......###.#.......#...#...###...#...#.#
|
||||||
|
#.#.#.#.#.###.#.#.#.#.#.#.#######.#.#####.#.#.#.###.###.#.#.#.#.#.#.###.#.#.###.###.#.#.#.#.###.#.#########.###.#######.#.#.#######.#.#.#.#.#
|
||||||
|
#.#.#.#.#.#...#.#.#.#.#.#.......#.#.....#.#.#.#.#...#...#.#.#.#.#.#.#...#.#...#...#.#.#.#.#...#.#...#.....#...#...#.....#.#.........#...#...#
|
||||||
|
#.#.#.#.#.#.###.#.#.#.#.#######.#.#####.#.#.#.#.#.###.###.#.#.#.#.#.#.###.###.###.#.#.#.#.###.#.###.#.###.###.###.#.#####.###################
|
||||||
|
#...#...#...###...#...#.........#.......#...#...#.....###...#...#...#.....###.....#...#...###...###...###.....###...#####...................#
|
||||||
|
###########################################################################################################################################.#
|
51
23/part1.pl
Normal file
51
23/part1.pl
Normal file
@@ -0,0 +1,51 @@
|
|||||||
|
:- use_module(library(pio)).
|
||||||
|
:- use_module(library(dcg/basics)).
|
||||||
|
:- initialization(main, main).
|
||||||
|
|
||||||
|
main([FileName|_]) :-
|
||||||
|
input(FileName, Map),
|
||||||
|
nth1(1, Map, Row1), nth1(StartY, Row1, '.'),
|
||||||
|
findall(N, route(Map, visited{}, 1-StartY, N), Ns),
|
||||||
|
max_list(Ns, Answer),
|
||||||
|
format('~w <- ~w', [Answer, Ns]), nl.
|
||||||
|
|
||||||
|
route(Map, _, X-_, 0) :- length(Map, Height), X =:= Height.
|
||||||
|
route(Map, Visiteds, X-Y, N) :-
|
||||||
|
Key is X*1000 + Y, NextVisiteds = Visiteds.put(Key, true),
|
||||||
|
neighbor(Map, X-Y, X1-Y1, Dist),
|
||||||
|
NeighborKey is X1*1000 + Y1, \+ _= Visiteds.get(NeighborKey),
|
||||||
|
route(Map, NextVisiteds, X1-Y1, N1),
|
||||||
|
N is N1 + Dist.
|
||||||
|
|
||||||
|
neighbor(Map, X-Y, NextX-NextY, Dist) :-
|
||||||
|
( 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, Cell1),
|
||||||
|
( Cell1 = '.' -> NextX = X1, NextY = Y1, Dist = 1
|
||||||
|
; Cell1 = '>' -> NextX = X1, NextY is Y1 + 1, Dist = 2
|
||||||
|
; Cell1 = 'v' -> NextX is X1 + 1, NextY = Y1, Dist = 2
|
||||||
|
),
|
||||||
|
( NextX =\= X; NextY =\= Y ).
|
||||||
|
|
||||||
|
% input parsing stuff below. Brick indexing is for debugging.
|
||||||
|
input(FileName, Map) :- phrase_from_file(lines(Map), FileName).
|
||||||
|
|
||||||
|
lines([]) --> eos, !.
|
||||||
|
lines([Line|Lines]) --> line(Line), lines(Lines).
|
||||||
|
|
||||||
|
line([]) --> ("\n"; eos), !.
|
||||||
|
line([C|Chars]) --> [Ascii], line(Chars), {atom_codes(C, [Ascii])}.
|
||||||
|
|
||||||
|
% debug
|
||||||
|
print(Map) :-
|
||||||
|
findall(
|
||||||
|
X,
|
||||||
|
( nth1(X, Map, Line),
|
||||||
|
format('~3d', [X]), write(" "),
|
||||||
|
atomic_list_concat(Line, Str), write(Str), nl
|
||||||
|
),
|
||||||
|
_),
|
||||||
|
nl.
|
90
23/part2.pl
Normal file
90
23/part2.pl
Normal 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.
|
23
23/test.txt
Normal file
23
23/test.txt
Normal file
@@ -0,0 +1,23 @@
|
|||||||
|
#.#####################
|
||||||
|
#.......#########...###
|
||||||
|
#######.#########.#.###
|
||||||
|
###.....#.>.>.###.#.###
|
||||||
|
###v#####.#v#.###.#.###
|
||||||
|
###.>...#.#.#.....#...#
|
||||||
|
###v###.#.#.#########.#
|
||||||
|
###...#.#.#.......#...#
|
||||||
|
#####.#.#.#######.#.###
|
||||||
|
#.....#.#.#.......#...#
|
||||||
|
#.#####.#.#.#########v#
|
||||||
|
#.#...#...#...###...>.#
|
||||||
|
#.#.#v#######v###.###v#
|
||||||
|
#...#.>.#...>.>.#.###.#
|
||||||
|
#####v#.#.###v#.#.###.#
|
||||||
|
#.....#...#...#.#.#...#
|
||||||
|
#.#########.###.#.#.###
|
||||||
|
#...###...#...#...#.###
|
||||||
|
###.###.#.###v#####v###
|
||||||
|
#...#...#.#.>.>.#.>.###
|
||||||
|
#.###.###.#.###.#.#v###
|
||||||
|
#.....###...###...#...#
|
||||||
|
#####################.#
|
300
24/input.txt
Normal file
300
24/input.txt
Normal file
@@ -0,0 +1,300 @@
|
|||||||
|
320870677764563, 335750934489987, 282502845957937 @ -40, -24, 10
|
||||||
|
219235623600942, 408022798608755, 245679379684914 @ 127, -45, 66
|
||||||
|
171834827764229, 225154401936948, 232302441670972 @ -122, -521, 95
|
||||||
|
399408000414510, 365475460204869, 325051385807860 @ -110, -35, -35
|
||||||
|
382531108862210, 229601570088564, 368913364777462 @ -119, 127, -107
|
||||||
|
149909452680584, 220522474055239, 215024246295982 @ 198, -73, 190
|
||||||
|
234205136344037, 217641496634781, 245767047966874 @ 50, 126, 57
|
||||||
|
154245972353770, 254717416188789, 165260557711000 @ 191, 37, 220
|
||||||
|
369540770291762, 356366422983125, 93794725449906 @ -15, 24, 216
|
||||||
|
226276010405492, 209995120939680, 310956910929616 @ -25, 99, -149
|
||||||
|
268638972773930, 269486309393569, 248987782583720 @ -21, 26, 50
|
||||||
|
361178860307414, 374454477296229, 399143377389604 @ -6, 7, -83
|
||||||
|
202257892924214, 270170054947827, 246834210935308 @ -51, -252, 15
|
||||||
|
277024186353899, 205267962954879, 342506025642424 @ -178, 112, -245
|
||||||
|
285916480116416, 388917502500415, 279882602663788 @ 60, -19, 31
|
||||||
|
145282209670550, 224173312800453, 249344095056520 @ 236, -215, -56
|
||||||
|
208447142984970, 231890691603339, 298351303820520 @ 61, 67, -75
|
||||||
|
161755191939510, 174118992755389, 243050626677760 @ 55, 212, -35
|
||||||
|
318313224606524, 381722223896712, 347955048413278 @ 27, -11, -39
|
||||||
|
305673336971274, 370290487695419, 422379794963756 @ 29, -13, -129
|
||||||
|
328180566576385, 213760869384648, 251670316230916 @ -34, 151, 55
|
||||||
|
230518001853761, 324986205789729, 203877601589479 @ 28, -118, 142
|
||||||
|
144072041563378, 90185316765691, 182011664702202 @ 217, 456, 233
|
||||||
|
185151810500310, 221100644135477, 245109663655204 @ 91, 60, 43
|
||||||
|
373850664858040, 293374889307828, 175368782897875 @ -89, 49, 154
|
||||||
|
328502469179556, 412212496772722, 260184335059001 @ 7, -55, 50
|
||||||
|
223132851962520, 223914729021163, 327185491912702 @ 76, 119, -80
|
||||||
|
198895082054102, 271680428770347, 234537752577403 @ 69, -56, 76
|
||||||
|
252972518344820, 389690617977839, 374418656922750 @ -153, -532, -403
|
||||||
|
192164383825878, 82139993028623, 120091254828574 @ 55, 519, 466
|
||||||
|
156955794165198, 191592767579977, 233413147425100 @ 64, -100, 79
|
||||||
|
165008537629302, 183661085826489, 248545405693408 @ -68, 52, -182
|
||||||
|
373129120338738, 368249004318254, 320596847750514 @ -71, -33, -27
|
||||||
|
275929675024853, 194671117708439, 343770846827540 @ -120, 152, -201
|
||||||
|
173580271204630, 203823601071863, 239810510444710 @ -139, -204, -11
|
||||||
|
189671912659874, 259317534315745, 248510443915264 @ 33, -150, 16
|
||||||
|
172552678412603, 76290981681303, 250440858733279 @ 148, 428, 40
|
||||||
|
127051067028085, 224685590300118, 27951449994759 @ 286, 13, 860
|
||||||
|
231732307446206, 111700054896778, 381283992852198 @ 93, 285, -115
|
||||||
|
196775286792290, 250152880582527, 165723767492786 @ -39, -179, 422
|
||||||
|
198162199765890, 326088593352961, 293740956136336 @ 121, -46, -20
|
||||||
|
181567111184732, 234940800451055, 284267674024586 @ 60, -61, -144
|
||||||
|
343894774969218, 251446196757409, 324645022076636 @ -155, 62, -88
|
||||||
|
154322997480050, 321666831724779, 170189917536370 @ 193, -37, 182
|
||||||
|
269135111242526, 422914585575117, 44342942222152 @ 18, -177, 368
|
||||||
|
174234267626414, 206600028766149, 247203043132680 @ 48, 7, -6
|
||||||
|
301438105099034, 196682335636041, 242355832704292 @ -37, 168, 65
|
||||||
|
52382227177535, 137282743662489, 90222907787860 @ 304, 242, 231
|
||||||
|
287281969399048, 189476966098213, 378020645240557 @ -65, 174, -200
|
||||||
|
329003376176988, 435916939135103, 202654481427582 @ 20, -61, 110
|
||||||
|
183674690012150, 191781746274329, 227891029018460 @ -72, 68, 123
|
||||||
|
366646274315090, 480902014044223, 227077161038699 @ -39, -136, 86
|
||||||
|
209229044274730, 190608724313417, 187400386715900 @ 136, 185, 129
|
||||||
|
261618567625850, 400563976485889, 144954360500820 @ 12, -178, 228
|
||||||
|
264216158312450, 334972046672343, 305882984918398 @ 41, -21, -22
|
||||||
|
466350980510496, 230380017371646, 332577962045002 @ -125, 145, -23
|
||||||
|
266431863912996, 290874605525783, 509046541048002 @ -10, -7, -418
|
||||||
|
132224880034084, 176627699412807, 220106637500956 @ 263, 196, 127
|
||||||
|
300469550083263, 426413462614973, 209018833990362 @ 40, -66, 105
|
||||||
|
311030442665825, 223508982594159, 255317416767895 @ -72, 120, 42
|
||||||
|
517047998068110, 239075216009569, 372653857063880 @ -166, 138, -60
|
||||||
|
170904351760141, 270353076576237, 209565974699113 @ 128, -122, 160
|
||||||
|
290157904191917, 379443622665012, 427270086392227 @ 42, -29, -140
|
||||||
|
173867272759940, 201864684820176, 243051222520867 @ 31, 15, 12
|
||||||
|
241502019378006, 260671504666073, 310914265664160 @ 100, 108, -6
|
||||||
|
271283475933083, 246303519670521, 255211216146782 @ 78, 130, 57
|
||||||
|
388021238794645, 216488511621914, 298488270181975 @ -184, 135, -26
|
||||||
|
335856195264706, 301351728593361, 283609538939852 @ -7, 61, 23
|
||||||
|
247561156076045, 271177759902429, 244748631170605 @ -154, -146, 38
|
||||||
|
276696780291055, 333024920521025, 305604257091590 @ -134, -214, -111
|
||||||
|
190855793421101, 153164710734612, 127049898278632 @ 28, 293, 523
|
||||||
|
443492983001086, 525011795745025, 422682967987684 @ -88, -142, -107
|
||||||
|
501694282984570, 467198174503214, 473605302628600 @ -239, -163, -221
|
||||||
|
335390812504546, 362603263870063, 309797115541008 @ -23, -24, -13
|
||||||
|
202304759605965, 213333718249183, 246143159635191 @ -94, -12, 8
|
||||||
|
177782812262045, 206513164309989, 236356130506975 @ -40, -66, 54
|
||||||
|
388319746430552, 513573144680169, 445043621805025 @ -53, -158, -146
|
||||||
|
194320135718360, 233248821891459, 202359964193575 @ 107, 80, 144
|
||||||
|
216771660023300, 171002079515199, 475642130495202 @ -54, 217, -838
|
||||||
|
234091788605150, 329933100121089, 222620683383130 @ -105, -358, 118
|
||||||
|
270608669158866, 301404666421918, 259633482142765 @ -7, -15, 34
|
||||||
|
257130045685842, 324015469970377, 192079653460084 @ 29, -36, 145
|
||||||
|
177501821940794, 206397724473173, 236757119637960 @ 117, 108, 69
|
||||||
|
258491080589540, 328713305053641, 347685992911240 @ 96, 54, -31
|
||||||
|
300241327661250, 317780474139381, 395082844930752 @ -119, -101, -264
|
||||||
|
166701742849052, 170048803933150, 279009405626079 @ 99, 231, -190
|
||||||
|
232167716240370, 309180901229489, 364847973540700 @ 82, 9, -110
|
||||||
|
272472196902758, 211620478899945, 169919557370053 @ 13, 146, 176
|
||||||
|
155257558622970, 215412500302073, 224645492519800 @ 151, -144, 154
|
||||||
|
165140630756911, 183872378821537, 189847493429559 @ 88, 138, 392
|
||||||
|
222481991685145, 381866546445014, 402626810510600 @ 106, -67, -141
|
||||||
|
195176269606298, 148450429795245, 252663005801584 @ 75, 275, 26
|
||||||
|
208907792419362, 350794355038735, 294502109591690 @ 89, -129, -36
|
||||||
|
163731694743470, 222695183641289, 249450695542684 @ 126, -48, -5
|
||||||
|
209099853718520, 241562956480389, 283990363935025 @ 11, -10, -82
|
||||||
|
161530626632686, 237419576114933, 319638596916810 @ 175, 68, -106
|
||||||
|
159481040133596, 158629339034865, 210459590512168 @ 58, 434, 405
|
||||||
|
123469770101234, 257476537375091, 234494092643914 @ 273, -27, 76
|
||||||
|
292278978987570, 239866606409241, 199533371820276 @ -149, 43, 162
|
||||||
|
380447223996379, 374529302108629, 538133423675973 @ -100, -58, -318
|
||||||
|
192314223519770, 237171949514439, 327368019710830 @ 101, 57, -140
|
||||||
|
164228470258070, 152786375782989, 233781247174300 @ 40, 443, 75
|
||||||
|
172857923598290, 361486110825537, 216740814450508 @ 111, -514, 143
|
||||||
|
215968779962610, 275822816042585, 255939903446892 @ 71, 5, 35
|
||||||
|
224072378959655, 219760339836420, 250116723554098 @ -94, 25, 13
|
||||||
|
341826278658070, 323384093598739, 317050311826650 @ -197, -105, -94
|
||||||
|
358061026812176, 333431655135129, 501927131792690 @ -36, 22, -226
|
||||||
|
362057930007880, 364175461079693, 291565175187926 @ -44, -16, 12
|
||||||
|
254480531220540, 261585394784649, 315221878253440 @ -61, -14, -125
|
||||||
|
239345238738065, 232921068298368, 52215243122876 @ 66, 115, 351
|
||||||
|
174121671759746, 253098934851105, 265802255418028 @ 127, -32, -18
|
||||||
|
336492062606489, 22227894726016, 480141325107541 @ -6, 371, -194
|
||||||
|
159311142016790, 144443435124894, 222453887189935 @ 117, 461, 172
|
||||||
|
264027680313710, 285411784271013, 175063578354076 @ 91, 96, 135
|
||||||
|
162835672903750, 194990375099697, 241394520022980 @ 16, -74, -31
|
||||||
|
306159412517226, 349026413686307, 514099559091684 @ 29, 11, -229
|
||||||
|
361674598186586, 541486806728355, 358055452228678 @ -143, -392, -123
|
||||||
|
387616545088370, 458824259273879, 187757363559110 @ -39, -84, 125
|
||||||
|
169441075829130, 63304826516582, 231410285377464 @ 161, 425, 83
|
||||||
|
25747427352685, 141237559854084, 110612909830610 @ 344, 241, 221
|
||||||
|
224941003813670, 293572180292369, 343069410375740 @ 66, -10, -117
|
||||||
|
230260619234115, 246354839816571, 227616486618513 @ -64, -32, 98
|
||||||
|
122374062836488, 129460749486351, 248910762647847 @ 283, 340, 32
|
||||||
|
257926150662427, 296587117999220, 269098859305457 @ 52, 35, 30
|
||||||
|
356168259600515, 496710404337273, 355767267199108 @ -164, -366, -137
|
||||||
|
499138453043411, 241721200046286, 383865072357541 @ -150, 135, -72
|
||||||
|
354351640576530, 333708262751349, 240972379666960 @ -43, 13, 70
|
||||||
|
414646107949045, 490351310759496, 391588852973424 @ -74, -125, -85
|
||||||
|
182510517018696, 196037200020145, 254600487937890 @ -88, 18, -106
|
||||||
|
203067123583136, 283551214233744, 250446375434740 @ 75, -53, 39
|
||||||
|
252810044109290, 237002938926201, 75981980028076 @ 46, 109, 315
|
||||||
|
336333829055570, 388442894436689, 291634558906300 @ 18, -7, 22
|
||||||
|
395076042194198, 359212075803360, 298728466148813 @ -51, 13, 12
|
||||||
|
158785266271843, 234903117684176, 269092839411151 @ 82, -559, -374
|
||||||
|
309601884465086, 412842250362681, 306976533326464 @ -32, -144, -28
|
||||||
|
294030373468330, 396089847565113, 280064088752700 @ 46, -35, 29
|
||||||
|
331545729822620, 256988945451264, 265060418520925 @ -81, 75, 30
|
||||||
|
190647571880991, 101485268249820, 252635532573594 @ 68, 439, 17
|
||||||
|
286448585468055, 517134354733154, 186333249962180 @ 38, -205, 135
|
||||||
|
153617721701820, 178833230713415, 252336845995825 @ 151, 156, -146
|
||||||
|
337398961767230, 377411392580169, 378982185725528 @ 6, -8, -72
|
||||||
|
195250366116408, 193178125048569, 472013133254368 @ 50, 142, -707
|
||||||
|
185967157561902, 242667813003287, 287987773258452 @ 59, -61, -133
|
||||||
|
178872203125295, 113519768889594, 13727599749985 @ 166, 275, 340
|
||||||
|
319415310905105, 435440863922004, 41521512187915 @ -32, -155, 342
|
||||||
|
251586814655345, 344865748855428, 269612063292298 @ 26, -89, 17
|
||||||
|
269246730728402, 271578178622193, 279439460804668 @ -88, -31, -32
|
||||||
|
135533496860438, 278285521115205, 214907869435324 @ 219, 68, 103
|
||||||
|
276812075909858, 466037129861747, 395316831883066 @ 57, -127, -104
|
||||||
|
236930960411706, 243177338144695, 356325165559341 @ 65, 96, -112
|
||||||
|
380460503419598, 324370013927517, 371388836906704 @ -82, 19, -90
|
||||||
|
427398362574065, 546630525363764, 426883192743950 @ -72, -163, -111
|
||||||
|
177868966679682, 217731875079305, 213146155346340 @ -143, -315, 324
|
||||||
|
290284806845247, 119840422044798, 184970876358517 @ -52, 301, 166
|
||||||
|
340880756829785, 288068023675589, 315817226541790 @ -36, 62, -23
|
||||||
|
185573708687938, 225251128591507, 128884524503130 @ 137, 113, 264
|
||||||
|
186685995213874, 219001269459803, 214926674026246 @ -47, -91, 202
|
||||||
|
199184710396145, 215180367747336, 203151616358728 @ -174, -101, 307
|
||||||
|
171076784522930, 146981293827499, 60098514063820 @ 177, 233, 271
|
||||||
|
270206225348270, 249412790853189, 300466015667500 @ -44, 51, -57
|
||||||
|
234689751989636, 218746599271293, 241908203795056 @ -60, 68, 53
|
||||||
|
336725151372856, 147342236950433, 199748653670338 @ -16, 234, 118
|
||||||
|
171003890899833, 195424392282388, 258493155527802 @ -28, -15, -187
|
||||||
|
149412455352770, 330619018965931, 331721336873716 @ 201, -121, -125
|
||||||
|
290849090590752, 279180853742381, 288711681503108 @ -65, 6, -25
|
||||||
|
163782604097570, 201369533990859, 276104464321110 @ -39, -239, -634
|
||||||
|
383466451055234, 487708948895409, 243501681722620 @ -31, -108, 69
|
||||||
|
278873443047818, 270949972855161, 295581748376284 @ -178, -79, -103
|
||||||
|
275483328204728, 359753199304611, 281769098655988 @ 55, -12, 23
|
||||||
|
155550526665711, 194627020895100, 222697531404203 @ 142, 13, 182
|
||||||
|
272548165774242, 183113072391357, 219832002893320 @ -71, 184, 109
|
||||||
|
365051505965124, 358358344604291, 369447127951585 @ -13, 20, -56
|
||||||
|
226749420175018, 136295903261165, 369261631685233 @ 49, 278, -188
|
||||||
|
347337565099555, 206264170469455, 435941166700880 @ -14, 168, -141
|
||||||
|
195173574972300, 288059724160556, 314475702179696 @ 131, 29, -45
|
||||||
|
290901181489325, 322228161855234, 270950972726635 @ -44, -53, 14
|
||||||
|
160976286106050, 217995178956129, 225852181163340 @ 97, -185, 147
|
||||||
|
194862657814148, 311950660223715, 37627659899164 @ 58, -229, 695
|
||||||
|
187756065196068, 189433672405609, 237753933445096 @ 95, 162, 67
|
||||||
|
314662593059606, 457342368237267, 280627472484196 @ 19, -109, 27
|
||||||
|
267078738018370, 395588665670289, 329017002090900 @ 41, -98, -51
|
||||||
|
198453105662012, 204180092239497, 125941083981442 @ 60, 118, 388
|
||||||
|
325515244603174, 193963026836233, 83616169017080 @ -40, 176, 284
|
||||||
|
306120915804898, 216669056599065, 224566702076996 @ -47, 136, 93
|
||||||
|
262952419990622, 189332097246832, 339944472270492 @ -123, 161, -225
|
||||||
|
430090980639770, 542562712338489, 554533524742700 @ -264, -407, -453
|
||||||
|
153428204187620, 258973851297351, 146351712685552 @ 176, -321, 621
|
||||||
|
267157324234725, 253300767826406, 247830886471870 @ -44, 39, 49
|
||||||
|
172772522836510, 205083962044941, 244745265268276 @ -34, -101, -35
|
||||||
|
196853173091800, 235959594193899, 277157185859790 @ 124, 103, 8
|
||||||
|
252233329257530, 150771238871169, 214260239540880 @ 99, 226, 98
|
||||||
|
260490329235010, 420724181636745, 466676682577804 @ 41, -152, -257
|
||||||
|
184101537716370, 206927897278749, 158088282864140 @ 61, 73, 383
|
||||||
|
371707477810145, 476446047030789, 395602648788850 @ -32, -114, -91
|
||||||
|
274680779584238, 328310092921155, 187337441960652 @ 27, -11, 143
|
||||||
|
199636505804290, 225659286596792, 281910746142349 @ -119, -121, -230
|
||||||
|
401663498069128, 324128314956575, 308385593557516 @ -122, 11, -17
|
||||||
|
306117741289910, 332540256531302, 198589750550180 @ 21, 21, 119
|
||||||
|
303752166745505, 329304097065024, 339365273624437 @ 16, 17, -48
|
||||||
|
154413399453767, 281779422496148, 262521206679621 @ 162, -631, -148
|
||||||
|
236991415564934, 260590948682271, 232297491880996 @ -113, -105, 83
|
||||||
|
169296005492162, 193449873692505, 238539375195412 @ -55, -36, 13
|
||||||
|
283385836439282, 243921272996229, 338818675191694 @ -207, -8, -242
|
||||||
|
360218974366508, 393941699996637, 490793199709315 @ -57, -66, -236
|
||||||
|
164882077279529, 201483737546733, 335070662943802 @ 124, 70, -427
|
||||||
|
428414485445962, 492485352755959, 272973136766672 @ -67, -103, 41
|
||||||
|
264897981595185, 404913442349664, 276336971338210 @ 88, -23, 37
|
||||||
|
124722508278926, 2134756155381, 110913025404874 @ 227, 384, 208
|
||||||
|
536832023822247, 453183106296689, 554060222944721 @ -356, -198, -382
|
||||||
|
319673051050466, 266571988792245, 210279914314000 @ 17, 103, 104
|
||||||
|
150821661312904, 219455030985091, 231399996053480 @ 194, -19, 89
|
||||||
|
158037715359790, 284936450761794, 164842330369291 @ 181, -53, 238
|
||||||
|
255633864100187, 315497864599284, 295466891366890 @ -90, -183, -91
|
||||||
|
392762975015658, 291483914154943, 229288562346068 @ -35, 89, 83
|
||||||
|
309403838076114, 336694805164365, 277758585027766 @ 17, 16, 28
|
||||||
|
287207150932613, 479713650170448, 553028229703657 @ -40, -331, -480
|
||||||
|
269836626986969, 417558006790458, 212469813227848 @ -6, -215, 115
|
||||||
|
196645388374976, 244570813283961, 249157458432502 @ 87, 34, 41
|
||||||
|
339693128219614, 399751916312913, 284680478974716 @ 8, -26, 27
|
||||||
|
187559549440250, 195622840636569, 254727426356500 @ -148, 13, -116
|
||||||
|
304935421756516, 348400992185367, 261097863957704 @ 10, -11, 45
|
||||||
|
394511030167381, 223826480972951, 305918192064792 @ -110, 140, -13
|
||||||
|
223011594988398, 194915959669899, 221220518871005 @ -131, 112, 134
|
||||||
|
235558411474303, 407906141462802, 340419559289067 @ -22, -401, -198
|
||||||
|
168807003005795, 353652818048826, 276081152261755 @ 126, -489, -86
|
||||||
|
146617870930743, 156137711671265, 286804418224879 @ 220, 330, -284
|
||||||
|
286018415412552, 353012603278297, 251064479342937 @ 23, -30, 56
|
||||||
|
447713232441308, 372146255273187, 341273315411916 @ -153, -32, -49
|
||||||
|
209718676758750, 247605970547674, 218062472885396 @ -19, -63, 135
|
||||||
|
343626695642120, 155974548843997, 172127764933794 @ -24, 224, 150
|
||||||
|
345109049048735, 227227570932339, 273481589457805 @ -136, 112, 10
|
||||||
|
188575330043159, 118850415966657, 305893691628208 @ 134, 298, -45
|
||||||
|
326608598650070, 151338233232649, 416515828832310 @ -99, 242, -231
|
||||||
|
360202364064386, 436602737274865, 326789378915772 @ -27, -81, -22
|
||||||
|
213268194460580, 241549002519749, 394962709612380 @ 84, 80, -217
|
||||||
|
197614206616568, 139979243625984, 357286465189054 @ 15, 337, -399
|
||||||
|
227981330842760, 156692554162989, 177379530796580 @ -57, 262, 263
|
||||||
|
157229517762970, 231523131346089, 46953217581800 @ 167, -44, 890
|
||||||
|
305219322429448, 177060442180047, 49658860244982 @ -22, 199, 342
|
||||||
|
152688286391810, 215257107452481, 216706409125996 @ 171, -167, 232
|
||||||
|
177207555863420, 203871290203365, 289811933188528 @ -74, -84, -479
|
||||||
|
190420105339073, 167303615894628, 216289073804446 @ 110, 219, 117
|
||||||
|
266399617296604, 299362499051479, 325520686693096 @ -20, -33, -95
|
||||||
|
481245676627650, 436807969705569, 314107082127180 @ -202, -116, -19
|
||||||
|
401026926420116, 374922905725809, 350888777956543 @ -101, -38, -62
|
||||||
|
256839644239620, 270114181543499, 257354063805598 @ 26, 47, 40
|
||||||
|
412259775717406, 242736865487561, 424824610687152 @ -86, 128, -130
|
||||||
|
66312913166752, 101998933996761, 60120199695721 @ 283, 274, 250
|
||||||
|
506958247823068, 361333863900433, 280005516982136 @ -152, 18, 33
|
||||||
|
298773017825360, 317212540408089, 312439900056100 @ 12, 22, -21
|
||||||
|
220796554287875, 214622218414014, 268263970137525 @ -96, 37, -66
|
||||||
|
189208611146850, 404126141855649, 112689238573260 @ 52, -656, 531
|
||||||
|
234488363250114, 231264618839649, 204011914548812 @ 65, 112, 126
|
||||||
|
283632869172150, 177048553588739, 391393075492010 @ -121, 197, -300
|
||||||
|
502765928206235, 353125800556389, 304677713378740 @ -156, 22, 7
|
||||||
|
137557454494001, 97473160546677, 94622893468780 @ 242, 470, 559
|
||||||
|
254064108665930, 262174096766589, 289808760599414 @ 21, 52, -18
|
||||||
|
182103896038108, 247435234271202, 351160194849282 @ -25, -299, -735
|
||||||
|
249420082303430, 42226989901413, 97645217504204 @ 36, 421, 303
|
||||||
|
284785302989480, 255729203245377, 252686569800496 @ -94, 26, 37
|
||||||
|
233601301711332, 322776864011749, 366444377930614 @ 70, -28, -128
|
||||||
|
155098520524958, 244934576541158, 226621458469431 @ 165, -241, 122
|
||||||
|
146746875809578, 160303698184733, 228748383224514 @ 205, 224, 86
|
||||||
|
326652196225864, 355170482041167, 311279979189430 @ -38, -41, -26
|
||||||
|
277275275212730, 369459942642369, 282937479061000 @ 59, -14, 24
|
||||||
|
295687269134249, 340949989963329, 238600197559195 @ 60, 42, 74
|
||||||
|
279992481783853, 333185439596083, 324914479814764 @ 64, 36, -17
|
||||||
|
241428276856914, 266598398788449, 362846190951676 @ -40, -38, -260
|
||||||
|
259307794913743, 295678437418021, 269285719406143 @ 8, -10, 16
|
||||||
|
240223936950226, 473763454154241, 220230835580308 @ 77, -206, 97
|
||||||
|
318558193417106, 334499570437515, 230529981435367 @ 25, 36, 82
|
||||||
|
275715901048290, 73132232580276, 217625216713160 @ 41, 331, 99
|
||||||
|
193044713426762, 394683970973463, 372101396303146 @ 145, -80, -99
|
||||||
|
145897314675055, 223949571890769, 176036980234010 @ 232, -230, 585
|
||||||
|
161440895273330, 237913221256553, 291149659043788 @ 171, 45, -65
|
||||||
|
264388423069872, 379242075888111, 338900807126713 @ -5, -164, -110
|
||||||
|
335398015038338, 259239092404812, 434897503751132 @ 9, 115, -129
|
||||||
|
236716202526674, 332397372379329, 276349416527020 @ 79, -18, 19
|
||||||
|
322665826998882, 358742494848305, 303038334161388 @ -13, -25, -7
|
||||||
|
428381456361421, 547609324289011, 198413346560546 @ -70, -160, 113
|
||||||
|
157290994488974, 206478542217105, 303245653405090 @ 157, 26, -311
|
||||||
|
395914211954640, 425947992394193, 312165656677126 @ -184, -190, -44
|
||||||
|
244618900201418, 557301378477177, 207722519450068 @ -51, -810, 147
|
||||||
|
279386951121298, 308300290814141, 289436636980500 @ -31, -36, -21
|
||||||
|
306161107858370, 145704637204577, 363514529004748 @ -99, 258, -170
|
||||||
|
157069989582566, 150135411048405, 169136269193176 @ 168, 309, 356
|
||||||
|
149210988438152, 134368802376762, 209337851128249 @ 203, 605, 318
|
||||||
|
332584662588854, 503022806009046, 148583395713307 @ -43, -235, 192
|
||||||
|
470742777193259, 423305548535160, 228962588950855 @ -160, -77, 84
|
||||||
|
250671602810546, 250908746265621, 243056875754412 @ -135, -50, 47
|
||||||
|
531229816428916, 231708023716351, 470967021948546 @ -196, 143, -168
|
||||||
|
237893080628802, 139019131653901, 131107424449688 @ 73, 254, 227
|
||||||
|
218711687951546, 159752359004265, 320741448667460 @ 78, 229, -76
|
||||||
|
165313081944257, 184601129061069, 299424839638243 @ 168, 182, -58
|
||||||
|
307210181456654, 421282787395425, 479731549148236 @ 37, -54, -177
|
||||||
|
305412361284452, 343104362104491, 360276884155534 @ -56, -75, -130
|
||||||
|
368644982396221, 368636169652378, 540142064185444 @ -22, 5, -233
|
||||||
|
296336361357714, 453921261262757, 388278886187068 @ 53, -79, -77
|
||||||
|
431597308261298, 363087620944641, 307225389042377 @ -231, -86, -34
|
||||||
|
302152593338480, 335110106105791, 293583504813410 @ 36, 29, 14
|
20
24/lol.txt
Normal file
20
24/lol.txt
Normal file
File diff suppressed because one or more lines are too long
35
24/part1.pl
Normal file
35
24/part1.pl
Normal 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).
|
35
24/part2.pl
Normal file
35
24/part2.pl
Normal 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).
|
27
24/test.txt
Normal file
27
24/test.txt
Normal file
@@ -0,0 +1,27 @@
|
|||||||
|
19, 13, 30 @ -2, 1, -2
|
||||||
|
18, 19, 22 @ -1, -1, -2
|
||||||
|
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
1205
25/input.txt
Normal file
File diff suppressed because it is too large
Load Diff
91
25/part1.pl
Normal file
91
25/part1.pl
Normal 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
13
25/test.txt
Normal 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
|
Reference in New Issue
Block a user