Advent of code 2023

Here’s my solution for today aoc2023/04/main.pl at 859f5e91a41db8cc3c2e42eaac9603ee26ea58a1 · meditans/aoc2023 · GitHub.
I had written the second part in a more verbose way, but your solution @emiruz inspired me to simplify it!

Where’s the fun in that :smile:? Jokes aside, I’m using my own collection of dcg parsing utils (pack dcg_tools), and my personal utilities (pack medikit). You can install them, or just read the source and copy what you need, and feel free to ask questions.

For parsing in particular, you could start using library(dcg/basics) and library(dcg/high_order) as @jan suggested!

2 Likes

Very nice… just 21 LOC! I have to start learning CHR, AoC seems like a good time to practice it. Is there any material you’d specifically recommend? I found a YouTube video and this PPT tutorial – and that’s about it …

1 Like

Neat. Just, there is no need to use `String` in SWI-Prolog’s DCGs. Just using "String" does the job. The DCG compiler finds the terminal and acts on its type dynamically. Using double quotes keeps the code portable.

1 Like

There is also a tutorial hosted at GitHub - Anniepoo/swiplchrtut: Tutorial for the CHR system, and a couple of books written by the creator of the CHR language, although with a more academic bent. I would suggest just trying to use it for AoC and developing a taste for when it’s useful as a tool. Ask in this forum, I myself have quite a lot of questions on the precise procedural semantics of CHR that I will have to get out in the next days.

Great tip, thank you!

I also used lazy_list_location//1 for day 3 and ran into problems with it; it seems to misbehave under some circumstances; wasn’t able to figure out exactly what is wrong with it, yet, though.

I had been parsing the input with:

schematic(Loci) --> `.`, !, schematic(Loci).
schematic(Loci) --> `\n`, !, schematic(Loci).
schematic([symbol(Line, Col, C) | More]) -->
    lazy_list_location(file(_, Line, Col, _)),
    [ C ], { \+ code_type(C, digit), C \== 0'. }, !,
    schematic(More).
schematic([number(Line, Col, Width, N) | More]) -->
    lazy_list_location(file(_, Line, Col, _)),
    integer(N), !,
    lazy_list_location(file(_, _, EndCol, _)),
    { Width is EndCol - Col },
    schematic(More).
schematic([]) --> [].

which seemed to produce more symbol/3 terms in the list than expected (just two “ghost” extras that weren’t in the input, out of 741!); I switched to

schematic(Loci) --> `.`, !, schematic(Loci).
schematic(Loci) --> `\n`, !, schematic(Loci).
schematic([symbol(Line, Col, C) | More]) -->
    [ C ], { \+ code_type(C, digit), C \== 0'. }, !,
    lazy_list_location(file(_, Line, Col0, _)), !, % <-- delayed call to lazy_list_location//1 to after the cut
    { Col is Col0 - 1 },
    schematic(More).
schematic([number(Line, Col, Width, N) | More]) -->
    lazy_list_location(file(_, Line, Col, _)),
    integer(N), !,
    lazy_list_location(file(_, _, EndCol, _)),
    { Width is EndCol - Col },
    schematic(More).
schematic([]) --> [].

and that fixed everything (!)

EDIT wow posting via email does not work very well; fixed indentation

(also, full solution is here)

1 Like

Nice ! You nailed it !

Its posted on another thread too, but here is a re-write (27 LOC) of day 3 solution, both parts. It uses DCG+CHR for a particularly concise implementation.

:- use_module(library(chr)).
:- use_module(library(dcg/basics)).

:- set_prolog_flag(chr_toplevel_show_store, false).

ns(N,V) :- number_string(N,V).

% Parse input, designate X,Y coordinates to each character.
t(Xs) --> t(1,1,Xs).
t(_,_,[]) --> [].
t(X0,_,Xs) --> "\n",{X is X0+1},!,t(X,1,Xs).
t(X0,Y0,[p(X0,Y0,Y0,[V])|Xs]) --> [V0],{char_code(V,V0)},{Y is Y0+1},!,t(X0,Y,Xs).

% Predicates for the constraint store.
:- chr_constraint p/4.
:- chr_constraint q/4.
:- chr_constraint k/3.
:- chr_constraint stage/1.

% Remove dot coordinates.
p(_,_,_,['.']) <=> true.

% Merge digits.
p(X,Y0,Y,V),p(X,Y01,Y1,V1) <=>
    Y01-Y=:=1,
    ns(_,V),ns(_,V1) | append(V,V1,V_),p(X,Y0,Y1,V_).

% Check if X1,Y1 (a symbol coordinate) is adjacent to a digit span.
adj(X1,Y1,X,Y0,Y) :- X1>=X-1,X+1>=X1,Y1>=Y0-1,Y+1>=Y1.

% iff stage(2), filter for digit spans adjacent to symbols.
stage(2),p(X1,Y1,Y1,_) \ p(X,Y0,Y,V) <=>
         ns(_,V),adj(X1,Y1,X,Y0,Y) | ns(N,V),q(X,Y0,Y,N).

% iff stage(3), group digit spans around star symbols.
stage(3),p(X1,Y1,Y1,['*']) \ q(X,Y0,Y,V) <=>
	 adj(X1,Y1,X,Y0,Y) | k(X1,Y1,[V]).
% iff stage(3), aggregate star groups.
stage(3) \ k(X,Y,V),k(X,Y,V1) <=> V\=V1 | append(V,V1,Vs),k(X,Y,Vs).

solve(File,Part1,Part2) :-
    phrase_from_file(t(Xs),File), % read file and parse with t DCG.
    maplist(call,Xs), % call all predicates to put into CHR store.
    %invoke stage(2) and sum qs.
    stage(2),aggregate_all(sum(N),find_chr_constraint(q(_,_,_,N)),Part1),
    % invoke stage(3) and sum ks with just 2 values.
    stage(3),aggregate_all(sum(N),(find_chr_constraint(k(_,_,[A,B])),N is A*B),Part2). 

It is an order of magnitude slower than @CapelliC solution unfortunately, but its a pretty naive implementation so its likely possible to write it in a more performant way whilst maintaining the DCG+CHR approach.

1 Like

Great work indeed.
But my good vibrations for constraints (and CHR in particular) has declined during the time, since I cannot see the benefits but just the additional problems in merging its semantic with the already overly complex (and sometime bizarre) semantic of Prolog (+attvars).
But I must thanks @ridgeworks for his work on clpBNR, that IMHO targets real problems in effective ways, and then keeps my attention alive…

2 Likes

As the docs say, it has a number of different representations. It is also slow. It is meant to support syntax_error//1, which can deal with the various representations and speed is typically not vital for reporting an error. Do not use it to keep track of positions for anything else.

Hey guys, day 5! Part 2 is a bit gnarly – I wen’t down the wrong rabbit hole on it, but I think I see a simple solution now. Here is a DCG+CHR solution to part 1 in 25 LOC. I’m still working on Part 2.

:- use_module(library(dcg/basics)).
:- use_module(library(chr)).

:- set_prolog_flag(chr_toplevel_show_store, false).

% Parse seed list.
seeds([]) --> [].
seeds([s(X)|Xs]) --> blanks,number(X),seeds(Xs).
% Parse rows.
rngs(_,_,[]) --> [].
rngs(Fr,To,[c(A-B-C,Fr,To)|Xs]) --> number(A),blanks,number(B),blanks,number(C),
				    "\n",rngs(Fr,To,Xs).
rngs(Fr,To,[c(A-B-C,Fr,To)]) --> number(A),blanks,number(B),blanks,number(C).
% Parse individual category.
cat([]) --> [].
cat(Rs) --> string(Fr),"-to-",string(To)," map:\n",rngs(Fr,To,Rs).
% Parse categories.
cats([Rs|Xs]) --> cat(Rs),"\n\n",!,cats(Xs).
cats([Rs]) --> cat(Rs).
% Parse file.
file(Seeds,Cats) --> "seeds:",seeds(Seeds),"\n\n",cats(Cats).

:- chr_constraint c/3.
:- chr_constraint s/1.
:- chr_constraint q/2.

c(D-S-L,`seed`,To) \ s(X) <=> X>=S,S+L-1>=X | N is X+D-S,q(N,To).

s(X) <=>  find_chr_constraint(c(_,`seed`,To)), q(X,To).

c(D-S-L,From,To) \ q(X,From) <=> X>=S,S+L-1>=X | N is X+D-S, q(N,To).

q(X,From) <=> From \= `location` | find_chr_constraint(c(_,From,To)), q(X,To).

solve(File,Part1) :-
    phrase_from_file(file(Ss,Cs0),File),
    flatten(Cs0,Cs),maplist(call,Cs),maplist(call,Ss),
    findall(X,find_chr_constraint(q(X,_)),Xs),!,
    min_member(Part1,Xs).

@CapelliC I really dislike having to do things like [0’s,0’e,0’e,0’d] in the code. Is there some way around that so that I can use strings without explicit conversion predicates?

EDIT: implementing @CapelliC advice RE literals.

backticks strings should do:

c(D-S-L,`seed`,To) \ s(X) <=> X>=S,S+L-1>=X | N is X+D-S,q(N,To).
1 Like

I was hoping it was something simple like that, thank you!

Awesome job, like the other CHR solution you posted yesterday! Only point, giving some better names to one-single letter constraints, or a short comment explaining what they are meant to be, would improve readability. I’m unsure where the different stages (seed → soil etc) are processed here.

Here’s my solution for both parts (comments are always welcome)

Just finished part 2 (below). I just wrote some code to try whether a location has a corresponding seed, and then tried all the locations in order. Since seeds are in very large blocks (as are the categories), I bound the solution first by stepping in units of 10000 and then finesse the final block of 10000 once I’ve found a solution. Its only really the last 20 lines or so that are specific to part2 – the rest is the same as part 1. Both parts together are here on Github. 44 LOC – not over the moon; feels like I’m missing some kind of key insight here which would have made for a more elegant solution.

:- use_module(library(dcg/basics)).
:- use_module(library(clpfd)).

% Parse seed list.
seeds([]) --> [].
seeds([X|Xs]) --> blanks,number(X),seeds(Xs).
% Parse rows.
rngs(_,_,[]) --> [].
rngs(Fr,To,[c(A-B-C,Fr,To)|Xs]) --> number(A),blanks,number(B),blanks,number(C),
				    "\n",rngs(Fr,To,Xs).
rngs(Fr,To,[c(A-B-C,Fr,To)]) --> number(A),blanks,number(B),blanks,number(C).
% Parse individual category.
cat([]) --> [].
cat(Rs) --> string(Fr),"-to-",string(To)," map:\n",rngs(Fr,To,Rs).
% Parse categories.
cats([Rs|Xs]) --> cat(Rs),"\n\n",!,cats(Xs).
cats([Rs]) --> cat(Rs).
% Parse file.
file(Seeds,Cats) --> "seeds:",seeds(Seeds),"\n\n",cats(Cats).

% Check if a location has a corresponding seed.
best(Ss,_,Try,`seed`) :-
    member(S-L,Ss),
    Try >= S, S+L-1 >= Try,!.
best(Ss,Cs,Try0,Name) :-
    member(c(D-S-L,Fr,Name),Cs),
    Try0 >= D, D+L-1 >= Try0,
    Try is Try0+S-D,!,
    best(Ss,Cs,Try,Fr).
best(Ss,Cs,Try,Name) :-
    memberchk(c(_,Fr,Name),Cs),
    best(Ss,Cs,Try,Fr).

pairs([],Acc,Acc) :- !.
pairs([A,B|T],Acc,Result) :- pairs(T,[A-B|Acc],Result).

until(Ss,Cs,_,X,X) :- best(Ss,Cs,X,`location`),!.
until(Ss,Cs,Inc,X0,Y) :- X is X0+Inc, until(Ss,Cs,Inc,X,Y).

solve(File,X) :-
    phrase_from_file(file(Ss,Cs0),File),
    pairs(Ss,[],Seeds),
    flatten(Cs0,Cs),
    until(Seeds,Cs,10000,0,X0),
    Start is X0-10000, until(Seeds,Cs,1,Start,X).

:slight_smile: Good old single letter variable names. I learned a language called J once – oh dead, you should see what that looks like… single letter everything! But I totally agree, CHRs are specially difficult to “execute mentally”, needs lots of comments.

Something I don’t love about CHR is that the order of constraints is not just important – it is crucial. If the order made no difference, it would lose capabilities, but the significance of the order is quite difficult to interpret on static code review.

1 Like

Its a beautiful solution but it contains a lot of Prolog features I never knew existed :slight_smile:

I don’t know what “dynamic” predicates are. So far as I can tell it uses clpfd implicitly to create an optimisation of sorts? Does it run fairly quickly?

Have you seen the stats for day 5? At the time of writing a 40% drop-off on completion of any part compared to day 4. Of those who did complete some part of the puzzle, 40%+ did not complete part 2.

This was pretty difficult for day 5!

1 Like

Probably the fact that since the transformation is linear, you can process intervals instead of single numbers.

Yes, I agree, and it’s why I tend to avoid computations with more than 3/5 rules in CHR. It starts to become magical when I read it again.

Dynamic predicates are predicates you can assert clauses of at runtime (check for assertz as a starting point). While I usually find this kind of behavior too side-effecty for my tastes I’m trying to de-empathize the role of ad-hoc datastructures, using just clauses instead. So the parsing creates a datastructure, but then, in set_knowledge, I extract all the subterms that look like information I want to have around, and assert those (and some cleanup).

The fact that I used clpfd is orthogonal to that, but it’s the key in having the solution run instantaneously - I mean the key is processing intervals instead of points, but clpfd makes it very pleasant to write. It’s probably one of my favorite libraries in prolog, to be fair.

What I had found tricky was that the range of the intervals at any given category isn’t exhaustive. So they can’t just be mapped to each other; fancier footwork is needed. I tried splitting and mapping intervals in various ways but it was too fiddly, I figured there must be some shortcut. Trying the numbers backwards (i.e. checking if a location has a corresponding seed) still takes <1s to find a solution.

I’ve read through a many of the solutions on /r/adventofcode/ – very few solutions, are as clean and systematic as yours.

Found on Reddit. This year is a bit different :slight_smile: