d13p1 and d13p2
This commit is contained in:
parent
25ad602e9a
commit
7a66d289ea
1339
13/input.txt
Normal file
1339
13/input.txt
Normal file
File diff suppressed because it is too large
Load Diff
44
13/part1.pl
Normal file
44
13/part1.pl
Normal file
@ -0,0 +1,44 @@
|
|||||||
|
:- use_module(library(pio)).
|
||||||
|
:- initialization(main, main).
|
||||||
|
|
||||||
|
main([FileName|_]) :-
|
||||||
|
input(FileName, Blocks),
|
||||||
|
convlist(vert_reflect, Blocks, Vs),
|
||||||
|
convlist(horz_reflect, Blocks, Hs),
|
||||||
|
sum_list(Vs, V),
|
||||||
|
sum_list(Hs, H),
|
||||||
|
Answer is 100*V + H,
|
||||||
|
writef('Answer=%t\n', [Answer]).
|
||||||
|
|
||||||
|
vert_reflect(Block, N) :- reflect(Block, N).
|
||||||
|
horz_reflect(Block, N) :- maplist({N}/[Row]>>(reflect(Row, N)), Block).
|
||||||
|
|
||||||
|
reflect(Items, N) :- perfect_reflect(Items, N).
|
||||||
|
reflect(Items, N) :-
|
||||||
|
append(SubItems, [_|_], Items),
|
||||||
|
perfect_reflect(SubItems, N).
|
||||||
|
reflect(Items, N) :-
|
||||||
|
append(Prefix, SubItems, Items),
|
||||||
|
perfect_reflect(SubItems, SubN),
|
||||||
|
length(Prefix, Len), N is SubN + Len.
|
||||||
|
|
||||||
|
% reflect right down the middle. N is half list length.
|
||||||
|
perfect_reflect([A, A], 1).
|
||||||
|
perfect_reflect(Items, N) :-
|
||||||
|
append([[Item], OtherItems, [Item]], Items),
|
||||||
|
perfect_reflect(OtherItems, N_sub1),
|
||||||
|
N is N_sub1 + 1.
|
||||||
|
|
||||||
|
input(FileName, Blocks) :- phrase_from_file(blocks(Blocks), FileName).
|
||||||
|
|
||||||
|
blocks([]) --> eos, !.
|
||||||
|
blocks([Block|Blocks]) --> block(Block), blocks(Blocks).
|
||||||
|
|
||||||
|
block([Line]) --> line(Line), ("\n"; eos), !.
|
||||||
|
block([Line|Lines]) --> line(Line), block(Lines).
|
||||||
|
|
||||||
|
line([]) --> ("\n"; eos), !.
|
||||||
|
line([#|Chars]) --> "#", line(Chars).
|
||||||
|
line([o|Chars]) --> ".", line(Chars).
|
||||||
|
|
||||||
|
eos([], []).
|
55
13/part2.pl
Normal file
55
13/part2.pl
Normal file
@ -0,0 +1,55 @@
|
|||||||
|
:- use_module(library(pio)).
|
||||||
|
:- use_module(library(clpfd)).
|
||||||
|
:- initialization(main, main).
|
||||||
|
|
||||||
|
main([FileName|_]) :-
|
||||||
|
input(FileName, Blocks),
|
||||||
|
convlist(almost_reflect, Blocks, Vs), sum_list(Vs, V),
|
||||||
|
maplist(transpose, Blocks, TBlocks),
|
||||||
|
convlist(almost_reflect, TBlocks, Hs), sum_list(Hs, H),
|
||||||
|
Answer is 100*V + H,
|
||||||
|
writef('Answer=%t\n', [Answer]).
|
||||||
|
|
||||||
|
almost_reflect(Items, N) :- almost_perfect_reflect(Items, N).
|
||||||
|
almost_reflect(Items, N) :-
|
||||||
|
append(SubItems, [_|_], Items),
|
||||||
|
almost_perfect_reflect(SubItems, N).
|
||||||
|
almost_reflect(Items, N) :-
|
||||||
|
append(Prefix, SubItems, Items),
|
||||||
|
almost_perfect_reflect(SubItems, SubN),
|
||||||
|
length(Prefix, Len), N is SubN + Len.
|
||||||
|
|
||||||
|
almost_perfect_reflect([A, B], 1) :- diff(A, B, 1).
|
||||||
|
almost_perfect_reflect(Items, N) :-
|
||||||
|
append([[A], OtherItems, [A]], Items),
|
||||||
|
almost_perfect_reflect(OtherItems, N_sub1),
|
||||||
|
N is N_sub1 + 1.
|
||||||
|
almost_perfect_reflect(Items, N) :-
|
||||||
|
append([[A], OtherItems, [B]], Items),
|
||||||
|
diff(A, B, 1),
|
||||||
|
perfect_reflect(OtherItems, N_sub1),
|
||||||
|
N is N_sub1 + 1.
|
||||||
|
|
||||||
|
% reflect right down the middle. N is half list length.
|
||||||
|
perfect_reflect([A, A], 1).
|
||||||
|
perfect_reflect(Items, N) :-
|
||||||
|
append([[Item], OtherItems, [Item]], Items),
|
||||||
|
perfect_reflect(OtherItems, N_sub1),
|
||||||
|
N is N_sub1 + 1.
|
||||||
|
|
||||||
|
diff(L1, L2, N) :-
|
||||||
|
foldl([A, B, Prev, Curr]>>(Curr is Prev + abs(A - B)), L1, L2, 0, N).
|
||||||
|
|
||||||
|
input(FileName, Blocks) :- phrase_from_file(blocks(Blocks), FileName).
|
||||||
|
|
||||||
|
blocks([]) --> eos, !.
|
||||||
|
blocks([Block|Blocks]) --> block(Block), blocks(Blocks).
|
||||||
|
|
||||||
|
block([Line]) --> line(Line), ("\n"; eos), !.
|
||||||
|
block([Line|Lines]) --> line(Line), block(Lines).
|
||||||
|
|
||||||
|
line([]) --> ("\n"; eos), !.
|
||||||
|
line([1|Chars]) --> "#", line(Chars).
|
||||||
|
line([0|Chars]) --> ".", line(Chars).
|
||||||
|
|
||||||
|
eos([], []).
|
15
13/test.txt
Normal file
15
13/test.txt
Normal file
@ -0,0 +1,15 @@
|
|||||||
|
#.##..##.
|
||||||
|
..#.##.#.
|
||||||
|
##......#
|
||||||
|
##......#
|
||||||
|
..#.##.#.
|
||||||
|
..##..##.
|
||||||
|
#.#.##.#.
|
||||||
|
|
||||||
|
#...##..#
|
||||||
|
#....#..#
|
||||||
|
..##..###
|
||||||
|
#####.##.
|
||||||
|
#####.##.
|
||||||
|
..##..###
|
||||||
|
#....#..#
|
Loading…
Reference in New Issue
Block a user