RabbitFarm

2021-02-07

The Weekly Challenge 098 (Prolog Solutions)

The examples used here are from the weekly challenge problem statement and demonstrate the working solution. Also, the challenge statements are given in a Perl context although for Prolog solutions some adjustments are made to account for the differing semantics between the two languages.

Part 1

You are given file $FILE. Create subroutine readN($FILE, $number) returns the first n-characters and moves the pointer to the (n+1)th character.

Solution


:-dynamic(position/1).
:-initialization(main).

position(0).

read_n_chars(Stream, N, Chars):-
    read_n_chars(Stream, N, [], Chars).
read_n_chars(_, 0, ByteAccum, Chars):-
    atom_codes(Chars, ByteAccum).    
read_n_chars(Stream, N, ByteAccum, Chars):-
    \+ at_end_of_stream(Stream),
    get_byte(Stream, C),
    N0 is N - 1,
    append(ByteAccum, [C], ByteAccum0),
    read_n_chars(Stream, N0, ByteAccum0, Chars).
read_n_chars(Stream, _, ByteAccum, Chars):-
    at_end_of_stream(Stream),
    read_n_chars(Stream, 0, ByteAccum, Chars).
    
read_n(File, N, Chars):-
    open(File, read, Stream,[type(binary),reposition(true)]),
    position(Position),
    seek(Stream, bof, Position, _),
    read_n_chars(Stream, N, Chars),
    X is N + Position,
    retract(position(Position)),
    asserta(position(X)),
    close(Stream).
    
main:-
    read_n('../ch-1.dat', 4, Chars0),
    write(Chars0), nl,
    read_n('../ch-1.dat', 4, Chars1),
    write(Chars1), nl,
    read_n('../ch-1.dat', 4, Chars2),
    write(Chars2), nl,
    halt.

Sample Run


$ gplc ch-1.p
$ ./ch-1
1234
5678
90

Notes

Clearly given the semantics of Prolog we need to adjust the challenge specification slightly. For the Prolog version we’ll write a predicate read_n/3 which will instantiate the third argument each time it is called in the way described, resuming the file reads after the last read position. Because we want to initialize the position to 0 to start and then update with retract/1 and asserta/1 we use the dynamic/1 specification to allow for this. If not specified dynamic we’d see an error such as system_error(cannot_catch_throw(error(permission_error(modify,static_procedure,position/1),retract/1))) when trying to make alterations.

The last read position is stored as a Prolog fact after each read. Each read_n/3 call will use that last position to do a seek/4 and then read in the characters. While some Prologs will allow seeking within text files Gnu Prolog disallows this. This is easily worked around, however, by opening the file in binary mode, reading in the characters using get_byte/2 and then using atom_codes/2 to convert. To make this work we need to specify Options of [type(binary),reposition(true)] to open/4.

Part 2

You are given a sorted array of distinct integers @N and a target `$N``. Write a script to return the index of the given target if found otherwise place the target in the sorted array and return the index.

Solution


:-initialization(main).

needle_haystack([H|T], N, Index):-
    ((N < H, Index is 0); 
       (last(T, Last), N > Last, 
       length([H|T], Length), Index is Length)).
needle_haystack([H|T], N, Index):-
    needle_haystack([H|T], N, 0, Index).
needle_haystack([], _, Index, Index).    
needle_haystack([_|[]], _, Index, Index).
needle_haystack([H0, _|_], N, Counter, Index):-
    H0 == N,
    Index is Counter.
needle_haystack([_, H1|_], N, Counter, Index):-
    H1 == N,
    Index is Counter + 1.
needle_haystack([H0, H1|T], N, Counter, Index):-
    H0 \== N,
    H1 \== N,
    \+ between(H0, H1, N),
    C is Counter + 2,
    needle_haystack(T, N, C, Index).
needle_haystack([H0, H1|_], N, Counter, Index):-
    H0 \== N,
    H1 \== N,
    between(H0, H1, N),
    Index is Counter + 1.
            
main:-
    needle_haystack([1, 2, 3, 4], 3, Index0),
    write(Index0), nl,
    needle_haystack([1, 3, 5, 7], 6, Index1),
    write(Index1), nl,
    needle_haystack([12, 14, 16, 18], 10, Index2),
    write(Index2), nl,
    needle_haystack([11, 13, 15, 17], 19, Index3),
    write(Index3), nl,
    halt.

Sample Run


$ gplc prolog/ch-2.p
$ ./ch-2
2
3
0
4

Notes

This is a somewhat convoluted sounding problem at first but it actually ends up being straight forward to solve, albeit slightly tedious. The code is largely an examination of the possible cases where N may be. If it would occur before the head of the list or after the last element we are done immediately. Otherwise we evaluate the list in search of N, returning the index if we find it. If we find two successive elements in which N would be between, but is not in the list, we have identified the point in which N would be inserted.

While the challenge statement indicates N should be inserted we only really seem to care about the index and so I don’t actually provide an updated list. To do so we could add an additional argument to needle_haystack/3 which would be instantiated to an updated list.

References

Challenge 098

posted at: 14:12 by: Adam Russell | path: /prolog | permanent link to this entry