1/*  File:    read/until.pl
    2    Author:  Roy Ratcliffe
    3    Created: Jul 12 2025
    4    Purpose: Read Until
    5*/
    6
    7:- module(read_until,
    8          [ read_stream_to_codes_until_end_of_file/2, % +In, -Codes
    9            read_stream_to_codes_until/3              % +In, -Codes, +Until
   10          ]).   11:- autoload(library(readutil), [read_stream_to_codes/2]).
 read_stream_to_codes_until_end_of_file(+In, -Codes) is nondet
 read_stream_to_codes_until(+In, -Codes, +Until) is nondet
Reads Codes from a stream until it finds a specific code term, such as end_of_file. The predicate reads the stream until it encounters the Until code term, which defaults to end_of_file. It succeeds non-deterministically for each chunk read before reaching the Until code term. Use this predicate to process multiple messages or data chunks from a stream, handling each chunk separately. The Codes variable contains the codes read from the stream, and the predicate succeeds until it reaches the Until condition.
Arguments:
In- The input stream to read from.
Codes- The codes read from the stream.
Until- The code term that terminates the reading.
   29read_stream_to_codes_until_end_of_file(In, Codes) :-
   30    read_stream_to_codes_until(In, Codes, end_of_file).
   31
   32read_stream_to_codes_until(In, Codes, Until) :-
   33    % Use repeat/0 to allow backtracking for each chunk read until `Until` is
   34    % encountered. The cut (!) and fail ensure the predicate only succeeds for
   35    % valid chunks and stops at `Until`.
   36    repeat,
   37    (   read_stream_to_codes(In, Codes),
   38        Codes \== Until
   39    ->  true
   40    ;   % Cut (!) and fail here to terminate the repeat loop when
   41        % `Until` is encountered.
   42        !,
   43        fail
   44    )