clpz:monotonic.
:- use_module(library(clpb)).
:- use_module(library(gensym)).
:- use_module(library(simplex)).

light(0)     --> ".".
light(1)     --> "#".
lights(Ls)   --> "[", sequence(light, "", Ls), "]".
button(Ls)   --> "(", sequence(number,",",Ls), ")".
joltages(Js) --> "{", sequence(number,",",Js), "}".

where(_,[])     --> [].
where(I,Is_)    --> [B], { if_(B = 1, Is_ = [I|Is], Is_ = Is), #I_ #= #I + 1 }, where(I_,Is).
where(Bools,Is) :- phrase(where(0,Is),Bools).
machine(machine(NButtons,ButtonGroups,Lights,Joltages)) -->
    lights(Lights), " ", sequence(button," ",Buttons), " ", joltages(Joltages),
		{ length(Buttons,NButtons), maplist(same_length(Lights),Bs), maplist(where,Bs,Buttons),
			transpose(Bs,Bs_), maplist(where,Bs_,ButtonGroups) }.
input(I) :- phrase_from_file(sequence(machine,"\n",I),"i/10.in").
get_presses(NButtons,ButtonGroups,Presses,GroupedPresses) :- 
    length(Presses,NButtons), maplist(maplist(Presses+\Idx^Press^nth0(Idx,Presses,Press)),ButtonGroups,GroupedPresses).

minimize_presses(Ps,N)   :- length(Ps,L), N in 0..L, indomain(N), sat(card([N],Ps)).
set_light(Presses,Light) :- foldl(\V^Xor0^Xor1^(Xor1 = V#Xor0),Presses,0,Xor), sat(Xor =:= Light).
part1(machine(NButtons,ButtonGroups,Lights,_),P1) :- get_presses(NButtons,ButtonGroups,Presses,GroupedPresses),
    maplist(set_light,GroupedPresses,Lights), minimize_presses(Presses,P1).

make_whole(Var)       --> constraint(integral(Var)).
set_joltage(Var,Jolt) --> constraint(Var = Jolt).
least_presses(Presses,GroupedPresses,Joltages) -->
    foldl(make_whole,Presses), foldl(set_joltage,GroupedPresses,Joltages), minimize(Presses), objective.
part2(machine(NButtons,ButtonGroups,_,Joltages),P2) :- get_presses(NButtons,ButtonGroups,Presses,GroupedPresses),
    maplist(gensym(b),Presses), gen_state(S0), least_presses(Presses,GroupedPresses,Joltages,S0,P2).

part(P)      --> maplist(P), sum_list. % should use sum/3, but it doesn't work for some reason
solve(P1,P2) :- input(Ms), part(part1,Ms,P1), part(part2,Ms,P2).
test         :- make_test(day(10),solve,449,17848).


Luckily Scryer has library(clpb) and library(simplex), otherwise today would have been much messier.

Is this cheating? I don't think so, since the whole point of Prolog is to be magical. However, this day didn't feel very satisfying, either.


~/aoc25pl/10