Skip to content

Instantly share code, notes, and snippets.

@z5h
Last active December 9, 2024 16:45
Show Gist options
  • Save z5h/166c9e5b9c170e9d83d18165cf3eeacf to your computer and use it in GitHub Desktop.
Save z5h/166c9e5b9c170e9d83d18165cf3eeacf to your computer and use it in GitHub Desktop.
Advent of Code 2024 in Prolog
% -*-Prolog-*-
:- module(d01, [
a/0,
b/0
]).
:- use_module(library(pio)).
:- use_module(library(dcg/basics)).
a :-
phrase_from_file(lists(L1, L2), '1/inputa.txt'),
sort(0, @=<, L1, S1),
sort(0, @=<, L2, S2),
l1_l2_sum(S1, S2, Sum),
writeln(sum:Sum).
b :-
phrase_from_file(lists(Left, Right), '1/inputa.txt'),
maplist(list_member_score(Right), Left, Scores),
sum_list(Scores, Sum),
writeln(sum:Sum).
list_member_score(L, M, S) :-
list_member_count(L, M, C),
S is M * C.
list_member_count([], _, 0).
list_member_count([H|T], M, C) :-
list_member_count(T, M, CT),
( M == H
-> C is CT + 1
; C is CT
).
l1_l2_sum([],[],0).
l1_l2_sum([H1|T1],[H2|T2],S) :-
l1_l2_sum(T1, T2, TSum),
S is abs(H1 - H2) + TSum.
lists([N1|L1], [N2|L2]) -->
blanks,
integer(N1),
blanks,
integer(N2),
lists(L1, L2).
lists([], []) -->
blanks, eos.
% -*-Prolog-*-
:- module(d02,
[a/0,
b/0
]
).
:- use_module(library(pio)).
:- use_module(library(dcg/basics)).
a :-
phrase_from_file(rows(Rows), '2/inputa.txt'),
include(safe, Rows, Safe),
length(Safe, Count),
writeln(safe:Count).
b :-
phrase_from_file(rows(Rows), '2/inputa.txt'),
include(tolerated, Rows, Tolerated),
length(Tolerated, Count),
writeln(safe:Count).
tolerated(List) :-
once(tolerable(List)).
tolerable(List) :-
safe(List).
tolerable(List) :-
select(_, List, Remainder),
safe(Remainder).
safe_pair(Comp, A, B) :-
compare(Comp, A, B),
Diff is abs(A - B),
1 =< Diff,
Diff =< 3.
safe(List) :-
safe(_Comp, List).
safe(Comp, [A,B]) :-
safe_pair(Comp, A, B).
safe(Comp, [A,B | Rest]) :-
safe_pair(Comp, A, B),
safe(Comp, [B | Rest]).
% DCGs for parsing the file
row([I]) -->
integer(I),
whites,
eol.
row([I | Rest]) -->
integer(I),
whites,
row(Rest).
rows([Row | Rest]) -->
row(Row),
rows(Rest).
rows([]) -->
blanks,
eos.
% -*-Prolog-*-
:- module(d03,[a/1, b/1]).
:- use_module(library(pio)).
:- use_module(library(dcg/basics)).
a(Total) :-
phrase_from_file(seq(0, Total), '3/inputa.txt').
b(Total) :-
phrase_from_file(do(0, Total), '3/inputa.txt').
ok_number(N) -->
( digit(A), digit(B), digit(C)
; {A = 0'0}, digit(B), digit(C)
; {A = 0'0, B = 0'0}, digit(C)
),
{number_chars(N, [A,B,C])}.
seq(Sum0, SumN) -->
mul(Sum0, Sum1),
seq(Sum1, SumN).
seq(Sum0, SumN) --> [_],
seq(Sum0, SumN).
seq(Sum, Sum) -->
eos.
mul(PrevSum, Sum) --> "mul(", ok_number(A), ",", ok_number(B), ")",
{ Sum is PrevSum + A * B}.
do(Sum0, SumN) --> "don't()",
dont(Sum0, SumN).
do(Sum0, SumN) -->
mul(Sum0, Sum1),
do(Sum1, SumN).
do(Sum0, SumN) --> [_],
do(Sum0, SumN).
do(Sum, Sum) -->
eos.
dont(Sum0, SumN) --> "do()",
do(Sum0, SumN).
dont(Sum0, SumN) --> [_],
dont(Sum0, SumN).
dont(Sum, Sum) -->
eos.
% -*-Prolog-*-
:- module(d04,[a/1, b/1]).
:- use_module(library(pio)).
:- use_module(library(dcg/basics)).
a(Total) :-
goal_count(
( lines_x_y(Lines, X, Y),
direction(DX,DY),
chars_in_at_direction(`XMAS`, Lines, (X,Y), (DX,DY))
),
Total).
b(Total) :-
goal_count(
( lines_x_y(Lines, X, Y),
xmas_in_at(Lines, (X,Y))
),
Total).
goal_count(G, C) :-
findall(ignore, G, Ss),
length(Ss, C).
lines_x_y(Lines, X, Y) :-
phrase_from_file(lines(Lines), '4/inputa.txt'),
length(Lines, Rows),
Lines = [Row | _ ],
length(Row, Columns), !,
between(1, Rows, Y),
between(1, Columns, X).
lines([]) --> eos.
lines([Line|Rest]) -->
line(Line),
lines(Rest).
line(Line) --> nonblanks(Line), eol.
direction(DX, DY) :-
between(-1, 1, DX),
between(-1, 1, DY),
\+ (DX = 0, DY = 0).
chars_in_at_direction([], _, _, _).
chars_in_at_direction([H|T], Lines, (X, Y), (DX, DY)) :-
nth1(Y, Lines, Line),
nth1(X, Line, H),
X1 is X + DX,
Y1 is Y + DY,
chars_in_at_direction(T, Lines, (X1, Y1), (DX, DY)).
xmas_in_at(Lines, (X,Y)) :-
( chars_in_at_direction(`MAS`, Lines, (X,Y), (1, 1))
; chars_in_at_direction(`SAM`, Lines, (X,Y), (1, 1))
),
X2 is X + 2,
( chars_in_at_direction(`MAS`, Lines, (X2,Y), (-1, 1))
; chars_in_at_direction(`SAM`, Lines, (X2,Y), (-1, 1))
), !.
% -*-Prolog-*-
:- module(d05,[orderings_updates/2, a/2]).
:- use_module(library(pio)).
:- use_module(library(dcg/basics)).
% return orderings and updates
% uses tableing (memoizing/caching) to avoid re-reading the file
:- table(orderings_updates/2).
orderings_updates(Os, Us) :-
% phrase_from_file uses Prolog's DCGs for parsing.
% this might look like recursion, but the orderings_updates
% goal here takes 4 parameters, and is implemented by
% orderings_updates(Os, Us) --> (which takes 4 parameters).
phrase_from_file(orderings_updates(OsUnsorted, Us), '5/inputa.txt'),
% convert our list of unsorted orderings to a
% sorted list with no duplicates (what Prolog calls an ord_set).
% standard list predicates still work, but "ord_" predicates
% are optimized as they can assume the list is sorted without dupes
list_to_ord_set(OsUnsorted, Os).
% our grammar. we expect orderings, then a blank line,
% then updates, then the end of the stream.
orderings_updates(Os, Us) -->
orderings(Os),
blanks_to_nl,
updates(Us),
eos.
% orderings can be an ordering then more orderings
% and this rule is attempted first in (recursive) calls
orderings([O|T]) -->
ordering(O),
orderings(T).
% consuming no content results in an empty list of orderings.
% this will be attempted as an alternative when no further orderings
% can be parsed
orderings([]) --> [].
% we'll represent pairs as the term A-B.
% there is no evaluation here, it's just a pattern of data
ordering(A-B) -->
integer(A), "|", integer(B), eol.
% updates are an update then more updates
updates([U|T]) -->
update(U),
updates(T).
% being done with updates is a valid "get more updates"
% and it's attempted when actually parsing further updates fails
updates([]) --> [].
% an update is an integer, and if a "," is seen, we condinue recursively
% else the tail of our update data is the empty list
update([H|T]) -->
integer(H),
( ","
-> update(T)
; eol,
{T = []}
).
% an empty list is a valid update ordering
valid_update([]).
% if the head of a list is before everything in the tail,
% and if the tail is a valid update ordering,
% then the entire input is valid
valid_update([H|T]) :-
before_after(H, T),
valid_update(T).
% any value (shown as an anonymous value here)
% is validly ordered against an empty list of values
before_after(_, []).
% Before is before After (in the second list)
% if there is nothing in the orderings to refute that
% we also recursively check Before against the tail of the list
before_after(Before, [After|T]) :-
orderings_updates(Os, _),
\+ ord_memberchk(After-Before, Os),
before_after(Before, T).
% M is the value in the middle of a list L
list_midpoint(L, M) :-
length(L, Length),
I is Length // 2 + 1,
nth1(I, L, M).
% relates a scrabled list S,
% and the element F which should be first
% and the remainder S
scrambled_first_rest(S, F, R) :-
orderings_updates(Os, _),
% take something from the list
% such that no other member of the list
% should have been first
ord_selectchk(F, S, R),
\+ (member(Firster, R), ord_memberchk(Firster-F, Os)).
% an empty list is an unscrambled empty list
scrambled_unscrambled([], []).
% if we remove the element that should be first from a
% scrambled list, and unscrable the remainder, then
% prepending the former to the latter results in a
% fully unscrambled list
scrambled_unscrambled(S, U) :-
scrambled_first_rest(S, F, R),
scrambled_unscrambled(R, RU),
U = [F|RU].
% do the work
a(T1, T2) :-
orderings_updates(_, Us),
partition(valid_update, Us, Valid, Invalid),
maplist(list_midpoint, Valid, Ms),
sumlist(Ms, T1),
maplist(scrambled_unscrambled, Invalid, Unscrambled),
maplist(list_midpoint, Unscrambled, M2s),
sumlist(M2s, T2).
% -*-Prolog-*-
:- module(d09,[a/1]).
:- use_module(library(pio)).
:- use_module(library(dcg/basics)).
input(Blocks, File) :-
phrase_from_file(id_blocks(0, Blocks), File).
% create a block with initialized values
length_value_block(L, V, B) :-
length(B, L),
maplist('='(V), B).
% single digit integer parser
integer_digit(I) --> digit(D),
{ number_codes(I, [D]) }.
% stop if nothing else to do
id_blocks(_, []) --> eol, eos.
% parse an ID block, then parse space
id_blocks(Id, Blocks) --> integer_digit(Length),
{ length_value_block(Length, Id, Block),
append(Block, Rest, Blocks),
NextId is Id + 1
},
id_space(NextId, Rest).
% stop if nothing else to do
id_space(_, []) --> eol, eos.
% parse a space block then an ID block
id_space(Id, Blocks) --> integer_digit(Length),
{ length(Block, Length),
append(Block, Rest, Blocks)
},
id_blocks(Id, Rest).
% cound actual data
blocks_data_length(B, DL) :-
include(ground, B, D),
length(D, DL).
% stop if we've done the count of work we expected
count_blocks_reversed(0, _, _) --> [].
% prioritize nonempty data
count_blocks_reversed(Count, [BH | BT], R) --> [BH],
{ ground(BH), Next is Count - 1 },
count_blocks_reversed(Next, BT, R).
% ignore empty blocks at the end of the disk
count_blocks_reversed(Count, B, [R | RT]) -->
{ var(R) },
count_blocks_reversed(Count, B, RT).
% just unify RH and BH. previous nonempty BH cluse will do the work
count_blocks_reversed(Count, [BH | BT], [RH | RT]) -->
{ ground(RH), var(BH), BH = RH },
count_blocks_reversed(Count, [BH | BT], RT).
a(Checksum) :-
input(Blocks, '9/input.txt'),
blocks_data_length(Blocks, DataLength),
reverse(Blocks, Reversed),
phrase(count_blocks_reversed(DataLength, Blocks, Reversed), Formatted),
findall(Product, (nth0(I, Formatted, V), Product is I * V), Products),
sum_list(Products, Checksum).
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment