2023-12-19 04:49:11 -06:00
|
|
|
:- use_module(library(pio)).
|
|
|
|
:- use_module(library(dcg/basics)).
|
|
|
|
:- initialization(main, main).
|
|
|
|
|
|
|
|
main([FileName|_]) :-
|
|
|
|
input(FileName, Workflows),
|
2023-12-20 01:15:01 -06:00
|
|
|
findall(
|
|
|
|
Count-Limit,
|
|
|
|
(
|
|
|
|
wf(Workflows, in, Route, Limit),
|
|
|
|
Limit = [x-Xmin-Xmax, m-Mmin-Mmax, a-Amin-Amax, s-Smin-Smax],
|
|
|
|
Count is (Xmax - Xmin)*(Mmax - Mmin)*(Amax - Amin)*(Smax - Smin),
|
|
|
|
write(Route), write(" - "), write(Limit), write(" - "), write(Count), nl
|
|
|
|
),
|
|
|
|
Limits),
|
|
|
|
length(Limits, LenLimits), write("lenlimits = "), write(LenLimits), nl,
|
|
|
|
maplist([Count-Limit, Count]>>(true), Limits, CountsOnly),
|
|
|
|
sum_list(CountsOnly, Answer), write("answer = "), write(Answer), nl,
|
|
|
|
true.
|
2023-12-19 04:49:11 -06:00
|
|
|
|
|
|
|
choices(Limit, N) :-
|
|
|
|
foldl([_-Min-Max, V0, V]>>(V is V0*(Max - Min + 1)), Limit, 1, N).
|
|
|
|
|
|
|
|
or_limits([Limit], Limit).
|
|
|
|
or_limits([Limit1, Limit2 | Limits], Limit) :-
|
|
|
|
findall(
|
|
|
|
Attr-Min-Max,
|
|
|
|
( member(Attr-Min1-Max1, Limit1), member(Attr-Min2-Max2, Limit2),
|
|
|
|
Min is min(Min1, Min2), Max is max(Max1, Max2)),
|
|
|
|
NewLimit),
|
|
|
|
or_limits([NewLimit|Limits], Limit).
|
|
|
|
|
2023-12-20 01:15:01 -06:00
|
|
|
% x -> [Min, Max)
|
|
|
|
wf(_, accept, [accept], [x-1-4001, m-1-4001, a-1-4001, s-1-4001]).
|
2023-12-19 04:49:11 -06:00
|
|
|
wf(Workflows, WorkflowName, [WorkflowName|Route], Limits) :-
|
|
|
|
\+ WorkflowName = accept, \+ WorkflowName = reject,
|
|
|
|
member(WorkflowName-Rules, Workflows),
|
|
|
|
with_rule(Workflows, Rules, Route, Limits).
|
|
|
|
|
|
|
|
with_rule(Workflows, [EndRule], Route, Limits) :-
|
|
|
|
wf(Workflows, EndRule, Route, Limits).
|
|
|
|
with_rule(Workflows, [Attr-Cond-N-Dest|Rules], Route, NewLimits) :-
|
|
|
|
% Either take the first route with its limit
|
|
|
|
( wf(Workflows, Dest, Route, Limits),
|
|
|
|
member(Attr-Min-Max, Limits),
|
|
|
|
combine(Min-Max, Cond-N, NewMin-NewMax)
|
|
|
|
% ...or skip the first route, given we satisfy its reverse limits
|
|
|
|
; with_rule(Workflows, Rules, Route, Limits),
|
|
|
|
member(Attr-Min-Max, Limits),
|
|
|
|
negate(Cond-N, NotCond-NotN),
|
|
|
|
combine(Min-Max, NotCond-NotN, NewMin-NewMax)
|
|
|
|
),
|
|
|
|
select(Attr-Min-Max, Limits, Attr-NewMin-NewMax, NewLimits).
|
|
|
|
|
|
|
|
negate('<'-N, '>'-NewN) :- NewN is N - 1.
|
|
|
|
negate('>'-N, '<'-NewN) :- NewN is N + 1.
|
2023-12-20 01:15:01 -06:00
|
|
|
combine(Min-Max, '<'-N, Min-NewMax) :- NewMax is min(N, Max), Min < NewMax.
|
2023-12-19 04:49:11 -06:00
|
|
|
combine(Min-Max, '>'-N, NewMin-Max) :- NewMin is max(N+1, Min), NewMin < Max.
|
2023-12-20 01:15:01 -06:00
|
|
|
|
2023-12-19 04:49:11 -06:00
|
|
|
% input parsing stuff below
|
|
|
|
input(FileName, Workflows) :-
|
|
|
|
phrase_from_file((workflows(Workflows), remainder(_)), FileName).
|
|
|
|
|
|
|
|
workflows([]) --> "\n", !.
|
|
|
|
workflows([Name-Rules|Ws]) -->
|
|
|
|
string_without("{", NameStr), "{", rules(Rules), "}\n", workflows(Ws),
|
|
|
|
{atom_codes(Name, NameStr)}.
|
|
|
|
|
|
|
|
rules([End]) --> dest(End).
|
|
|
|
rules([Rule|Rules]) --> rule(Rule), ",", rules(Rules).
|
|
|
|
|
|
|
|
rule(Attr-Cond-N-Dest) --> attr(Attr), cond(Cond), number(N), ":", dest(Dest).
|
|
|
|
|
|
|
|
attr(x) --> "x".
|
|
|
|
attr(m) --> "m".
|
|
|
|
attr(a) --> "a".
|
|
|
|
attr(s) --> "s".
|
|
|
|
cond('>') --> ">".
|
|
|
|
cond('<') --> "<".
|
|
|
|
dest(reject) --> "R", !.
|
|
|
|
dest(accept) --> "A", !.
|
|
|
|
dest(Dest) --> endrule(Dest).
|
|
|
|
endrule(Rule) --> string_without(",}", RuleStr), {atom_codes(Rule, RuleStr)}.
|