Hmmm I see. Re-testing several of the days. Adding the header makes no difference for me, but not using the lambdas is a huge difference: 20x speed difference for some days. Quite the caveat emptor …
Good points, thanks!
I actually tried CLPFD first, too, but found that some queries did not terminate within seconds, so I went with CLPQ instead.
Unfortunately I don’t have as much time to spend on AoC this year, otherwise I would’ve been more involved!
RE clpfd, oddly I think it’s because you used 10^13 instead of the number written out. The former doesn’t terminate within a reasonable waiting time for me but the latter finishes very quickly. You can try it with my code to see for yourself; a bit weird.
Right, that works.
The solution using CLPQ is much faster, though.
Day 19
Missed many days, but today seems good for using tabling.
:- use_module(library(dcg/high_order)).
:- use_module(library(yall)).
:- use_module(library(aggregate)).
:- table possible_ways(_,_,sum).
towel(T) --> string_without(`,\n`, T).
towels(Ts) --> sequence(towel, `, `, Ts).
design(D) --> string_without(`\n`, D).
designs(Ds) --> sequence(design, `\n`, Ds).
towels_and_designs(Ts-Ds) --> towels(Ts), `\n\n`, designs(Ds0), { append(Ds, [[]], Ds0) }.
input(I) :- phrase_from_file(towels_and_designs(I), 'day19.txt').
possible_ways(_, [], 1).
possible_ways(Towels, Design, N) :-
aggregate_all(sum(W), (member(T, Towels),
append(T, Rest, Design),
possible_ways(Towels, Rest, W)), N).
solve(P1,P2) :-
input(Ts-Ds),
maplist(possible_ways(Ts), Ds, Ways),
include(<(0), Ways, Possible),
length(Possible, P1),
sum_list(Ways, P2).
Here is a belated Day 15 from me. Its fairly short but it was very tedious to write down. It is a good exercise and example of logical state management I think.
Here is a belated Day 16. The code is about concise as I can make it. Dijksktra was the only possible solution here because Part 2 requires all shortest paths between source and sink along with a record of all visited nodes. The code is very slow (about 90-130sec). Profiling suggest it spends all its time doing heap or rb lookups, so I’m not sure what can be done about that.
Here is my day 17. This questions is easy with clpfd, but difficult otherwise. It has the highest abandonment rate for Part2 so far this year.
:- use_module([library(clpfd), library(yall)]).
combo(Code,_,_,_,Code) :- Code #>= 0, 4 #> Code.
combo(Code0,A,B,C,Code) :- Code0 #> 3, I #= 1+mod(Code0,4), element(I,[A,B,C],Code).
execute([0,Y0|Rest],P,A0,B,C,XX,O) :- combo(Y0,A0,B,C,Y), A #= A0 // (2^Y), execute(Rest,P,A,B,C,XX,O).
execute([1,Y|Rest],P,A,B0,C,XX,O) :- B #= B0 xor Y, execute(Rest,P,A,B,C,XX,O).
execute([2,Y0|Rest],P,A,B0,C,XX,O) :- combo(Y0,A,B0,C,Y), B #= mod(Y,8), execute(Rest,P,A,B,C,XX,O).
execute([3,_|Rest],P,0,B,C,XX,O) :- execute(Rest,P,0,B,C,XX,O).
execute([3,Y|_],P0,A,B,C,XX,O) :- length(X,Y), append(X,P,P0), execute(P,P0,A,B,C,XX,O).
execute([4,_|Rest],P,A,B0,C,XX,O) :- B #= B0 xor C, execute(Rest, P,A,B,C,XX,O).
execute([5,Y0|Rest],P,A,B,C,XX,O) :- combo(Y0,A,B,C,Y), X #= Y mod 8, execute(Rest, P,A,B,C,[X|XX],O).
execute([6,Y0|Rest],P,A,B0,C,XX,O) :- combo(Y0,A,B0,C,Y), B #= A // (2^Y), execute(Rest,P,A,B,C,XX,O).
execute([7,Y0|Rest],P,A,B,C0,XX,O) :- combo(Y0,A,B,C0,Y), C #= A // (2^Y), execute(Rest,P,A,B,C,XX,O).
execute([], _,_,_,_,O0,O) :- reverse(O0,O).
solve(In, Part1, Part2) :-
read_file_to_string(In, S, []),
re_foldl([_{0:N},[N|V0],V0]>>true, "\\d+"/t, S, [A,B,C|Prog], [], []),
execute(Prog,Prog,A,B,C,[],Part1),
Part2 #> 0, execute(Prog,Prog,Part2,B,C,[],Prog), labeling([bisect],[Part2]).
Here is Day 18. The walk/3 predicate implements Djikstra again: I think its about as concise as it can be made in Prolog.
Here is my take on day 19:
:- table walk/2.
walk(S,N) :-
opts(Os),
aggregate_all(sum(N0),(member(O,Os), string_concat(O,T,S),
(T="" -> N0=1 ; walk(T,N0))), N).
solve(In, Part1, Part2) :-
read_file_to_string(In, S, []),
string_concat(S0, S2, S), string_concat(S1, "\n\n", S0),
re_foldl([_{0:X},[X|V0],V0]>>true, "[a-z]+", S1, Opts, [], []),
re_foldl([_{0:X},[X|V0],V0]>>true, "[a-z]+", S2, Pats, [], []),
retractall(opts(_)), asserta(opts(Opts)),
convlist([X,N]>>(walk(X,N),N\=0), Pats, Counts),
aggregate_all(count-sum(C), member(C,Counts), Part1-Part2).
Here is day 20. Its straightforward if you note that there is just one path through the maze. Much more difficult if you ignore that and attempt to solve the general problem.
path(X-Y, Prev, Acc, Final) :-
member(I-J, [0-1,1-0,-1-0,0-(-1)]), A is I+X, B is J+Y,
\+ p(A,B,'#'), A-B \= Prev,
!, path(A-B, X-Y, [X-Y|Acc], Final).
path(End, _, Acc, [End|Acc]).
solve(In, Part1, Part2) :-
read_file_to_string(In, S, []), string_chars(S,Cs0),
nth0(Cols, Cs0, '\n'), !, exclude(=('\n'), Cs0, Cs),
findall(I-J-C, (nth0(X,Cs,C), I is mod(X,Cols), J is X//Cols), Coo),
retractall(p(_,_,_)), maplist([I-J-C]>>asserta(p(I,J,C)), Coo),
p(X0,Y0,'S'), path(X0-Y0, none, [], Path),
lazy_findall(P1-P2,
( nth0(I1, Path, X-Y), nth0(I2, Path, I-J), I1<I2,
Man is abs(X-I) + abs(Y-J),
(2>=Man, abs(I1-I2) - Man >= 100->P1=1; P1=0),
(20>=Man, abs(I1-I2) - Man >= 100->P2=1; P2=0) ), Calc),
foldl([A-B,T1-T2,T3-T4]>>(T3 is T1+A, T4 is T2+B), Calc, 0-0, Part1-Part2).
@jan attempting to use aggregate_all/3 for this simple calculation uses about 6Gb of RAM for < 9000^2 items. Meanwhile lazy_findall/3 is great for memory but it is epically slow. Can you suggest a way to speed up the above (by orders of magnitude)?
I am not Jan so sorry about this.
Could you show how you used aggregate_all/3?
This is relevant because (from the docs and also easy to see in the source):
The Template values
count
,sum(X)
,max(X)
,min(X)
,max(X,W)
andmin(X,W)
are processed incrementally rather than using findall/3 and run in constant memory.
Any other template just uses findall/3 internally.
aggregate_all(sum(P1)-sum(P2),
( nth0(I1, Path, X-Y), nth0(I2, Path, I-J), I1<I2,
Man is abs(X-I) + abs(Y-J),
(2>=Man, abs(I1-I2) - Man >= 100->P1=1; P1=0),
(20>=Man, abs(I1-I2) - Man >= 100->P2=1; P2=0) ), Part1-Part2)
My partial day 21 is here, day 22 is here and day 23 is here. I tried to learn lazy_list/3 but I’m not sure I can recommend it.
I’m missing Part 2’s for 21 and 24, but except for that this year is complete. I regret I may have to do those parts in Python. Especially with regard to 24, it felt like it should admit a neat Prolog solution, since its fault diagnostics of a binary circuit (AND, OR, XOR), but working out what CLP(B) actually does in code seem much more difficult than it needs to be. If someone else has a neat solution to 24 part 2, please post it!