Skip to content

Instantly share code, notes, and snippets.

@ljos
Last active December 10, 2020 17:17
Show Gist options
  • Select an option

  • Save ljos/0d9f094dafbf801c9f79372ab87be9d7 to your computer and use it in GitHub Desktop.

Select an option

Save ljos/0d9f094dafbf801c9f79372ab87be9d7 to your computer and use it in GitHub Desktop.

Revisions

  1. ljos revised this gist Dec 10, 2020. 1 changed file with 0 additions and 1 deletion.
    1 change: 0 additions & 1 deletion advent_10.pl
    Original file line number Diff line number Diff line change
    @@ -30,7 +30,6 @@
    assert_dag(T).

    :- table n_paths/2.

    n_paths(N, 1) :- \+ edge(N, _).
    n_paths(N, Sum) :-
    aggregate(set(C), edge(N, C), Children),
  2. ljos revised this gist Dec 10, 2020. 1 changed file with 1 addition and 4 deletions.
    5 changes: 1 addition & 4 deletions advent_10.pl
    Original file line number Diff line number Diff line change
    @@ -37,9 +37,6 @@
    maplist(n_paths, Children, Vals),
    sum(Vals, #=, Sum).

    n_paths(Sum) :-
    n_paths(0, Sum).

    main(Part1, Part2) :-
    phrase_from_file(sequence(n, List), 'advent_10_inp.txt'),
    sort(List, Adapters),
    @@ -48,4 +45,4 @@
    Part1 #= A * C,
    retractall(edge(_, _)),
    assert_dag([0|Adapters]),
    n_paths(Part2).
    n_paths(0, Part2).
  3. ljos revised this gist Dec 10, 2020. 1 changed file with 0 additions and 1 deletion.
    1 change: 0 additions & 1 deletion advent_10.pl
    Original file line number Diff line number Diff line change
    @@ -16,7 +16,6 @@
    arrange([_|T], Jmax, J, Cs) :-
    arrange(T, Jmax, J, Cs).


    assert_edge(N, C) :- assertz(edge(N, C)).

    children(N, [C|T], [C|Children]) :-
  4. ljos revised this gist Dec 10, 2020. 1 changed file with 6 additions and 10 deletions.
    16 changes: 6 additions & 10 deletions advent_10.pl
    Original file line number Diff line number Diff line change
    @@ -4,19 +4,15 @@

    n(N) --> integer(N), "\n".

    arrange(_, Jmax, Jmax, [0, 0, 1]).
    arrange([H|T], Jmax, J, [A, B, C]) :-
    arrange(_, Jmax, Jmax, [0, 1]).
    arrange([H|T], Jmax, J, [A, C]) :-
    1 #= H - J,
    A0 #= A - 1,
    arrange(T, Jmax, H, [A0, B, C]).
    arrange([H|T], Jmax, J, [A, B, C]) :-
    2 #= H - J,
    B0 #= B - 1,
    arrange(T, Jmax, H, [A, B0, C]).
    arrange([H|T], Jmax, J, [A, B, C]) :-
    arrange(T, Jmax, H, [A0, C]).
    arrange([H|T], Jmax, J, [A, C]) :-
    3 #= H - J,
    C0 #= C - 1,
    arrange(T, Jmax, H, [A, B, C0]).
    arrange(T, Jmax, H, [A, C0]).
    arrange([_|T], Jmax, J, Cs) :-
    arrange(T, Jmax, J, Cs).

    @@ -49,7 +45,7 @@
    phrase_from_file(sequence(n, List), 'advent_10_inp.txt'),
    sort(List, Adapters),
    max_list(Adapters, Max),
    arrange(Adapters, Max, 0, [A, _, C]), !,
    arrange(Adapters, Max, 0, [A, C]), !,
    Part1 #= A * C,
    retractall(edge(_, _)),
    assert_dag([0|Adapters]),
  5. ljos revised this gist Dec 10, 2020. 1 changed file with 3 additions and 5 deletions.
    8 changes: 3 additions & 5 deletions advent_10.pl
    Original file line number Diff line number Diff line change
    @@ -20,6 +20,7 @@
    arrange([_|T], Jmax, J, Cs) :-
    arrange(T, Jmax, J, Cs).


    assert_edge(N, C) :- assertz(edge(N, C)).

    children(N, [C|T], [C|Children]) :-
    @@ -33,26 +34,23 @@
    maplist(assert_edge(H), C),
    assert_dag(T).

    :- table n_paths/2.

    n_paths(N, 1) :- \+ edge(N, _).
    n_paths(N, Sum) :- sum(N, Sum).
    n_paths(N, Sum) :-
    aggregate(set(C), edge(N, C), Children),
    maplist(n_paths, Children, Vals),
    sum(Vals, #=, Sum),
    assertz(sum(N, Sum)).
    sum(Vals, #=, Sum).

    n_paths(Sum) :-
    n_paths(0, Sum).


    main(Part1, Part2) :-
    phrase_from_file(sequence(n, List), 'advent_10_inp.txt'),
    sort(List, Adapters),
    max_list(Adapters, Max),
    arrange(Adapters, Max, 0, [A, _, C]), !,
    Part1 #= A * C,
    retractall(edge(_, _)),
    retractall(sum(_, _)),
    assert_dag([0|Adapters]),
    n_paths(Part2).
  6. ljos revised this gist Dec 10, 2020. 1 changed file with 0 additions and 1 deletion.
    1 change: 0 additions & 1 deletion advent_10.pl
    Original file line number Diff line number Diff line change
    @@ -20,7 +20,6 @@
    arrange([_|T], Jmax, J, Cs) :-
    arrange(T, Jmax, J, Cs).


    assert_edge(N, C) :- assertz(edge(N, C)).

    children(N, [C|T], [C|Children]) :-
  7. ljos revised this gist Dec 10, 2020. 9 changed files with 0 additions and 0 deletions.
    File renamed without changes.
    File renamed without changes.
    File renamed without changes.
    File renamed without changes.
    File renamed without changes.
    File renamed without changes.
    File renamed without changes.
    File renamed without changes.
    File renamed without changes.
  8. ljos revised this gist Dec 10, 2020. 1 changed file with 59 additions and 0 deletions.
    59 changes: 59 additions & 0 deletions advent_10.pl
    Original file line number Diff line number Diff line change
    @@ -0,0 +1,59 @@
    :- use_module(library(clpfd)).
    :- use_module(library(dcg/basics)).
    :- use_module(library(dcg/high_order)).

    n(N) --> integer(N), "\n".

    arrange(_, Jmax, Jmax, [0, 0, 1]).
    arrange([H|T], Jmax, J, [A, B, C]) :-
    1 #= H - J,
    A0 #= A - 1,
    arrange(T, Jmax, H, [A0, B, C]).
    arrange([H|T], Jmax, J, [A, B, C]) :-
    2 #= H - J,
    B0 #= B - 1,
    arrange(T, Jmax, H, [A, B0, C]).
    arrange([H|T], Jmax, J, [A, B, C]) :-
    3 #= H - J,
    C0 #= C - 1,
    arrange(T, Jmax, H, [A, B, C0]).
    arrange([_|T], Jmax, J, Cs) :-
    arrange(T, Jmax, J, Cs).


    assert_edge(N, C) :- assertz(edge(N, C)).

    children(N, [C|T], [C|Children]) :-
    C - N #>= 1 #/\ C - N #=< 3,
    !, children(N, T, Children).
    children(_, _, []).

    assert_dag([]).
    assert_dag([H|T]) :-
    children(H, T, C),
    maplist(assert_edge(H), C),
    assert_dag(T).


    n_paths(N, 1) :- \+ edge(N, _).
    n_paths(N, Sum) :- sum(N, Sum).
    n_paths(N, Sum) :-
    aggregate(set(C), edge(N, C), Children),
    maplist(n_paths, Children, Vals),
    sum(Vals, #=, Sum),
    assertz(sum(N, Sum)).

    n_paths(Sum) :-
    n_paths(0, Sum).


    main(Part1, Part2) :-
    phrase_from_file(sequence(n, List), 'advent_10_inp.txt'),
    sort(List, Adapters),
    max_list(Adapters, Max),
    arrange(Adapters, Max, 0, [A, _, C]), !,
    Part1 #= A * C,
    retractall(edge(_, _)),
    retractall(sum(_, _)),
    assert_dag([0|Adapters]),
    n_paths(Part2).
  9. ljos revised this gist Dec 9, 2020. 1 changed file with 2 additions and 2 deletions.
    4 changes: 2 additions & 2 deletions advent_9.pl
    Original file line number Diff line number Diff line change
    @@ -8,8 +8,8 @@

    dom([P|Preamble], V) :-
    foldl(union_, Preamble, P, Domain),
    A in Domain,
    B in Domain,
    [A, B] ins Domain,
    A #\= B,
    V #= A + B,
    indomain(V).

  10. ljos revised this gist Dec 9, 2020. 1 changed file with 4 additions and 1 deletion.
    5 changes: 4 additions & 1 deletion advent_9.pl
    Original file line number Diff line number Diff line change
    @@ -32,13 +32,16 @@

    find([], _, []).
    find([H|T], Target, Seq) :-
    find_([H|T], 0, Target, Seq);
    find_([H|T], 0, Target, Seq).
    find([_|T], Target, Seq) :-
    find(T, Target, Seq).

    main(Part1, Part2) :-
    phrase_from_file(sequence(n, List), 'advent_9_inp.txt'),
    validate(List, Part1),
    find(List, Part1, Example),
    length(Example, Length),
    Length #> 1,
    min_member(Min, Example),
    max_member(Max, Example),
    Part2 #= Min + Max.
  11. ljos revised this gist Dec 9, 2020. 1 changed file with 0 additions and 4 deletions.
    4 changes: 0 additions & 4 deletions advent_9.pl
    Original file line number Diff line number Diff line change
    @@ -23,10 +23,6 @@
    validate([_|Numbers], Invalid) :-
    validate(Numbers, Invalid).

    part_1(Invalid) :-
    phrase_from_file(sequence(n, List), 'advent_9_inp.txt'),
    validate(List, Invalid).

    find_([H|T], Sum0, Target, [H|Seq]) :-
    Sum #= Sum0 + H,
    Sum #< Target,
  12. ljos revised this gist Dec 9, 2020. 1 changed file with 2 additions and 2 deletions.
    4 changes: 2 additions & 2 deletions advent_9.pl
    Original file line number Diff line number Diff line change
    @@ -16,9 +16,9 @@
    check(Preamble, N) :-
    \+ dom(Preamble, N).

    validate([N|Numbers], Invalid) :-
    validate(Numbers, Invalid) :-
    length(Preamble, 25),
    append(Preamble, [Invalid | _], [N|Numbers]),
    append(Preamble, [Invalid | _], Numbers),
    check(Preamble, Invalid).
    validate([_|Numbers], Invalid) :-
    validate(Numbers, Invalid).
  13. ljos revised this gist Dec 9, 2020. 1 changed file with 48 additions and 0 deletions.
    48 changes: 48 additions & 0 deletions advent_9.pl
    Original file line number Diff line number Diff line change
    @@ -0,0 +1,48 @@
    :- use_module(library(clpfd)).
    :- use_module(library(dcg/basics)).
    :- use_module(library(dcg/high_order)).

    n(N) --> integer(N), "\n".

    union_(E, D, '\\/'(E, D)).

    dom([P|Preamble], V) :-
    foldl(union_, Preamble, P, Domain),
    A in Domain,
    B in Domain,
    V #= A + B,
    indomain(V).

    check(Preamble, N) :-
    \+ dom(Preamble, N).

    validate([N|Numbers], Invalid) :-
    length(Preamble, 25),
    append(Preamble, [Invalid | _], [N|Numbers]),
    check(Preamble, Invalid).
    validate([_|Numbers], Invalid) :-
    validate(Numbers, Invalid).

    part_1(Invalid) :-
    phrase_from_file(sequence(n, List), 'advent_9_inp.txt'),
    validate(List, Invalid).

    find_([H|T], Sum0, Target, [H|Seq]) :-
    Sum #= Sum0 + H,
    Sum #< Target,
    find_(T, Sum, Target, Seq).
    find_([H|_], Sum0, Target, [H]) :-
    Target #= Sum0 + H.

    find([], _, []).
    find([H|T], Target, Seq) :-
    find_([H|T], 0, Target, Seq);
    find(T, Target, Seq).

    main(Part1, Part2) :-
    phrase_from_file(sequence(n, List), 'advent_9_inp.txt'),
    validate(List, Part1),
    find(List, Part1, Example),
    min_member(Min, Example),
    max_member(Max, Example),
    Part2 #= Min + Max.
  14. ljos revised this gist Dec 8, 2020. 1 changed file with 9 additions and 14 deletions.
    23 changes: 9 additions & 14 deletions advent_8.pl
    Original file line number Diff line number Diff line change
    @@ -2,17 +2,12 @@
    :- use_module(library(dcg/high_order)).

    instruction(Inst-Val) -->
    [A, B, C],
    blank,
    integer(Val),
    blank,
    [A, B, C], " ", integer(Val), "\n",
    { atom_codes(Inst, [A,B,C]) }.

    instructions(Insts) --> sequence(instruction, Insts).

    assert_insts(Insts) :-
    retractall(inst(_, _, _)),
    assert_insts(1, Insts).
    assert_insts(Insts) :- retractall(inst(_, _, _)), assert_insts(1, Insts).

    assert_insts(_, []).
    assert_insts(N, [Inst-Val|Insts]) :-
    @@ -24,16 +19,17 @@
    eval(jmp, Val, [I0, Acc], [I, Acc]) :- I #= I0 + Val.
    eval(nop, _, [I0, Acc], [I, Acc]) :- I #= I0 + 1.

    interpret_1(Vs, I, Acc, Acc) :- member(I, Vs), !.
    interpret_1(Vs, I, Acc, Acc) :-
    member(I, Vs), !.
    interpret_1(Vs, I0, Acc0, Out) :-
    inst(I0, Inst, Val),
    eval(Inst, Val, [I0, Acc0], [I, Acc]),
    interpret_1([I0| Vs], I, Acc, Out).

    interpret_1(Out) :-
    interpret_1([], 1, 0, Out).
    interpret_1(Out) :- interpret_1([], 1, 0, Out).

    interpret_2(_, _, I, Acc, Acc) :- \+ inst(I, _, _).
    interpret_2(_, _, I, Acc, Acc) :-
    \+ inst(I, _, _).
    interpret_2(Mod, Vs, I0, Acc0, Out) :-
    \+ member(I0, Vs),
    inst(I0, jmp, Val),
    @@ -46,11 +42,10 @@
    eval(Inst, Val, [I0, Acc0], [I, Acc]),
    interpret_2(Mod, [I0|Vs], I, Acc, Out).

    interpret_2(Out) :-
    interpret_2(_, [], 1, 0, Out).
    interpret_2(Out) :- interpret_2(_, [], 1, 0, Out).

    main(Part1, Part2) :-
    phrase_from_file(instructions(Insts), 'advent_8_inp.txt'),
    assert_insts(Insts),
    interpret_1(Part1),
    interpret_2(Part2).
    interpret_2(Part2).
  15. ljos revised this gist Dec 8, 2020. 1 changed file with 15 additions and 18 deletions.
    33 changes: 15 additions & 18 deletions advent_8.pl
    Original file line number Diff line number Diff line change
    @@ -17,43 +17,40 @@
    assert_insts(_, []).
    assert_insts(N, [Inst-Val|Insts]) :-
    assertz(inst(N, Inst, Val)),
    N1 is N + 1,
    N1 #= N + 1,
    assert_insts(N1, Insts).

    eval(acc, Val, [I0, Acc0], [I, Acc]) :- I is I0 + 1, Acc is Acc0 + Val.
    eval(jmp, Val, [I0, Acc], [I, Acc]) :- I is I0 + Val.
    eval(nop, _, [I0, Acc], [I, Acc]) :- I is I0 + 1.
    eval(acc, Val, [I0, Acc0], [I, Acc]) :- I #= I0 + 1, Acc #= Acc0 + Val.
    eval(jmp, Val, [I0, Acc], [I, Acc]) :- I #= I0 + Val.
    eval(nop, _, [I0, Acc], [I, Acc]) :- I #= I0 + 1.

    interpret_1(_, Vs, I, Acc, Acc) :- member(I, Vs), !.
    interpret_1(N, Vs, I0, Acc0, Out) :-
    interpret_1(Vs, I, Acc, Acc) :- member(I, Vs), !.
    interpret_1(Vs, I0, Acc0, Out) :-
    inst(I0, Inst, Val),
    eval(Inst, Val, [I0, Acc0], [I, Acc]),
    N1 is N + 1,
    interpret_1(N1, [I0| Vs], I, Acc, Out).
    interpret_1([I0| Vs], I, Acc, Out).

    interpret_1(Out) :-
    interpret_1(1, [], 1, 0, Out).
    interpret_1([], 1, 0, Out).

    interpret_2(_, _, _, I, Acc, Acc) :- \+ inst(I, _, _).
    interpret_2(N, Mod, Vs, I0, Acc0, Out) :-
    interpret_2(_, _, I, Acc, Acc) :- \+ inst(I, _, _).
    interpret_2(Mod, Vs, I0, Acc0, Out) :-
    \+ member(I0, Vs),
    inst(I0, jmp, Val),
    Mod = I0,
    eval(nop, Val, [I0, Acc0], [I, Acc]),
    N1 is N + 1,
    interpret_2(N1, Mod, [I0|Vs], I, Acc, Out).
    interpret_2(N, Mod, Vs, I0, Acc0, Out) :-
    interpret_2(Mod, [I0|Vs], I, Acc, Out).
    interpret_2( Mod, Vs, I0, Acc0, Out) :-
    \+ member(I0, Vs),
    inst(I0, Inst, Val),
    eval(Inst, Val, [I0, Acc0], [I, Acc]),
    N1 is N + 1,
    interpret_2(N1, Mod, [I0|Vs], I, Acc, Out).
    interpret_2(Mod, [I0|Vs], I, Acc, Out).

    interpret_2(Out) :-
    interpret_2(1, _, [], 1, 0, Out).
    interpret_2(_, [], 1, 0, Out).

    main(Part1, Part2) :-
    phrase_from_file(instructions(Insts), 'advent_8_inp.txt'),
    assert_insts(Insts),
    interpret_1(Part1),
    interpret_2(Part2).
    interpret_2(Part2).
  16. ljos revised this gist Dec 8, 2020. 1 changed file with 59 additions and 0 deletions.
    59 changes: 59 additions & 0 deletions advent_8.pl
    Original file line number Diff line number Diff line change
    @@ -0,0 +1,59 @@
    :- use_module(library(dcg/basics)).
    :- use_module(library(dcg/high_order)).

    instruction(Inst-Val) -->
    [A, B, C],
    blank,
    integer(Val),
    blank,
    { atom_codes(Inst, [A,B,C]) }.

    instructions(Insts) --> sequence(instruction, Insts).

    assert_insts(Insts) :-
    retractall(inst(_, _, _)),
    assert_insts(1, Insts).

    assert_insts(_, []).
    assert_insts(N, [Inst-Val|Insts]) :-
    assertz(inst(N, Inst, Val)),
    N1 is N + 1,
    assert_insts(N1, Insts).

    eval(acc, Val, [I0, Acc0], [I, Acc]) :- I is I0 + 1, Acc is Acc0 + Val.
    eval(jmp, Val, [I0, Acc], [I, Acc]) :- I is I0 + Val.
    eval(nop, _, [I0, Acc], [I, Acc]) :- I is I0 + 1.

    interpret_1(_, Vs, I, Acc, Acc) :- member(I, Vs), !.
    interpret_1(N, Vs, I0, Acc0, Out) :-
    inst(I0, Inst, Val),
    eval(Inst, Val, [I0, Acc0], [I, Acc]),
    N1 is N + 1,
    interpret_1(N1, [I0| Vs], I, Acc, Out).

    interpret_1(Out) :-
    interpret_1(1, [], 1, 0, Out).

    interpret_2(_, _, _, I, Acc, Acc) :- \+ inst(I, _, _).
    interpret_2(N, Mod, Vs, I0, Acc0, Out) :-
    \+ member(I0, Vs),
    inst(I0, jmp, Val),
    Mod = I0,
    eval(nop, Val, [I0, Acc0], [I, Acc]),
    N1 is N + 1,
    interpret_2(N1, Mod, [I0|Vs], I, Acc, Out).
    interpret_2(N, Mod, Vs, I0, Acc0, Out) :-
    \+ member(I0, Vs),
    inst(I0, Inst, Val),
    eval(Inst, Val, [I0, Acc0], [I, Acc]),
    N1 is N + 1,
    interpret_2(N1, Mod, [I0|Vs], I, Acc, Out).

    interpret_2(Out) :-
    interpret_2(1, _, [], 1, 0, Out).

    main(Part1, Part2) :-
    phrase_from_file(instructions(Insts), 'advent_8_inp.txt'),
    assert_insts(Insts),
    interpret_1(Part1),
    interpret_2(Part2).
  17. ljos revised this gist Dec 7, 2020. 2 changed files with 11 additions and 18 deletions.
    2 changes: 1 addition & 1 deletion advent_5.pl
    Original file line number Diff line number Diff line change
    @@ -2,7 +2,7 @@
    :- use_module(library(clpfd)).

    row([1]) --> "B".
    row([1|Ls]) --> "B" ; "B", row(Ls).
    row([1|Ls]) --> "B", row(Ls).
    row([0]) --> "F".
    row([0|Ls]) --> "F", row(Ls).

    27 changes: 10 additions & 17 deletions advent_7.pl
    Original file line number Diff line number Diff line change
    @@ -3,29 +3,23 @@
    :- use_module(library(dcg/high_order)).

    bag(Bag) -->
    nonblanks(A),
    blank, nonblanks(C),
    blank, "bag",
    optional("s", ""),
    nonblanks(A), " ", nonblanks(C), " bag", optional("s", []),
    { append(A, [0'_|C], S), atom_codes(Bag, S) }.

    bags([N-Bag|Bags]) --> integer(N), blanks, bag(Bag), ",", blanks, bags(Bags).
    bags([N-Bag]) --> integer(N), blanks, bag(Bag).
    bags([N-Bag|Bags]) --> integer(N), " ", bag(Bag), ", ", bags(Bags).
    bags([N-Bag]) --> integer(N), " ", bag(Bag).

    rule(contains(B, Bags)) --> bag(B), blank, "contain", blank, bags(Bags), ".".
    rule(contains(B, [])) --> bag(B), blank, "contain no other bags.".
    rule(contains(B, Bags)) --> bag(B), " contain ", bags(Bags), ".".
    rule(contains(B, [])) --> bag(B), " contain no other bags.".

    rules([R|Rules]) --> rule(R), blanks, rules(Rules).
    rules([R|Rules]) --> rule(R), "\n", rules(Rules).
    rules([R]) --> rule(R), blanks.

    assert_contains(S, N-O) :-
    assertz(contains(S, N, O)).
    assert_contains(S, N-O) :- assertz(contains(S, N, O)).

    assert_rule(contains(S, Os)) :-
    maplist(assert_contains(S), Os).
    assert_rule(contains(S, Os)) :- maplist(assert_contains(S), Os).

    assert_rules(Rules) :-
    maplist(assert_rule, Rules).
    assert_rules(Rules) :- maplist(assert_rule, Rules).

    can_contain(Bag, Container) :-
    contains(Container, _, Bag).
    @@ -35,8 +29,7 @@

    product_(A, B, N) :- N #= A * B.

    count(A-_, Bs, Ns) :-
    maplist(product_(A), Bs, Ns).
    count(A-_, Bs, Ns) :- maplist(product_(A), Bs, Ns).

    inventory(N-Bag, Value) :-
    findall(C-B, contains(Bag, C, B), Cs),
  18. ljos revised this gist Dec 7, 2020. 1 changed file with 0 additions and 1 deletion.
    1 change: 0 additions & 1 deletion advent_7.pl
    Original file line number Diff line number Diff line change
    @@ -33,7 +33,6 @@
    contains(C, _, Bag),
    can_contain(C, Container).


    product_(A, B, N) :- N #= A * B.

    count(A-_, Bs, Ns) :-
  19. ljos revised this gist Dec 7, 2020. 1 changed file with 58 additions and 0 deletions.
    58 changes: 58 additions & 0 deletions advent_7.pl
    Original file line number Diff line number Diff line change
    @@ -0,0 +1,58 @@
    :- use_module(library(clpfd)).
    :- use_module(library(dcg/basics)).
    :- use_module(library(dcg/high_order)).

    bag(Bag) -->
    nonblanks(A),
    blank, nonblanks(C),
    blank, "bag",
    optional("s", ""),
    { append(A, [0'_|C], S), atom_codes(Bag, S) }.

    bags([N-Bag|Bags]) --> integer(N), blanks, bag(Bag), ",", blanks, bags(Bags).
    bags([N-Bag]) --> integer(N), blanks, bag(Bag).

    rule(contains(B, Bags)) --> bag(B), blank, "contain", blank, bags(Bags), ".".
    rule(contains(B, [])) --> bag(B), blank, "contain no other bags.".

    rules([R|Rules]) --> rule(R), blanks, rules(Rules).
    rules([R]) --> rule(R), blanks.

    assert_contains(S, N-O) :-
    assertz(contains(S, N, O)).

    assert_rule(contains(S, Os)) :-
    maplist(assert_contains(S), Os).

    assert_rules(Rules) :-
    maplist(assert_rule, Rules).

    can_contain(Bag, Container) :-
    contains(Container, _, Bag).
    can_contain(Bag, Container) :-
    contains(C, _, Bag),
    can_contain(C, Container).


    product_(A, B, N) :- N #= A * B.

    count(A-_, Bs, Ns) :-
    maplist(product_(A), Bs, Ns).

    inventory(N-Bag, Value) :-
    findall(C-B, contains(Bag, C, B), Cs),
    maplist(inventory, Cs, Bags),
    sum(Bags, #=, V),
    Value #= N + V * N.

    read_rules :-
    retractall(contains(_, _, _)),
    phrase_from_file(rules(Rules), 'advent_7_inp.txt'),
    assert_rules(Rules), !.

    main(Part1, Part2) :-
    read_rules,
    aggregate_all(set(C), can_contain(shiny_gold, C), S),
    length(S, Part1),
    inventory(1-shiny_gold, Value),
    Part2 #= Value - 1.
  20. ljos revised this gist Dec 6, 2020. 1 changed file with 2 additions and 2 deletions.
    4 changes: 2 additions & 2 deletions advent_6.pl
    Original file line number Diff line number Diff line change
    @@ -27,8 +27,8 @@
    length(Unique, Count).

    main(Part1, Part2) :-
    phrase_from_file(string(Str), 'advent_6_inp.txt'),
    groups(Str, Groups),
    read_file_to_codes('advent_6_inp.txt', Codes, []),
    groups(Codes, Groups),
    maplist(unique_1, Groups, Count1),
    sum(Count1, #=, Part1),
    maplist(unique_2, Groups, Count2),
  21. ljos revised this gist Dec 6, 2020. 1 changed file with 2 additions and 2 deletions.
    4 changes: 2 additions & 2 deletions advent_6.pl
    Original file line number Diff line number Diff line change
    @@ -29,7 +29,7 @@
    main(Part1, Part2) :-
    phrase_from_file(string(Str), 'advent_6_inp.txt'),
    groups(Str, Groups),
    maplist(unique_2, Groups, Count1),
    maplist(unique_1, Groups, Count1),
    sum(Count1, #=, Part1),
    maplist(unique_1, Groups, Count2),
    maplist(unique_2, Groups, Count2),
    sum(Count2, #=, Part2), !.
  22. ljos revised this gist Dec 6, 2020. 1 changed file with 35 additions and 0 deletions.
    35 changes: 35 additions & 0 deletions advent_6.pl
    Original file line number Diff line number Diff line change
    @@ -0,0 +1,35 @@
    :- use_module(library(dcg/basics)).
    :- use_module(library(clpfd)).

    answers([], []).
    answers(Group, [Answer|Answers]) :-
    append(Answer, [10 | Rest], Group),
    answers(Rest, Answers).
    answers(Group, [Answer]) :-
    append(Answer, [10], Group).
    answers(Group, [Group]).

    groups(Str, [Answers | Groups]) :-
    append(Group, [10, 10 | Rest], Str),
    answers(Group, Answers),
    groups(Rest, Groups).
    groups(Str, [Answer]) :-
    answers(Str, Answer).

    unique_1(Answers, Count) :-
    [A| As] = Answers,
    foldl(union, As, A, Unique),
    length(Unique, Count).

    unique_2(Answers, Count) :-
    [A| As] = Answers,
    foldl(intersection, As, A, Unique),
    length(Unique, Count).

    main(Part1, Part2) :-
    phrase_from_file(string(Str), 'advent_6_inp.txt'),
    groups(Str, Groups),
    maplist(unique_2, Groups, Count1),
    sum(Count1, #=, Part1),
    maplist(unique_1, Groups, Count2),
    sum(Count2, #=, Part2), !.
  23. ljos revised this gist Dec 5, 2020. 1 changed file with 38 additions and 0 deletions.
    38 changes: 38 additions & 0 deletions advent_5.pl
    Original file line number Diff line number Diff line change
    @@ -0,0 +1,38 @@
    :- use_module(library(dcg/basics)).
    :- use_module(library(clpfd)).

    row([1]) --> "B".
    row([1|Ls]) --> "B" ; "B", row(Ls).
    row([0]) --> "F".
    row([0|Ls]) --> "F", row(Ls).

    col([1]) --> "R".
    col([1|Ls]) --> "R", col(Ls).
    col([0]) --> "L".
    col([0|Ls]) --> "L", col(Ls).

    position([Row,Col]) --> row(Row), col(Col).

    seating([S]) --> position(S), blanks.
    seating([S|Seats]) --> position(S), blanks, seating(Seats).

    restrict(0, L-U0, L-U) :- U #= U0 - ((U0 - L) // 2) - 1.
    restrict(1, L0-U, L-U) :- L #= L0 + ((U - L0) // 2) + 1.

    seat([X, Y], Id) :-
    foldl(restrict, X, 0-127, Row-Row),
    foldl(restrict, Y, 0-7, Col-Col),
    Id #= Row * 8 + Col.

    hole([A, B | _], Missing) :-
    2 #= B - A,
    Missing #= A + 1.
    hole([_|Seats], Missing) :-
    hole(Seats, Missing).

    main(Part1, Part2) :-
    phrase_from_file(seating(Seating), 'advent_5_inp.txt'),
    maplist(seat, Seating, Ids), !,
    max_list(Ids, Part1),
    sort(Ids, Sorted),
    hole(Sorted, Part2).
  24. ljos revised this gist Dec 4, 2020. 2 changed files with 5 additions and 14 deletions.
    11 changes: 3 additions & 8 deletions advent_2.pl
    Original file line number Diff line number Diff line change
    @@ -6,10 +6,8 @@
    % We want a predicate that will give us the number (L) of passwords
    % that fit the password constraints given in the task.
    step_1(L) :-
    % The easiest way to get the data is to read it in as a stream.
    open('advent_2_inp.txt', read, Fd),
    % We parse the stream using definite clause grammar (DCG).
    phrase_from_stream(passwords(Passwords), Fd),
    % We parse the input file using definite clause grammar (DCG).
    phrase_from_file(passwords(Passwords), 'advent_2_inp.txt'),
    % We then count which passwords meet the constraint for the
    % passwords.
    aggregate_all(count, (member(P, Passwords), check_step_1(P)), L).
    @@ -30,10 +28,7 @@
    % In step two the constraints on the password changes, but the process
    % is the same as in the first step.
    step_2(L) :-
    % Open the file...
    open('advent_2_inp.txt', read, Fd),
    % Parse the file ...
    phrase_from_stream(passwords(Passwords), Fd),
    phrase_from_file(passwords(Passwords), 'advent_2_inp.txt'),
    % And count the passwords that meet the constraint.
    aggregate_all(count, (member(P, Passwords), check_step_2(P)), L).

    8 changes: 2 additions & 6 deletions advent_3.pl
    Original file line number Diff line number Diff line change
    @@ -32,17 +32,13 @@
    aggregate_all(count, member(35, Path), Count).

    step_1(Trees) :-
    open('advent_3_inp.txt', read, Fd),
    phrase_from_stream(lines(Lines), Fd),
    close(Fd),
    phrase_from_file(lines(Lines), 'advent_3_inp.txt'),
    path(3-1, Lines, Path),
    aggregate_all(count, member(35, Path), Trees), !.

    product_(N, M, P) :- P #= N * M.

    step_2([C|Counts], Product) :-
    open('advent_3_inp.txt', read, Fd),
    phrase_from_stream(lines(Lines), Fd),
    close(Fd),
    phrase_from_file(lines(Lines), 'advent_3_inp.txt'),
    maplist(path(Lines), [1-1, 3-1, 5-1, 7-1, 1-2], [C|Counts]),
    foldl(product_, Counts, C, Product), !.
  25. ljos revised this gist Dec 4, 2020. 1 changed file with 1 addition and 3 deletions.
    4 changes: 1 addition & 3 deletions advent_1.pl
    Original file line number Diff line number Diff line change
    @@ -36,9 +36,7 @@
    foldl(product_, Ns, N, Product).

    day_1(Numbers) :-
    open('advent_1_inp.txt', read, Fd),
    phrase_from_stream(numbers([E|Expenses], Fd),
    close(Fd),
    phrase_from_stream(numbers([E|Expenses], 'advent_1_inp.txt'),
    % We need to restrict the numbers that we can choose from to the
    % numbers in the list of expenses. We do that by creating a domain
    % that contains all of the expenses. Here we can see the small
  26. ljos revised this gist Dec 4, 2020. 1 changed file with 5 additions and 10 deletions.
    15 changes: 5 additions & 10 deletions advent_4.pl
    Original file line number Diff line number Diff line change
    @@ -17,11 +17,6 @@
    maplist(functor, Info, Names, _),
    subtract([byr, iyr, eyr, hgt, hcl, ecl, pid], Names, []).

    step_1(C) :-
    phrase_from_file(passports(Passports), 'advent_4_inp.txt'),
    include(valid, Passports, Valid),
    length(Valid, C).

    check(byr(Byr)) :- integer(Y, Byr, []), Y #>= 1920, Y #=< 2002.
    check(iyr(Iyr)) :- integer(Y, Iyr, []), Y #>= 2010, Y #=< 2020.
    check(eyr(Eyr)) :- integer(Y, Eyr, []), Y #>= 2020, Y #=< 2030.
    @@ -32,9 +27,9 @@
    check(pid(Pid)) :- length(Pid, 9), integer(_, Pid, []).
    check(cid(_)).

    validate(Passport) :- valid(Passport), maplist(check, Passport).

    step_2(C) :-
    main(Step1, Step2) :-
    phrase_from_file(passports(Passports), 'advent_4_inp.txt'),
    include(validate, Passports, Valid),
    length(Valid, C).
    include(valid, Passports, Valid),
    length(Valid, Step1),
    include(maplist(check), Valid, Checked),
    length(Checked, Step2).
  27. ljos revised this gist Dec 4, 2020. 1 changed file with 1 addition and 1 deletion.
    2 changes: 1 addition & 1 deletion advent_4.pl
    Original file line number Diff line number Diff line change
    @@ -32,7 +32,7 @@
    check(pid(Pid)) :- length(Pid, 9), integer(_, Pid, []).
    check(cid(_)).

    validate(Passport) :- include(check, Passport, Info), valid(Info).
    validate(Passport) :- valid(Passport), maplist(check, Passport).

    step_2(C) :-
    phrase_from_file(passports(Passports), 'advent_4_inp.txt'),
  28. ljos revised this gist Dec 4, 2020. 1 changed file with 1 addition and 1 deletion.
    2 changes: 1 addition & 1 deletion advent_4.pl
    Original file line number Diff line number Diff line change
    @@ -27,7 +27,7 @@
    check(eyr(Eyr)) :- integer(Y, Eyr, []), Y #>= 2020, Y #=< 2030.
    check(hgt(Hgt)) :- integer(H, Hgt, "cm"), H #>= 150, H #=< 193.
    check(hgt(Hgt)) :- integer(H, Hgt, "in"), H #>= 59, H #=< 76.
    check(hcl([0'#| Hcl])) :- xinteger(_, Hcl, []).
    check(hcl(Hcl)) :- phrase(("#", xinteger(_)), Hcl).
    check(ecl(Ecl)) :- atom_codes(E, Ecl), memberchk(E, [amb, blu, brn, gry, grn, hzl, oth]).
    check(pid(Pid)) :- length(Pid, 9), integer(_, Pid, []).
    check(cid(_)).
  29. ljos revised this gist Dec 4, 2020. 1 changed file with 1 addition and 1 deletion.
    2 changes: 1 addition & 1 deletion advent_4.pl
    Original file line number Diff line number Diff line change
    @@ -27,7 +27,7 @@
    check(eyr(Eyr)) :- integer(Y, Eyr, []), Y #>= 2020, Y #=< 2030.
    check(hgt(Hgt)) :- integer(H, Hgt, "cm"), H #>= 150, H #=< 193.
    check(hgt(Hgt)) :- integer(H, Hgt, "in"), H #>= 59, H #=< 76.
    check(hcl([35| Hcl])) :- xinteger(_, Hcl, []).
    check(hcl([0'#| Hcl])) :- xinteger(_, Hcl, []).
    check(ecl(Ecl)) :- atom_codes(E, Ecl), memberchk(E, [amb, blu, brn, gry, grn, hzl, oth]).
    check(pid(Pid)) :- length(Pid, 9), integer(_, Pid, []).
    check(cid(_)).
  30. ljos revised this gist Dec 4, 2020. 1 changed file with 0 additions and 7 deletions.
    7 changes: 0 additions & 7 deletions advent_4.pl
    Original file line number Diff line number Diff line change
    @@ -23,20 +23,13 @@
    length(Valid, C).

    check(byr(Byr)) :- integer(Y, Byr, []), Y #>= 1920, Y #=< 2002.

    check(iyr(Iyr)) :- integer(Y, Iyr, []), Y #>= 2010, Y #=< 2020.

    check(eyr(Eyr)) :- integer(Y, Eyr, []), Y #>= 2020, Y #=< 2030.

    check(hgt(Hgt)) :- integer(H, Hgt, "cm"), H #>= 150, H #=< 193.
    check(hgt(Hgt)) :- integer(H, Hgt, "in"), H #>= 59, H #=< 76.

    check(hcl([35| Hcl])) :- xinteger(_, Hcl, []).

    check(ecl(Ecl)) :- atom_codes(E, Ecl), memberchk(E, [amb, blu, brn, gry, grn, hzl, oth]).

    check(pid(Pid)) :- length(Pid, 9), integer(_, Pid, []).

    check(cid(_)).

    validate(Passport) :- include(check, Passport, Info), valid(Info).