Skip to content

Instantly share code, notes, and snippets.

@tatut
Created October 17, 2023 15:45
Show Gist options
  • Save tatut/39c3de52fa49effb926f035ae9fe01bd to your computer and use it in GitHub Desktop.
Save tatut/39c3de52fa49effb926f035ae9fe01bd to your computer and use it in GitHub Desktop.
AoC 2022, dqy 5 prolog implementation (SWI-Prolog)
:- use_module(library(dcg/basics)).
:- use_module(library(yall)).
:- set_prolog_flag(double_quotes, codes).
crates(_, []) --> [].
crates(Ind, Cs) --> " ", { Ind1 is Ind + 1 }, crates(Ind1, Cs).
crates(Ind, [Ind-C|Cs]) --> "[", [Code], "] ", { char_code(C, Code) },
{ Ind1 is Ind + 1},
crates(Ind1, Cs).
% Just skip crate numbers line, we know them
crate_numbers --> string_without("\n", _), eol.
crate_lines([]) --> crate_numbers, eol.
crate_lines([L|Lines]) --> crates(1, L), eol, crate_lines(Lines).
move(m(Count, From, To)) --> "move ", integer(Count), " from ", integer(From), " to ", integer(To).
move_lines([]) --> [].
move_lines([M|Moves]) --> move(M), eol, move_lines(Moves).
% Turning the DCG parse output (list of lines that are lists of pairs [[1-'A', 3-'B'], [1-'C'], ...])
% into the format I want to use (list of pairs like [1-['A','B'], ...])
% looks somewhat awkward... I'm sure this is a skill issue on my part.
construct_crate(N, CrateLines, N-Crate) :-
findall(Item, (member(CL, CrateLines),
member(N-Item, CL)), Crate).
construct_crates(CrateLines, Crates) :-
findall(Crate, (member(CL, CrateLines), member(CrateNum-_, CL),
construct_crate(CrateNum, CrateLines, Crate)), CratePairs),
sort(CratePairs, CratePairsSorted),
list_to_assoc(CratePairsSorted, Crates).
input(Crates,Moves) --> crate_lines(CrateLines), { construct_crates(CrateLines, Crates) },
move_lines(Moves).
% DCG
state(S0,S1), [S1] --> [S0].
move_item(part1, m(0, _, _)) --> [].
move_item(part1, m(Count, From, To)) -->
{ Count1 is Count - 1},
state(Before, After),
{ get_assoc(From, Before, [It|FromItems]),
get_assoc(To, Before, ToItems),
put_assoc(From, Before, FromItems, After0),
put_assoc(To, After0, [It|ToItems], After) },
move_item(part1, m(Count1, From, To)).
move_item(part2, m(Count, From, To)) -->
state(Before, After),
{ get_assoc(From, Before, FromItems0),
get_assoc(To, Before, ToItems0),
length(MoveItems, Count),
append(MoveItems, FromItems1, FromItems0),
append(MoveItems, ToItems0, ToItems1),
put_assoc(From, Before, FromItems1, After0),
put_assoc(To, After0, ToItems1, After) }.
moves(_, []) --> [].
moves(Part, [M|Moves]) --> move_item(Part, M), moves(Part, Moves).
first([Item|_], Item).
top_items(Crates, TopItems) :-
assoc_to_values(Crates, CrateItems),
maplist(first, CrateItems, TopItemChs),
string_chars(TopItems, TopItemChs).
input(C,M) :- phrase_from_file(input(C,M), "day5.txt").
part(Part,Answer) :-
input(C, M),
phrase(moves(Part,M), [C], [C1]),
top_items(C1, Answer).
part1(Answer) :- part(part1, Answer).
part2(Answer) :- part(part2, Answer).
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment