Last active
December 10, 2020 17:17
-
-
Save ljos/0d9f094dafbf801c9f79372ab87be9d7 to your computer and use it in GitHub Desktop.
Advent of code, 2020
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
% The first task is to find numbers in a list that sum up to 2020. We | |
% will solve this problem using constraint logic programming over | |
% finite domains in prolog. | |
:- use_module(library(clpfd)). | |
:- use_module(library(dcg/basics)). | |
% In the first part we are given a list of numbers and we want to find | |
% 2 numbers that sum up to the value 2020 and then calculate the | |
% product of those two numbers. We therefore want a predicate that | |
% takes the length of the list of numbers to find (Length), and will | |
% find the numbers (Numbers) that sum to 2020 and the product of those | |
% numbers (Product). Finding the numbers is strictly not necessary, | |
% but it makes it verify that we have the correct numbers. | |
step_1(Numbers, Product) :- | |
once(solve(2, Numbers, Product)). | |
% Part 2 is exactly the same as part one, but we want to ask for 3 | |
% numbers instead of 2: | |
step_2(Numbers, Product) :- | |
once(solve(3, Numbers, Product)). | |
solve(Length, Numbers, Product) :- | |
% Firstly, Numbers is an ungrounded and unconstrained | |
% variable. That means that it can have any value. The first thing | |
% we do is to restrict Numbers to be a list of Length values. Each of | |
% those values can, for now, be any value. | |
length(Numbers, Length), | |
% day_1 then calculate the constraints given to us by the task that we were given. | |
day_1(Numbers), | |
% We find the an example of Numbers that satisfy the | |
% constraint. | |
label(Numbers), | |
% Lastly, we also want to calculate the product of the numbers as | |
% that is the proof that we found the correct numbers. | |
[N| Ns] = Numbers, | |
foldl(product_, Ns, N, Product). | |
day_1(Numbers) :- | |
phrase_from_stream(numbers([E|Expenses], 'advent_1_inp.txt'), | |
% We need to restrict the numbers that we can choose from to the | |
% numbers in the list of expenses. We do that by creating a domain | |
% that contains all of the expenses. Here we can see the small | |
% optimization: We use the first expense as the accumulator in the | |
% foldl so that we don't have to consider how to handle the empty | |
% domain. Here we say that the Domain is the union of all of the | |
% expenses. | |
foldl(union_, Expenses, E, Domain), | |
% We then say that each of the numbers in the list is part of the | |
% domain over expenses. | |
Numbers ins Domain, | |
% Another small optimization is that we assume that non of the | |
% numbers repeat and that we can only use a number once. We can | |
% therefore say that the numbers in the list are ordered from | |
% smallest to largest. | |
chain(Numbers, #<), | |
% Finally, we can say that the sum of the numbers should be 2020; | |
% the task that we were asked to solve. | |
sum(Numbers, #=, 2020). | |
% This is a helper predicate that is used with foldl and just | |
% creates the union of the domains E and D. | |
union_(E, D, '\\/'(E, D)). | |
% this is a helper predicate that is used with foldl and just gives us | |
% the product of N and M. | |
product_(N, M, P) :- P #= N * M. | |
numbers([N]) --> integer(N), blanks. | |
numbers([N|Ns]) --> integer(N), blanks, numbers(Ns). |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
% Solving advent of code day 2 using constraint logic programming over | |
% finite domains in prolog. | |
:- use_module(library(clpfd)). | |
:- use_module(library(dcg/basics)). | |
% We want a predicate that will give us the number (L) of passwords | |
% that fit the password constraints given in the task. | |
step_1(L) :- | |
% We parse the input file using definite clause grammar (DCG). | |
phrase_from_file(passwords(Passwords), 'advent_2_inp.txt'), | |
% We then count which passwords meet the constraint for the | |
% passwords. | |
aggregate_all(count, (member(P, Passwords), check_step_1(P)), L). | |
% Each password (p) exists of a Lower and Upper bound for the number | |
% of times the character (Char) can appear in the Password. | |
check_step_1(p(Lower, Upper, Char, Password)) :- | |
% We count the number of times the Char appears in the | |
% Password. 'aggregate_all' count all the number of ways that the | |
% 'arg' goal can complete. In our instance, the password is a | |
% functor and we count where the arguments are the character. This | |
% could be a list instead, but indexed lookup is much faster for a | |
% functor. | |
aggregate_all(count, arg(_, Password, Char), Length), | |
% and check if it is between the Lower and Upper bound. | |
chain([Lower, Length, Upper], #=<). | |
% In step two the constraints on the password changes, but the process | |
% is the same as in the first step. | |
step_2(L) :- | |
phrase_from_file(passwords(Passwords), 'advent_2_inp.txt'), | |
% And count the passwords that meet the constraint. | |
aggregate_all(count, (member(P, Passwords), check_step_2(P)), L). | |
check_step_2(p(Idx1, Idx2, Char, Password)) :- | |
% We get the Char at index 1... | |
arg(Idx1, Password, Char1), | |
% The character at index 2... | |
arg(Idx2, Password, Char2), | |
% and we check that either Char1 is the Char or Char2 is the Char, | |
% but not both. | |
Char1 #= Char #\ Char2 #= Char. | |
% To parse the input file, we define a system of definite clause | |
% grammars. We want to be able to say that the file consists of many | |
% passwords; one after the other. | |
% | |
% We say that by saying that a list of passwords either has a single | |
% password, or it has one password followed by more passwords. | |
passwords([P]) --> | |
% For a list of 1 passwords, the list should | |
password(P), % contain a password, and | |
blanks. % potentially some blanks. | |
passwords([P|Passwords]) --> | |
% For a list of many passwords, the list should contain | |
password(P), % first one password and | |
blanks, % potentially some blanks, | |
passwords(Passwords). % lastly there should be more passwords. | |
% We then have to be able to acutally parse a single password. A | |
% single password consinsts of a Lower and Upper bound, a Char and | |
% then the acutal Password string. | |
password(p(Lower, Upper, Char, Password)) --> | |
% We should first find an integer, | |
integer(Lower), | |
% Then a - | |
"-", | |
% then another integer, | |
integer(Upper), | |
% a blank space | |
blank, | |
% a nonblank character | |
nonblank(Char), | |
% a colon | |
":", | |
% a blank space | |
blank, | |
% and the rest of the line, is the password string. | |
string_without("\n", String), | |
{ | |
% We could use just the String, but that is a list and we are | |
% going to access the characters in the string by index. It is | |
% much faster to acess the arguments of a functor than the | |
% indices of a list. | |
Password =.. [array | String] | |
}. |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
:- use_module(library(clpfd)). | |
:- use_module(library(dcg/basics)). | |
line(Line) --> | |
string_without("\n", L), | |
{ Line =.. [line | L] }. | |
lines([Line]) --> line(Line), blanks. | |
lines([L|Lines]) --> | |
line(L), | |
blanks, | |
lines(Lines). | |
traverse(_, _, [], []). | |
traverse(R-D, Rd-Dd, Lines, Tiles) :- | |
R #> 31, | |
R1 #= R - 31, | |
traverse(R1-D, Rd-Dd, Lines, Tiles). | |
traverse(_, _-Dd, Lines, []) :- | |
length(Lines, L), | |
Dd #> L. | |
traverse(R-D, Rd-Dd, [Line | Lines], [T|Tiles]) :- | |
arg(R, Line, T), | |
R1 #= R + Rd, | |
D1 #= D + Dd, | |
length(Head, Dd), | |
append(Head, Lines1, [Line | Lines]), | |
traverse(R1-D1, Rd-Dd, Lines1, Tiles). | |
path(Lines, D, Count) :- | |
traverse(1-1, D, Lines, Path), | |
aggregate_all(count, member(35, Path), Count). | |
step_1(Trees) :- | |
phrase_from_file(lines(Lines), 'advent_3_inp.txt'), | |
path(3-1, Lines, Path), | |
aggregate_all(count, member(35, Path), Trees), !. | |
product_(N, M, P) :- P #= N * M. | |
step_2([C|Counts], Product) :- | |
phrase_from_file(lines(Lines), 'advent_3_inp.txt'), | |
maplist(path(Lines), [1-1, 3-1, 5-1, 7-1, 1-2], [C|Counts]), | |
foldl(product_, Counts, C, Product), !. |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
:- use_module(library(clpfd)). | |
:- use_module(library(dcg/basics)). | |
:- set_prolog_flag(double_quotes, codes). | |
info(Prop) --> | |
[A, B, C], ":", !, nonblanks(Value), | |
{ atom_codes(Name, [A, B, C]), Prop =.. [Name, Value] }. | |
passport([I]) --> info(I). | |
passport([I|Info]) --> info(I), blank, passport(Info). | |
passports([P]) --> passport(P), blanks. | |
passports([P|Passports]) --> passport(P), "\n\n" , passports(Passports). | |
valid(Info) :- | |
maplist(functor, Info, Names, _), | |
subtract([byr, iyr, eyr, hgt, hcl, ecl, pid], Names, []). | |
check(byr(Byr)) :- integer(Y, Byr, []), Y #>= 1920, Y #=< 2002. | |
check(iyr(Iyr)) :- integer(Y, Iyr, []), Y #>= 2010, Y #=< 2020. | |
check(eyr(Eyr)) :- integer(Y, Eyr, []), Y #>= 2020, Y #=< 2030. | |
check(hgt(Hgt)) :- integer(H, Hgt, "cm"), H #>= 150, H #=< 193. | |
check(hgt(Hgt)) :- integer(H, Hgt, "in"), H #>= 59, H #=< 76. | |
check(hcl(Hcl)) :- phrase(("#", xinteger(_)), Hcl). | |
check(ecl(Ecl)) :- atom_codes(E, Ecl), memberchk(E, [amb, blu, brn, gry, grn, hzl, oth]). | |
check(pid(Pid)) :- length(Pid, 9), integer(_, Pid, []). | |
check(cid(_)). | |
main(Step1, Step2) :- | |
phrase_from_file(passports(Passports), 'advent_4_inp.txt'), | |
include(valid, Passports, Valid), | |
length(Valid, Step1), | |
include(maplist(check), Valid, Checked), | |
length(Checked, Step2). |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
:- use_module(library(dcg/basics)). | |
:- use_module(library(clpfd)). | |
row([1]) --> "B". | |
row([1|Ls]) --> "B", row(Ls). | |
row([0]) --> "F". | |
row([0|Ls]) --> "F", row(Ls). | |
col([1]) --> "R". | |
col([1|Ls]) --> "R", col(Ls). | |
col([0]) --> "L". | |
col([0|Ls]) --> "L", col(Ls). | |
position([Row,Col]) --> row(Row), col(Col). | |
seating([S]) --> position(S), blanks. | |
seating([S|Seats]) --> position(S), blanks, seating(Seats). | |
restrict(0, L-U0, L-U) :- U #= U0 - ((U0 - L) // 2) - 1. | |
restrict(1, L0-U, L-U) :- L #= L0 + ((U - L0) // 2) + 1. | |
seat([X, Y], Id) :- | |
foldl(restrict, X, 0-127, Row-Row), | |
foldl(restrict, Y, 0-7, Col-Col), | |
Id #= Row * 8 + Col. | |
hole([A, B | _], Missing) :- | |
2 #= B - A, | |
Missing #= A + 1. | |
hole([_|Seats], Missing) :- | |
hole(Seats, Missing). | |
main(Part1, Part2) :- | |
phrase_from_file(seating(Seating), 'advent_5_inp.txt'), | |
maplist(seat, Seating, Ids), !, | |
max_list(Ids, Part1), | |
sort(Ids, Sorted), | |
hole(Sorted, Part2). |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
:- use_module(library(dcg/basics)). | |
:- use_module(library(clpfd)). | |
answers([], []). | |
answers(Group, [Answer|Answers]) :- | |
append(Answer, [10 | Rest], Group), | |
answers(Rest, Answers). | |
answers(Group, [Answer]) :- | |
append(Answer, [10], Group). | |
answers(Group, [Group]). | |
groups(Str, [Answers | Groups]) :- | |
append(Group, [10, 10 | Rest], Str), | |
answers(Group, Answers), | |
groups(Rest, Groups). | |
groups(Str, [Answer]) :- | |
answers(Str, Answer). | |
unique_1(Answers, Count) :- | |
[A| As] = Answers, | |
foldl(union, As, A, Unique), | |
length(Unique, Count). | |
unique_2(Answers, Count) :- | |
[A| As] = Answers, | |
foldl(intersection, As, A, Unique), | |
length(Unique, Count). | |
main(Part1, Part2) :- | |
read_file_to_codes('advent_6_inp.txt', Codes, []), | |
groups(Codes, Groups), | |
maplist(unique_1, Groups, Count1), | |
sum(Count1, #=, Part1), | |
maplist(unique_2, Groups, Count2), | |
sum(Count2, #=, Part2), !. |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
:- use_module(library(clpfd)). | |
:- use_module(library(dcg/basics)). | |
:- use_module(library(dcg/high_order)). | |
bag(Bag) --> | |
nonblanks(A), " ", nonblanks(C), " bag", optional("s", []), | |
{ append(A, [0'_|C], S), atom_codes(Bag, S) }. | |
bags([N-Bag|Bags]) --> integer(N), " ", bag(Bag), ", ", bags(Bags). | |
bags([N-Bag]) --> integer(N), " ", bag(Bag). | |
rule(contains(B, Bags)) --> bag(B), " contain ", bags(Bags), ".". | |
rule(contains(B, [])) --> bag(B), " contain no other bags.". | |
rules([R|Rules]) --> rule(R), "\n", rules(Rules). | |
rules([R]) --> rule(R), blanks. | |
assert_contains(S, N-O) :- assertz(contains(S, N, O)). | |
assert_rule(contains(S, Os)) :- maplist(assert_contains(S), Os). | |
assert_rules(Rules) :- maplist(assert_rule, Rules). | |
can_contain(Bag, Container) :- | |
contains(Container, _, Bag). | |
can_contain(Bag, Container) :- | |
contains(C, _, Bag), | |
can_contain(C, Container). | |
product_(A, B, N) :- N #= A * B. | |
count(A-_, Bs, Ns) :- maplist(product_(A), Bs, Ns). | |
inventory(N-Bag, Value) :- | |
findall(C-B, contains(Bag, C, B), Cs), | |
maplist(inventory, Cs, Bags), | |
sum(Bags, #=, V), | |
Value #= N + V * N. | |
read_rules :- | |
retractall(contains(_, _, _)), | |
phrase_from_file(rules(Rules), 'advent_7_inp.txt'), | |
assert_rules(Rules), !. | |
main(Part1, Part2) :- | |
read_rules, | |
aggregate_all(set(C), can_contain(shiny_gold, C), S), | |
length(S, Part1), | |
inventory(1-shiny_gold, Value), | |
Part2 #= Value - 1. |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
:- use_module(library(dcg/basics)). | |
:- use_module(library(dcg/high_order)). | |
instruction(Inst-Val) --> | |
[A, B, C], " ", integer(Val), "\n", | |
{ atom_codes(Inst, [A,B,C]) }. | |
instructions(Insts) --> sequence(instruction, Insts). | |
assert_insts(Insts) :- retractall(inst(_, _, _)), assert_insts(1, Insts). | |
assert_insts(_, []). | |
assert_insts(N, [Inst-Val|Insts]) :- | |
assertz(inst(N, Inst, Val)), | |
N1 #= N + 1, | |
assert_insts(N1, Insts). | |
eval(acc, Val, [I0, Acc0], [I, Acc]) :- I #= I0 + 1, Acc #= Acc0 + Val. | |
eval(jmp, Val, [I0, Acc], [I, Acc]) :- I #= I0 + Val. | |
eval(nop, _, [I0, Acc], [I, Acc]) :- I #= I0 + 1. | |
interpret_1(Vs, I, Acc, Acc) :- | |
member(I, Vs), !. | |
interpret_1(Vs, I0, Acc0, Out) :- | |
inst(I0, Inst, Val), | |
eval(Inst, Val, [I0, Acc0], [I, Acc]), | |
interpret_1([I0| Vs], I, Acc, Out). | |
interpret_1(Out) :- interpret_1([], 1, 0, Out). | |
interpret_2(_, _, I, Acc, Acc) :- | |
\+ inst(I, _, _). | |
interpret_2(Mod, Vs, I0, Acc0, Out) :- | |
\+ member(I0, Vs), | |
inst(I0, jmp, Val), | |
Mod = I0, | |
eval(nop, Val, [I0, Acc0], [I, Acc]), | |
interpret_2(Mod, [I0|Vs], I, Acc, Out). | |
interpret_2( Mod, Vs, I0, Acc0, Out) :- | |
\+ member(I0, Vs), | |
inst(I0, Inst, Val), | |
eval(Inst, Val, [I0, Acc0], [I, Acc]), | |
interpret_2(Mod, [I0|Vs], I, Acc, Out). | |
interpret_2(Out) :- interpret_2(_, [], 1, 0, Out). | |
main(Part1, Part2) :- | |
phrase_from_file(instructions(Insts), 'advent_8_inp.txt'), | |
assert_insts(Insts), | |
interpret_1(Part1), | |
interpret_2(Part2). |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
:- use_module(library(clpfd)). | |
:- use_module(library(dcg/basics)). | |
:- use_module(library(dcg/high_order)). | |
n(N) --> integer(N), "\n". | |
union_(E, D, '\\/'(E, D)). | |
dom([P|Preamble], V) :- | |
foldl(union_, Preamble, P, Domain), | |
[A, B] ins Domain, | |
A #\= B, | |
V #= A + B, | |
indomain(V). | |
check(Preamble, N) :- | |
\+ dom(Preamble, N). | |
validate(Numbers, Invalid) :- | |
length(Preamble, 25), | |
append(Preamble, [Invalid | _], Numbers), | |
check(Preamble, Invalid). | |
validate([_|Numbers], Invalid) :- | |
validate(Numbers, Invalid). | |
find_([H|T], Sum0, Target, [H|Seq]) :- | |
Sum #= Sum0 + H, | |
Sum #< Target, | |
find_(T, Sum, Target, Seq). | |
find_([H|_], Sum0, Target, [H]) :- | |
Target #= Sum0 + H. | |
find([], _, []). | |
find([H|T], Target, Seq) :- | |
find_([H|T], 0, Target, Seq). | |
find([_|T], Target, Seq) :- | |
find(T, Target, Seq). | |
main(Part1, Part2) :- | |
phrase_from_file(sequence(n, List), 'advent_9_inp.txt'), | |
validate(List, Part1), | |
find(List, Part1, Example), | |
length(Example, Length), | |
Length #> 1, | |
min_member(Min, Example), | |
max_member(Max, Example), | |
Part2 #= Min + Max. |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
:- use_module(library(clpfd)). | |
:- use_module(library(dcg/basics)). | |
:- use_module(library(dcg/high_order)). | |
n(N) --> integer(N), "\n". | |
arrange(_, Jmax, Jmax, [0, 1]). | |
arrange([H|T], Jmax, J, [A, C]) :- | |
1 #= H - J, | |
A0 #= A - 1, | |
arrange(T, Jmax, H, [A0, C]). | |
arrange([H|T], Jmax, J, [A, C]) :- | |
3 #= H - J, | |
C0 #= C - 1, | |
arrange(T, Jmax, H, [A, C0]). | |
arrange([_|T], Jmax, J, Cs) :- | |
arrange(T, Jmax, J, Cs). | |
assert_edge(N, C) :- assertz(edge(N, C)). | |
children(N, [C|T], [C|Children]) :- | |
C - N #>= 1 #/\ C - N #=< 3, | |
!, children(N, T, Children). | |
children(_, _, []). | |
assert_dag([]). | |
assert_dag([H|T]) :- | |
children(H, T, C), | |
maplist(assert_edge(H), C), | |
assert_dag(T). | |
:- table n_paths/2. | |
n_paths(N, 1) :- \+ edge(N, _). | |
n_paths(N, Sum) :- | |
aggregate(set(C), edge(N, C), Children), | |
maplist(n_paths, Children, Vals), | |
sum(Vals, #=, Sum). | |
main(Part1, Part2) :- | |
phrase_from_file(sequence(n, List), 'advent_10_inp.txt'), | |
sort(List, Adapters), | |
max_list(Adapters, Max), | |
arrange(Adapters, Max, 0, [A, C]), !, | |
Part1 #= A * C, | |
retractall(edge(_, _)), | |
assert_dag([0|Adapters]), | |
n_paths(0, Part2). |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment