mndrix / list_util

Prolog list utility predicates
The Unlicense
11 stars 5 forks source link

lines/2 improvements #3

Closed mndrix closed 10 years ago

mndrix commented 10 years ago

lines/2 only works on streams that allow set_stream_position/2. It also leaves a trailing choicepoint when calling length/2 or maplist/2. Both of these problems are fixed by the following code. Write failing tests for the problems and then use this code to implement lines/2.

:- use_module(library(readutil), [read_line_to_string/2]).

% custom, non-backtracking linked list built with nb_setarg/3
new_ll(Stream, LL) :-
    LL = ll(Stream, unknown, unknown).

is_empty(ll(_,end_of_file,_)) :-
    !.
is_empty(LL) :-
    LL = ll(Stream, _, _),
    at_end_of_stream(Stream),
    nb_setarg(2,LL,end_of_file).

head_tail(ll(_,H,T), Head, Tail) :-
    string(H),
    !,
    Head = H,
    Tail = T.
head_tail(LL, Head, Tail) :-
    LL = ll(Stream, unknown, _),
    debug(lazy, "reading a line", []),
    read_line_to_string(Stream, H),
    nb_setarg(2, LL, H),
    nb_setarg(3, LL, ll(Stream,unknown,unknown)),

    % now that side effects are done we can unify
    Head = H,
    LL = ll(_,_,Tail).

% reads each line only once, despite backtracking
try(LL0) :-
    open('test.txt', read, Stream),
    new_ll(Stream, LL0),
    ( head_tail(LL0, Head0, LL1),
      writeln(Head0),
      head_tail(LL1, Head1, _LL2),
      writeln(Head1)
    ; head_tail(LL0, Head0, LL1),
      writeln(Head0),
      head_tail(LL1, Head1, LL2),
      writeln(Head1),
      head_tail(LL2, Head2, _),
      writeln(Head2)
    ).

lines(File, Lines) :-
    open(File, read, Stream),
    new_ll(Stream, LL),
    freeze(Lines, lines_(Lines, LL)).

lines_([], LL) :-
    is_empty(LL),
    !.
lines_([H|T], LL0) :-
    head_tail(LL0, Head, LL),
    H = Head,
    ( is_empty(LL) -> % terminate list as soon as possible
        T = []
    ; true -> % more content available, fetch it on demand
        freeze(T, lines_(T, LL))
    ).

Also consider using the non-backtrackable list trick in a patch for library(pure_input).

mndrix commented 10 years ago

Perhaps refactor head_tail/3 so that it can use read_line_to_string/2 or read_pending_input/3 for acquiring data from a stream. The former is perfect for lines/2 while the latter is ideal for codes/2 (lazy list of all character codes in a stream). In that case, the non-backtracking list stores "chunks" of data. The lazy list assembles those chunks into a single, long list.