aarroyoc / advent-of-code-2020

Solutions of Advent of Code 2020
The Unlicense
7 stars 0 forks source link

phrase_from_file/2 seems useful for a few solutions #1

Open triska opened 3 years ago

triska commented 3 years ago

Thank you very much for sharing these solutions!

One small thing I noticed: It seems that some of these programs would benefit from using phrase_from_file/2 which is available in library(pio). There are several major advantages of using phrase_from_file/2 instead of phrase_from_stream/2:

  1. it reliably closes the file handle at the earliest possible opportunity, also if errors occur.
  2. it makes the code more portable to other Prolog systems: For example, Scryer Prolog and Trealla Prolog also already provide phrase_from_file/2.
  3. it can be implemented more efficiently by the engine: In particular, phrase_from_file/2 can be implemented by using the system call mmap to map the entire file to memory, and thus process the entire file without loading it into memory at once. Trealla Prolog already does it in this way.
aarroyoc commented 3 years ago

Thanks for the suggestions. I've never used so many DCGs before, and in this "contest" I'm learning a lot about them (in fact, quite embarrassing, sometimes I've spent more time doing a good DCG than doing the actual solution :sweat_smile: ).

I'll try to update the solutions to use phrase_from_file/2 as soon as possible

Mousaka commented 3 years ago

Hi @aarroyoc and @triska ! I'm on also on a road of learning prolog with advent of code =) Would love any feedback on my solutions as well https://github.com/Mousaka/advent-of-code-2020. Btw do you know any chat where prologers are hanging? I'm idling in #prolog on the functional programming slack https://fpchat-invite.herokuapp.com/ but it's a bit quiet in there.

I hope it is okey for me reaching out here. I will be comparing solutions and maybe ask questions if that's ok? Cheers

triska commented 3 years ago

@Mousaka: Thank you for sharing this, and for your interest!

@aarroyoc: I hope you are OK with discussing these points in the issue tracker! The tracker works nicely because we can easily link to existing issues that are already filed for Prolog systems, and it is to be hoped that a cross-linked discussion of these issues will help motivate Prolog implementors to work on features that would be useful in solutions of these puzzles.

For example, here are few additional comments regarding phrase_from_file/2 that are also related to this issue, and I hope you find them useful. First, if you do want to read the entire file contents into memory, then you can easily do it by defining a DCG nonterminal that describes any list at all, such as:

list([]) --> [].
list([L|Ls]) --> [L], list(Ls).

You can then use phrase_from_file/2 to obtain the entire file contents as a list of characters:

phrase_from_file(list(Ls), File)

An advantage of this approach is that it is more general than using low-level IO to read from files, because you can also use it to generate lists by using phrase/2 instead of phrase_from_file/2. Another advantage is that you can test the same code interactively on the toplevel, without any file at all, also by using phrase/2.

On top of this, phrase_from_file/2 is much more efficient than reading characters individually from a file, because phrase_from_file/2 can read characters in entire blocks, or even map the entire file into memory using mmap and process the contents directly on the in-memory mapping that is efficiently performed by the operating system (see https://github.com/mthom/scryer-prolog/issues/251, and Trealla Prolog already does it in this way!).

Note that in Scryer Prolog, File must currently be an atom. I have filed https://github.com/mthom/scryer-prolog/issues/566 in the hope that strings (i.e, lists of characters) will also be supported in the future, as they already are in Trealla Prolog (see also https://github.com/infradig/trealla/issues/128).

Another thing I noticed in some solutions is the use of backticks (`...`). The Prolog ISO standard says about back quoted strings:

4 A back quoted string (6.4.7) contains back quoted characters,
but this part of ISO/IEC 13211 does not define a token (or
term) based on a back quoted string.

Therefore, relying on this feature is not portable to other conforming Prolog systems. You can use double quotes to portably denote lists of characters, assuming the Prolog flag double_quotes is set to chars (which I recommend, and which is already the default in the newest Prolog systems Scryer, Tau and Trealla Prolog).

Another thing I noticed is the heavy use of !/0 and other impure constructs in several solutions. These constructs severely restrict the generality of the solutions. Consider for instance this example I found in the repositories:


count(_, [], 0) :- !.
count(A, [A|Chars], N) :-
    !,count(A, Chars, N1),
    N is N1 + 1.
count(A, [_Char|Chars], N) :-
    count(A, Chars, N).

Please consider it briefly from my position: Initially, I have no idea what the predicate means, so I use Prolog to find out more about the predicate, right? So I ask Prolog the most general query one can pose for this predicate, namely: What does this predicate describe at all, are there any arguments whatsoever for which it holds? So I ask:

?- count(C, Cs, N).

And in response, I get the unique solution:

   Cs = [], N = 0.

Well, if that's all that the predicate describes, then why not define it as:

count(_, [], 0).

?

By using !/0 and other impure constructs, we are throwing away key attractions of logic programming, such as the ability to reason logically about our code, to ask questions about and work with partially known data, to think in terms of generalizations and specializations, and to debug our programs by reasoning about smaller fragments of our programs.

We benefit most from Prolog by keeping to its pure monotonic subset. For example, suppose we define the above predicate instead as follows:

char_chars_num(C, Cs, N) :-
        tfilter(=(C), Cs, Ls),
        length(Ls, N).

This uses tfilter/3 from library(reif), which already ships with Scryer Prolog. This is a pure construct, and as a consequence, we now get for the most general query:

?- char_chars_num(C, Cs, N).
   Cs = [], N = 0
;  Cs = [C], N = 1
;  Cs = [C,C], N = 2
;  Cs = [C,C,C], N = 3
;  Cs = [C,C,C,C], N = 4
;  ...

So, above all, we get the information that there is more than one answer. We can reason about termination properties: Does the predicate terminate universally?

?- char_chars_num(C, Cs, N), false.

Apparently not, as intended, because it would be wrong (incomplete) if it did! Moreover, since the definition preserves monotonicity, we can apply alternative execution strategies such as iterative deepening:

?- length(Cs, _),
   char_chars_num(C, Cs, N).

And now we get a fair enumeration of answers, showing us all possibilities in general:

?- length(Cs, _),
   char_chars_num(C, Cs, N).
   Cs = [], N = 0
;  Cs = [C], N = 1
;  Cs = [_A], N = 0, dif:dif(C,_A)
;  Cs = [C,C], N = 2
;  Cs = [C,_A], N = 1, dif:dif(C,_A)
;  Cs = [_A,C], N = 1, dif:dif(C,_A)
;  Cs = [_A,_B], N = 0, dif:dif(C,_A), dif:dif(C,_B)
;  ...

As I see it, the main challenge with these puzzles is not to find how we can "somehow" solve them, by writing imperative code in Prolog. Rather, the primary challenge is: How can we solve them in a logical sense, by using pure constructs that let us unleash the full potential of Prolog to solve also more general tasks than the particular instances that are stated here? For example, what about solving these puzzles with only partial information? And what about generating not only solutions, but also instances of the puzzles? A good declarative solution will be able to do that. With these goals in mind, we will use and develop new predicates such as if_/3 and tfilter/3 that combine generality with good performance.

aarroyoc commented 3 years ago

@Mousaka I don't have any problem discussing solutions here hahaha, beware that I do not consider myself a Prolog expert (I'm reading @triska post with lots of interest right now :) ). Also, some solutions are ugly and non-optimal (like Day 14, it is very slow compared to other peoples solution), but that's because my main objective is to finish every puzzle in the day since I'm competing with friends :sweat_smile:

aarroyoc commented 3 years ago

Today's solution (day 15) is not going to like @triska because it is non-pure and non-portable, but it is the fastest way to get a result (and avoid stack limits) in this performance puzzle. :rofl:

triska commented 3 years ago

I think a good approach keeps everything as pure as possible. For instance, here is a quick draft for today's puzzle:

game(Ls0, I, N) :-
        length(Ls0, L),
        ht_new(A0),
        starting_numbers(Ls0, Ls1, 1, A0, A),
        reverse(Ls1, Ls2),
        Index #= L + 1,
        RL #= I - L,
        length(Rs, RL),
        game_(Rs, Ls2, Index, A, Ls),
        Ls = [N-_|_].

starting_numbers([], [], _, A, A).
starting_numbers([N|Ns], [N-Val|NVs], Index0, A0, A) :-
        record_number(N, Index0, Val, A0, A1),
        Index #= Index0 + 1,
        starting_numbers(Ns, NVs, Index, A1, A).

record_number(N, Index, Val, A0, A0) :-
        (   ht_get(A0, N, I) ->
            record_number_(I, N, Index, Val, A0, _A)
        ;   Val = first(Index),
            ht_put(A0, N, Val)
        ).

record_number_(first(Prev), N, Index, Val, A0, A0) :-
        Val = now_prev(Index,Prev),
        ht_put(A0, N, Val).
record_number_(now_prev(Now,_), N, Index, Val, A0, A0) :-
        Val = now_prev(Index,Now),
        ht_put(A0, N, Val).

game_([], Ls0, _, _, Ls0).
game_([_|Rs], Ls0, Index0, A0, Ls) :-
        spoken_next(Ls0, Index0, Ls1, A0, A),
        Index #= Index0 + 1,
        game_(Rs, Ls1, Index, A, Ls).

spoken_next(Ls0, Index, [N-Val|Ls0], A0, A) :-
        Ls0 = [_-Val0|_],
        value_n(Val0, N),
        record_number(N, Index, Val, A0, A).

value_n(first(_), 0).
value_n(now_prev(I,P), N) :- N #= I-P.

I made it so that we can rather quickly experiment with different data structures: For the hash table, only a single argument needs to be passed around, but for association lists, two need to be passed around, so I kept two in place, even if these arguments are identical in this case where a hash table is used.

Notice that a few portions of the code remain pure, and can be used in all directions. For instance, we can query:

?- value_n(V, N).
V = first(_8140),
N = 0 ;
V = now_prev(_10118, _10120),
N+_10120#=_10118.

and we get general answers, telling us everything there is to say about the predicate.

Note that there is no assert/retract, so what we see here is the entire code, and we know that invoking a predicate repeatedly will always yield the same result! Still, not everything is pure here, and these are portions of the program that can potentially be improved!

Sample query:

?- time(game([6,3,15,13,1], 30000000, Ls)).
%@ % 801,905,252 inferences, 96.211 CPU in 114.750 seconds (84% CPU, 8334843 Lips)
%@ Ls = 51358.

It seems acceptably fast.

aarroyoc commented 3 years ago

Really nice!! I need to do more Prolog still to come up with those elegant solutions. I've seen on Reddit that some people used a Trie and achieved results under 20 seconds. I'll trie it (pun intended) also.

triska commented 3 years ago

To come back to the actual issue I filed here, let me be more explicit:

load_data(Lines) :-
    read_file_to_string('day18/input.dat', String, []),
    string_chars(String, Chars),
    phrase(lines(Lines), Chars).

can be written as:

load_data(Lines) :- 
    phrase_from_file(lines(Lines), 'day18/input.dat').

with the advantages I stated above.

aarroyoc commented 3 years ago

Ups, I forgot to told you that I've already tried that but on SWI (which is what I'm using right now, but I'll port it to Scryer once finished the challenge) this doesn't work. Seems like by default phrase_from_file processes a stream which in SWI doesn't match with double quotes or char atoms.

triska commented 3 years ago

To make this work correctly in SWI-Prolog, I think you have to use a more recent version of library(pio):

http://www.complang.tuwien.ac.at/ulrich/Prolog-inedit/swi/pio.pl