RabbitFarm

2021-06-20

The Weekly Challenge 117 (Prolog Solutions)

The examples used here are from the weekly challenge problem statement and demonstrate the working solution.

Part 1

You are given text file with rows numbered 1-15 in random order but there is a catch one row in missing in the file.

Solution


:-initialization(main).

check_and_read(10, [] ,_):-
    !.
check_and_read(13, [], _):-
    !.
check_and_read(44, [], _):-
    !.
check_and_read(end_of_file, [], _):-
    !.
check_and_read(Char, [Char|Chars], Stream):-
    get_code(Stream, NextChar),
    check_and_read(NextChar, Chars, Stream).

read_data(Stream, []):-
    at_end_of_stream(Stream).
read_data(Stream, [X|L]):-
    \+ at_end_of_stream(Stream),
    get_code(Stream, Char),
    check_and_read(Char, Chars, Stream),
    atom_codes(X, Chars),
    read_data(Stream, L).

line_numbers([], []).  
line_numbers([N0,_|T], [N1|N]):-
    number_atom(N1, N0),
    line_numbers(T, N). 

missing(Contents, Missing):-
    line_numbers(Contents, Numbers),
    max_list(Numbers, Max),
    min_list(Numbers, Min),
    between(Min, Max, X),
    \+ member(X, Numbers),
    Missing = X. 

main:-
    open('data', read, Stream),
    read_data(Stream, Contents),
    close(Stream),
    missing(Contents, Missing),
    format('Missing: ~d ~N', [Missing]), 
    halt.   

Sample Run


$ gprolog --consult-file prolog/ch-1.p
GNU Prolog 1.4.5 (32 bits)
Compiled Dec  3 2020, 00:37:14 with gcc
By Daniel Diaz
Copyright (C) 1999-2020 Daniel Diaz
compiling /home/adamcrussell/Projects/perlweeklychallenge-club/challenge-117/adam-russell/prolog/ch-1.p for byte code...
/home/adamcrussell/Projects/perlweeklychallenge-club/challenge-117/adam-russell/prolog/ch-1.p compiled, 18 lines read - 1808 bytes written, 38 ms
Missing: 12

Notes

What interested me the most on this is the majority of the code here is to read in the data file. It's all boilerplate stuff, ordinarily it'd be in some other file of utilities. The work is all done in the seven lines of missing/2. Once we have all the line numbers we use member/2 to determine which one is missing.

As usual there was a second task in this week's challenge but I did not get around to coding up a solution in Prolog. I did get do it in Perl however. Given the nature of that problem my Prolog would have been a fairly close re-implementation of the same algorithm.

Happy Father's Day!

References

Challenge 117

posted at: 22:53 by: Adam Russell | path: /prolog | permanent link to this entry