d20p1
This commit is contained in:
parent
43a83d487b
commit
a4856cf9ef
58
20/input.txt
Normal file
58
20/input.txt
Normal file
@ -0,0 +1,58 @@
|
|||||||
|
%hb -> mj
|
||||||
|
%mx -> mt, xz
|
||||||
|
%xh -> qc
|
||||||
|
%tg -> cq
|
||||||
|
%kp -> xz, nj
|
||||||
|
%mj -> jj, lv
|
||||||
|
%cq -> jm
|
||||||
|
%mt -> sj, xz
|
||||||
|
&jj -> hb, lz, rk, xv, vj, vh, lv
|
||||||
|
%rm -> bz, xq
|
||||||
|
%hx -> bz
|
||||||
|
%xv -> lz
|
||||||
|
%xx -> kp, xz
|
||||||
|
%pt -> vx
|
||||||
|
&xz -> bq, gr, sj, rv, zf
|
||||||
|
%vx -> gf, cv
|
||||||
|
%xb -> xz, bq
|
||||||
|
%xk -> gf, rd
|
||||||
|
%lv -> zk
|
||||||
|
&rk -> gh
|
||||||
|
%kn -> gf, tz
|
||||||
|
&gh -> rx
|
||||||
|
%sj -> vp
|
||||||
|
%jm -> vm, bz
|
||||||
|
%rr -> rv, xz
|
||||||
|
%tz -> rz
|
||||||
|
%gg -> kn
|
||||||
|
&cd -> gh
|
||||||
|
%qc -> kh, bz
|
||||||
|
%kb -> gf
|
||||||
|
%vp -> xz, xx
|
||||||
|
%fb -> bz, tg
|
||||||
|
%rd -> cp
|
||||||
|
%qn -> vh, jj
|
||||||
|
%xr -> jj
|
||||||
|
%tp -> rm, bz
|
||||||
|
%cp -> gg
|
||||||
|
&bz -> qx, cq, xh, fb, tg
|
||||||
|
%qq -> pt, gf
|
||||||
|
%xq -> bz, hx
|
||||||
|
%gx -> jj, qv
|
||||||
|
%bq -> rr
|
||||||
|
%cv -> gf, kb
|
||||||
|
%zk -> jj, xv
|
||||||
|
&zf -> gh
|
||||||
|
&qx -> gh
|
||||||
|
%vh -> gx
|
||||||
|
%qv -> xr, jj
|
||||||
|
%lz -> qn
|
||||||
|
broadcaster -> fb, xk, gr, vj
|
||||||
|
%nj -> xz
|
||||||
|
%gr -> xz, xb
|
||||||
|
%kh -> tp, bz
|
||||||
|
%vm -> bz, xh
|
||||||
|
%rz -> qq, gf
|
||||||
|
&gf -> tz, cd, rd, xk, pt, cp, gg
|
||||||
|
%rv -> mx
|
||||||
|
%vj -> hb, jj
|
123
20/part1.pl
Normal file
123
20/part1.pl
Normal file
@ -0,0 +1,123 @@
|
|||||||
|
:- use_module(library(pio)).
|
||||||
|
:- use_module(library(dcg/basics)).
|
||||||
|
:- initialization(main, main).
|
||||||
|
|
||||||
|
% ================================ begin stupid ===============================
|
||||||
|
main([FileName|_]) :-
|
||||||
|
input(FileName, Circuit),
|
||||||
|
cycle(Circuit, 0, [], [], First-Cycle-_, Counts),
|
||||||
|
NCycles is 1000 div Cycle, Leftovers is 1000 mod Cycle,
|
||||||
|
CycleEnd1 is First + Cycle,
|
||||||
|
|
||||||
|
slice(Counts, 0, First, FirstCounts),
|
||||||
|
sumpairs(FirstCounts, FirstL-FirstH),
|
||||||
|
slice(Counts, First, CycleEnd1, CycleCounts),
|
||||||
|
sumpairs(CycleCounts, CycleL-CycleH),
|
||||||
|
slice(Counts, First, Leftovers, LeftoverCounts),
|
||||||
|
sumpairs(LeftoverCounts, LeftoverL-LeftoverH),
|
||||||
|
|
||||||
|
Answer is (FirstL + NCycles*CycleL + LeftoverL)*
|
||||||
|
(FirstH + NCycles*CycleH + LeftoverH),
|
||||||
|
write("answer="), write(Answer), nl.
|
||||||
|
|
||||||
|
sumpairs([], 0-0).
|
||||||
|
sumpairs([A-B|List], SumA-SumB) :-
|
||||||
|
sumpairs(List, A1-B1), SumA is A + A1, SumB is B + B1.
|
||||||
|
|
||||||
|
cycle(Circuit, N, Hist, Counts, First-Cycle-Hist, Counts) :-
|
||||||
|
match(Circuit, Hist, Cycle),
|
||||||
|
write("match. N="), write(N), write(", cycle="), write(Cycle), nl,
|
||||||
|
First is N - Cycle,
|
||||||
|
!.
|
||||||
|
cycle(Circuit, N, Hist, Counts, X, Y) :-
|
||||||
|
% \+ match(Circuit, Hist, _), % remove this for performance.
|
||||||
|
run([button-l-broadcaster], Circuit, NewCircuit, Ls-Hs),
|
||||||
|
NewN is N + 1,
|
||||||
|
NewHist = [Circuit|Hist],
|
||||||
|
% write(NewN), write(": "), write(Ls-Hs), write(" - "), write(NewCircuit), nl,
|
||||||
|
cycle(NewCircuit, NewN, NewHist, [Ls-Hs|Counts], X, Y).
|
||||||
|
|
||||||
|
match(Map, [Map|_], 1) :- !.
|
||||||
|
match(Map, [_|Entries], N) :-
|
||||||
|
match(Map, Entries, NextN),
|
||||||
|
N is NextN + 1.
|
||||||
|
|
||||||
|
slice(L, From, To, R):-
|
||||||
|
ToX is To + 1,
|
||||||
|
length(LFrom, From), length([_|LTo], ToX),
|
||||||
|
append(LTo, _, L), append(LFrom, R, LTo).
|
||||||
|
% ================================ end stupid ===============================
|
||||||
|
|
||||||
|
% part1
|
||||||
|
run1000(Circuit, Answer) :-
|
||||||
|
length(Range, 1000),
|
||||||
|
foldl(
|
||||||
|
{Circuit}/[_, In-Lin-Hin, Out-Lout-Hout]>>(
|
||||||
|
run([button-l-broadcaster], In, Out, L-H),
|
||||||
|
Lout is L+Lin, Hout is H+Hin),
|
||||||
|
Range, Circuit-0-0, _-Lx-Hx),
|
||||||
|
Answer is Lx*Hx.
|
||||||
|
|
||||||
|
% code to run one circuit
|
||||||
|
run([], Circuit, Circuit, 0-0).
|
||||||
|
run([Src-Level-Target|Pulses], CircuitIn, CircuitOut, Ls-Hs) :-
|
||||||
|
( member(Type-Target-State-Dests, CircuitIn)
|
||||||
|
-> /*write([Src, Level, Target]), write(" -> "),
|
||||||
|
write([Type, Target, State, Dests]), write(" = "),*/
|
||||||
|
call(Type, Src, Level, State, NewState, Out),
|
||||||
|
send(Target, Out, Dests, AdditionalPulses),
|
||||||
|
% write(NewState-AdditionalPulses), nl,
|
||||||
|
select(Type-Target-State-Dests, CircuitIn,
|
||||||
|
Type-Target-NewState-Dests, Circuit1),
|
||||||
|
append(Pulses, AdditionalPulses, NewPulses),
|
||||||
|
run(NewPulses, Circuit1, CircuitOut, NextLs-NextHs)
|
||||||
|
; run(Pulses, CircuitIn, CircuitOut, NextLs-NextHs)
|
||||||
|
),
|
||||||
|
call(Level, NextLs-NextHs, Ls-Hs).
|
||||||
|
|
||||||
|
l(L1s-H1s, L2s-H1s) :- L2s is L1s + 1.
|
||||||
|
h(L1s-H1s, L1s-H2s) :- H2s is H1s + 1.
|
||||||
|
|
||||||
|
broadcaster(_, l, x, x, l).
|
||||||
|
|
||||||
|
ff(_, h, State, State, none).
|
||||||
|
ff(_, l, 0, 1, h).
|
||||||
|
ff(_, l, 1, 0, l).
|
||||||
|
|
||||||
|
nand(Src, Level, State, NewState, OutLevel) :-
|
||||||
|
select(Src-_, State, Src-Level, NewState),
|
||||||
|
(maplist([_-h]>>(true), NewState) -> OutLevel = l; OutLevel = h).
|
||||||
|
|
||||||
|
send(_, none, _, []).
|
||||||
|
send(From, Level, Dests, Pulses) :-
|
||||||
|
\+ Level = none,
|
||||||
|
maplist({Level}/[Dest, From-Level-Dest]>>(true), Dests, Pulses).
|
||||||
|
|
||||||
|
% input initialization
|
||||||
|
prefill_nands([], Circuit, Circuit).
|
||||||
|
prefill_nands([_-Src-_-Dests|Nodes], CircuitIn, CircuitOut) :-
|
||||||
|
convlist(
|
||||||
|
{CircuitIn}/[Dest, Dest]>>(member(nand-Dest-_-_, CircuitIn)),
|
||||||
|
Dests, NandDests),
|
||||||
|
foldl(fill_one_nand(Src), NandDests, CircuitIn, Circuit1),
|
||||||
|
prefill_nands(Nodes, Circuit1, CircuitOut).
|
||||||
|
|
||||||
|
fill_one_nand(Src, Nand, CIn, COut) :-
|
||||||
|
select(nand-Nand-State-Dests, CIn, nand-Nand-[Src-l|State]-Dests, COut).
|
||||||
|
|
||||||
|
% input parsing stuff below
|
||||||
|
input(FileName, Circuit) :-
|
||||||
|
phrase_from_file(modules(EmptyCircuit), FileName),
|
||||||
|
prefill_nands(EmptyCircuit, EmptyCircuit, Circuit).
|
||||||
|
|
||||||
|
modules([]) --> eos, !.
|
||||||
|
modules([Module|Modules]) --> module(Module), "\n", modules(Modules).
|
||||||
|
|
||||||
|
module(broadcaster-broadcaster-x-Dests) --> "broadcaster -> ", dests(Dests).
|
||||||
|
module(ff-Name-0-Dests) --> "%", node(Name), " -> ", dests(Dests).
|
||||||
|
module(nand-Name-[]-Dests) --> "&", node(Name), " -> ", dests(Dests).
|
||||||
|
|
||||||
|
dests([Dest]) --> node(Dest).
|
||||||
|
dests([Dest|Dests]) --> node(Dest), ", ", dests(Dests).
|
||||||
|
|
||||||
|
node(Name) --> string_without(", \n", NameStr), {atom_codes(Name, NameStr)}.
|
5
20/test.txt
Normal file
5
20/test.txt
Normal file
@ -0,0 +1,5 @@
|
|||||||
|
broadcaster -> a, b, c
|
||||||
|
%a -> b
|
||||||
|
%b -> c
|
||||||
|
%c -> inv
|
||||||
|
&inv -> a
|
5
20/test2.txt
Normal file
5
20/test2.txt
Normal file
@ -0,0 +1,5 @@
|
|||||||
|
broadcaster -> a
|
||||||
|
%a -> inv, con
|
||||||
|
&inv -> b
|
||||||
|
%b -> con
|
||||||
|
&con -> output
|
Loading…
Reference in New Issue
Block a user