View source with formatted comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2016-2025, VU University Amsterdam
    7                              CWI Amsterdam
    8                              SWI-Prolog Solutions b.v.
    9    All rights reserved.
   10
   11    Redistribution and use in source and binary forms, with or without
   12    modification, are permitted provided that the following conditions
   13    are met:
   14
   15    1. Redistributions of source code must retain the above copyright
   16       notice, this list of conditions and the following disclaimer.
   17
   18    2. Redistributions in binary form must reproduce the above copyright
   19       notice, this list of conditions and the following disclaimer in
   20       the documentation and/or other materials provided with the
   21       distribution.
   22
   23    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   24    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   25    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   26    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   27    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   28    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   29    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   30    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   31    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   32    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   33    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   34    POSSIBILITY OF SUCH DAMAGE.
   35*/
   36
   37:- module(lazy_lists,
   38          [ lazy_list/2,                        % :Next, -List
   39            lazy_list/3,                        % :Next, +State0, -List
   40                                                % Utilities
   41            lazy_list_materialize/1,            % ?List
   42            lazy_list_length/2,                 % +List, -Len
   43
   44            lazy_findall/3,                     % ?Templ, :Goal, -List
   45            lazy_findall/4,                     % +ChunkSize, ?Templ, :Goal, -List
   46                                                % Interators
   47            lazy_get_codes/4,                   % +Stream, +N, -List, -Tail
   48            lazy_read_terms/4,                  % +Stream, +Options, -List, -Tail
   49            lazy_read_lines/4,                  % +Stream, +Options, -List, -Tail
   50
   51            lazy_message_queue/4,               % +Queue, +Options, -List, -Tail
   52            lazy_engine_next/4,                 % +Engine, +N, -List, -Tail
   53
   54            lazy_list_iterator/4                % +Iterator, -Next, :GetNext,
   55                                                % :TestEnd
   56          ]).   57:- autoload(library(error),
   58	    [type_error/2,instantiation_error/1,must_be/2]).   59:- autoload(library(lists),[append/3]).   60:- autoload(library(option),[select_option/4,option/3]).   61:- autoload(library(readutil),
   62	    [read_line_to_string/2,read_line_to_codes/2]).   63
   64
   65:- meta_predicate
   66    lazy_list(2, -),
   67    lazy_list(3, +, -),
   68    lazy_findall(?, 0, -),
   69    lazy_findall(+, ?, 0, -).   70
   71/** <module> Lazy list handling
   72
   73This module builds a lazy list from   a predicate that fetches a _slice_
   74of this list. In addition it provides _interactors_ (slice constructors)
   75for several common use cases for lazy  lists, such as reading objects of
   76several sizes from files (characters,   lines,  terms), reading messages
   77from message queues and reading answers from _engines_.
   78
   79Lazy lists are lists that  end  in   a  constraint.  Trying to unify the
   80constraint forces the next slice of the list  to be fetched and added to
   81the list.
   82
   83The typical use case for lazy lists is to   run a DCG grammar on it. For
   84example, an _agent_ may be listening on a socket and turn the line-based
   85message protocol into a list using the fragment below.
   86
   87```
   88        ...,
   89        tcp_open(Socket, Read, Write),
   90        lazy_list(lazy_read_lines(Read, [as(codes)]), List),
   91        phrase(action, List).
   92```
   93
   94Typically, the iterator works on a globally allocated object that is not
   95always subject to garbage collection.  In such cases, the skeleton usage
   96follows the pattern below:
   97
   98```
   99        setup_call_cleanup(
  100            <open resource>(R),
  101            (  lazy_list(<iterator>(R), List),
  102               process_list(List)
  103            ),
  104            <close resource>(R))
  105```
  106
  107This is rather unfortunately, but there is no way we can act on the fact
  108that `List` is no further accessed. In  some cases, e.g., message queues
  109or engines, the resource is subject to (atom) garbage collection.
  110*/
  111
  112:- predicate_options(lazy_read_terms/4, 2,
  113                     [ chunk(positive_integer),
  114                       pass_to(read_term/3, 3)
  115                     ]).  116:- predicate_options(lazy_read_lines/4, 2,
  117                     [ chunk(positive_integer),
  118                       as(oneof([atom,string,codes,chars]))
  119                     ]).  120:- predicate_options(lazy_message_queue/4, 2,
  121                     [ chunk(positive_integer),
  122                       pass_to(thread_get_message/3, 3)
  123                     ]).  124
  125%!  lazy_list(:Next, -List)
  126%
  127%   Create a lazy list from a callback. Next is called repeatedly to
  128%   extend the list. It is called   as call(Next, List, Tail), where
  129%   the _difference list_ List\Tail produces the   next slice of the
  130%   list. If the end of  the  input   is  reached,  `List` must be a
  131%   proper list and `Tail` must be `[]`.
  132%
  133%   @bug The content returned  by  the   iterator  is  duplicated in
  134%   nb_setarg/3. This is  needed  by  avoid   the  risk  of  trailed
  135%   assignments in the structure. Avoiding   this  duplication would
  136%   significantly reduce the overhead.
  137
  138lazy_list(Next, List) :-
  139    put_attr(List, lazy_lists, lazy_list(Next, _)).
  140
  141% (*) We need a copy of the  list   where  the copy must include the new
  142% attributed  variable  to  avoid  that   backtracking  makes  the  list
  143% non-lazy.  We do want to avoid copying `Next`.  So, we add a dummy and
  144% then replace this using nb_linkarg/3 with our Next.
  145
  146attr_unify_hook(State, Value) :-
  147    State = lazy_list(Next, Read),
  148    (   var(Read)
  149    ->  call(Next, NewList, Tail),
  150        (   Tail == []
  151        ->  nb_setarg(2, State, NewList)
  152        ;   put_attr(Tail, lazy_lists, lazy_list(dummy, _)),  % See (*)
  153            nb_setarg(2, State, NewList),
  154            arg(2, State, NewListCP),
  155            '$skip_list'(_, NewListCP, TailCP),
  156            get_attr(TailCP, lazy_lists, LazyList),
  157            nb_linkarg(1, LazyList, Next)
  158        ),
  159        arg(2, State, Value)
  160    ;   Value = Read
  161    ).
  162
  163attribute_goals(X) -->
  164    { get_attr(X, lazy_lists, lazy_list(Next, _)) },
  165    [lazy_list(Next, X)].
  166
  167%!  lazy_list(:Next, +State0, -List)
  168%
  169%   Create a lazy list where the next element is defined by
  170%
  171%       call(Next, State0, State1, Head)
  172%
  173%   The example below uses this  predicate   to  define  a lazy list
  174%   holding the Fibonacci numbers. Our state  keeps the two previous
  175%   Fibonacci numbers.
  176%
  177%     ```
  178%     fibonacci_numbers(L) :-
  179%         lazy_list(fib, state(-,-), L).
  180%
  181%     fib(state(-,-), state(0,-), 0) :- !.
  182%     fib(state(0,-), state(1,0), 1) :- !.
  183%     fib(state(P,Q), state(F,P), F) :-
  184%         F is P+Q.
  185%     ```
  186%
  187%   The above can be used to retrieve   the Nth Fibonacci number. As
  188%   fib/2 provides no access  to  the   complete  list  of Fibonacci
  189%   numbers, this can be used to generate large Fibonacci numbers.
  190%
  191%     ```
  192%     fib(N, F) :-
  193%         fibonacci_numbers(L),
  194%         nth1(N, L, F).
  195%     ```
  196
  197lazy_list(Next, State0, List) :-
  198    lazy_list(lazy_state(Next, s(State0)), List).
  199
  200lazy_state(Pred, LState, [H|T], T) :-
  201    LState = s(State0),
  202    call(Pred, State0, State1, H),
  203    !,
  204    nb_setarg(1, LState, State1).
  205lazy_state(_, _, [], []).
  206
  207
  208                 /*******************************
  209                 *   OPERATIONS ON LAZY LISTS   *
  210                 *******************************/
  211
  212%!  lazy_list_materialize(?List) is det.
  213%
  214%   Materialize the lazy list.
  215
  216lazy_list_materialize(List) :-
  217    '$skip_list'(_, List, Tail),
  218    (   var(Tail),
  219        Tail = [_|T2]
  220    ->  lazy_list_materialize(T2)
  221    ;   Tail = []
  222    ->  true
  223    ;   type_error(list, Tail)
  224    ).
  225
  226%!  lazy_list_length(+List, -Len) is det.
  227%
  228%   True if Len is the length of   the  materialized lazy list. Note
  229%   that length/2 reports the length   of the currently materialized
  230%   part and on backtracking longer lists.
  231
  232lazy_list_length(List, Len) :-
  233    lazy_list_length(List, 0, Len).
  234
  235lazy_list_length(List, L0, L) :-
  236    !,
  237    '$skip_list'(N, List, Tail),
  238    (   var(Tail),
  239        Tail = [_|T2]
  240    ->  L1 is L0+N+1,
  241        lazy_list_length(T2, L1, L)
  242    ;   Tail = []
  243    ->  L is L0+N
  244    ;   type_error(list, Tail)
  245    ).
  246
  247
  248                 /*******************************
  249                 *          INTERATORS          *
  250                 *******************************/
  251
  252lazy_list_expand_handler(
  253    lazy_list_iterator(Handler, Next, Get1, TestEnd),
  254    Clauses) :-
  255    negate(TestEnd, NotTestEnd),
  256    extend_goal(Handler, [N, List, Tail], Head),
  257    extend_goal(Handler, [N2,T,Tail], Recurse),
  258    general_goal(Handler, Handler2),
  259    extend_goal(Handler2, [_, Tail,Tail], Head2),
  260    Clauses = [ (Head :-
  261                    succ(N2, N), !,
  262                    (   Get1,
  263                        NotTestEnd
  264                    ->  List = [Next|T],
  265                        Recurse
  266                    ;   List = [],
  267                        Tail = []
  268                    )),
  269                (Head2)
  270              ].
  271
  272negate(A==B, A\==B) :- !.
  273negate(fail, true) :- !.
  274negate(false, true) :- !.
  275negate(Goal, \+ Goal).
  276
  277extend_goal(Var, _, _) :-
  278    var(Var),
  279    !,
  280    instantiation_error(Var).
  281extend_goal(M:G, Args, M:GX) :-
  282    !,
  283    extend_goal(G, Args, GX).
  284extend_goal(Name, Args, GX) :-
  285    atom(Name),
  286    !,
  287    compound_name_arguments(GX, Name, Args).
  288extend_goal(G, XArgs, GX) :-
  289    compound_name_arguments(G, Name, Args0),
  290    append(Args0, XArgs, Args),
  291    compound_name_arguments(GX, Name, Args).
  292
  293general_goal(Var, Var) :-
  294    var(Var),
  295    !.
  296general_goal(M:G, M:GG) :-
  297    !,
  298    general_goal(G, GG).
  299general_goal(Atom, Atom) :-
  300    atom(Atom),
  301    !.
  302general_goal(G, GG) :-
  303    !,
  304    compound_name_arity(G, Name, Arity),
  305    compound_name_arity(GG, Name, Arity).
  306
  307:- multifile
  308    system:term_expansion/2.  309
  310system:term_expansion((:- lazy_list_iterator(It, One, GetNext, TestEnd)),
  311                      Expanded) :-
  312    lazy_list_expand_handler(
  313        lazy_list_iterator(It, One, GetNext, TestEnd),
  314        Expanded).
  315
  316%!  lazy_list_iterator(+Iterator, -Next, :GetNext, :TestEnd)
  317%
  318%   Directive to create a lazy list  iterator from a predicate that
  319%   gets a single next value.
  320
  321lazy_list_iterator(Iterator, Next, GetNext, TestEnd) :-
  322    throw(error(context_error(nodirective,
  323                              lazy_list_iterator(Iterator, Next,
  324                                                  GetNext, TestEnd)),
  325                _)).
  326
  327%!  lazy_get_codes(+Stream, +N, -List, -Tail)
  328%
  329%   Lazy list iterator to get character   codes  from a stream.
  330%
  331%   @see library(pure_input) The predicate lazy_get_codes/4 provides
  332%   similar functionality to what   stream_to_lazy_list/2 does while
  333%   in addition library(pure_input) is faster due to the use of more
  334%   low-level primitives and supports fetching   the location in the
  335%   stream.
  336
  337:- lazy_list_iterator(lazy_get_codes(Stream), Code,
  338                      get_code(Stream, Code),
  339                      Code == -1).  340
  341%!  lazy_read_terms(+Stream, +Options, -List, -Tail)
  342%
  343%   Turn a stream into a lazy list of Prolog terms.  Options are
  344%   passed to read_term/3, except for:
  345%
  346%     - chunk(ChunkSize)
  347%     Determines the read chunk size.  Default is 10.
  348
  349lazy_read_terms(Stream, Options, List, Tail) :-
  350    select_option(chunk(N), Options, ReadOptions, 10),
  351    lazy_read_terms_(Stream, ReadOptions, N, List, Tail).
  352
  353:- lazy_list_iterator(lazy_read_terms_(Stream, Options), Term,
  354                      read_term(Stream, Term, Options),
  355                      Term == end_of_file).  356
  357%!  lazy_read_lines(+Stream, +Options, -List, -Tail) is det.
  358%
  359%   Lazy list iterator to read lines from Stream.  Options include:
  360%
  361%     - chunk(ChunkSize)
  362%     Determines the read chunk size.  Default is 10.
  363%     - as(+Type)
  364%     Determine the output type for each line.  Valid values are
  365%     `atom`, `string`, `codes` or `chars`.  Default is `string`.
  366
  367lazy_read_lines(Stream, Options, List, Tail) :-
  368    option(chunk(ChunkSize), Options, 10),
  369    option(as(Type), Options, string),
  370    must_be(positive_integer, ChunkSize),
  371    must_be(oneof([atom,string,codes,chars]), Type),
  372    lazy_read_lines(Type, Stream, ChunkSize, List, Tail).
  373
  374lazy_read_lines(string, Stream, ChunkSize, List, Tail) :-
  375    lazy_read_string_lines(Stream, ChunkSize, List, Tail).
  376lazy_read_lines(atom, Stream, ChunkSize, List, Tail) :-
  377    lazy_read_atom_lines(Stream, ChunkSize, List, Tail).
  378lazy_read_lines(codes, Stream, ChunkSize, List, Tail) :-
  379    lazy_read_codes_lines(Stream, ChunkSize, List, Tail).
  380lazy_read_lines(chars, Stream, ChunkSize, List, Tail) :-
  381    lazy_read_chars_lines(Stream, ChunkSize, List, Tail).
  382
  383:- lazy_list_iterator(lazy_read_string_lines(Stream), Line,
  384                      read_line_to_string(Stream, Line),
  385                      Line == end_of_file).  386:- lazy_list_iterator(lazy_read_codes_lines(Stream), Line,
  387                      read_line_to_codes(Stream, Line),
  388                      Line == end_of_file).  389:- lazy_list_iterator(lazy_read_chars_lines(Stream), Line,
  390                      read_line_to_chars(Stream, Line),
  391                      Line == end_of_file).  392:- lazy_list_iterator(lazy_read_atom_lines(Stream), Line,
  393                      read_line_to_atom(Stream, Line),
  394                      Line == -1).  395
  396read_line_to_chars(Stream, Chars) :-
  397    read_line_to_string(Stream, String),
  398    (   String == end_of_file
  399    ->  Chars = String
  400    ;   string_chars(String, Chars)
  401    ).
  402
  403read_line_to_atom(Stream, Atom) :-
  404    read_line_to_string(Stream, String),
  405    (   String == end_of_file
  406    ->  Atom = -1
  407    ;   atom_string(Atom, String)
  408    ).
  409
  410%!  lazy_message_queue(+Queue, +Options, -List, -Tail) is det.
  411%
  412%   Lazy list iterator for message  queues.   Options  are passed to
  413%   thread_get_message/3. In addition,  the   following  options are
  414%   processed:
  415%
  416%     - chunk(ChunkSize)
  417%     Determines the read chunk size.  Default is 1.
  418%
  419%   A thread can listen to its own message queue using
  420%
  421%   ```
  422%           thread_self(Me),
  423%           lazy_list(lazy_message_queue(Me, []), List),
  424%           phrase(action(List)).
  425%   ```
  426
  427lazy_message_queue(Queue, Options, List, Tail) :-
  428    select_option(chunk(ChunkSize), Options, QueueOptions, 1),
  429    lazy_message_queue_(Queue, QueueOptions, ChunkSize, List, Tail).
  430
  431:- lazy_list_iterator(lazy_message_queue_(Queue, Options), Message,
  432                      thread_get_message(Queue, Message, Options),
  433                      fail).  434
  435
  436%!  lazy_engine_next(+Engine, +N, -List, -Tail)
  437%
  438%   Lazy list iterator for  engines.  This   is  used  to  implement
  439%   lazy_findall/3,4.
  440
  441:- lazy_list_iterator(lazy_engine_next(Engine), Answer,
  442                      engine_next(Engine, Answer),
  443                      fail).  444
  445%!  lazy_findall(?Templ, :Goal, -List) is det.
  446%!  lazy_findall(+ChunkSize, ?Templ, :Goal, -List) is det.
  447%
  448%   True when List is a lazy  list containing the instantiations for
  449%   Template for each  answer  of  Goal.   Goal  is  executed  in an
  450%   _engine_ (see engine_create/3).
  451%
  452%   @bug    Engines are reclaimed by atom garbage collection.  As
  453%           they can be quite expensive, a large amount of resources
  454%           may be waiting for collection.  If the list is fully
  455%           materialized only the dead engine remains, which is
  456%           fairly cheap.
  457
  458lazy_findall(Templ, Goal, List) :-
  459    lazy_findall(1, Templ, Goal, List).
  460lazy_findall(Chunk, Templ, Goal, List) :-
  461    engine_create(Templ, Goal, Engine),
  462    lazy_list(lazy_engine_next(Engine, Chunk), List).
  463
  464
  465                 /*******************************
  466                 *            SANDBOX           *
  467                 *******************************/
  468
  469:- multifile
  470    sandbox:safe_meta_predicate/1.  471
  472sandbox:safe_meta_predicate(lazy_lists:lazy_findall/3).
  473sandbox:safe_meta_predicate(lazy_lists:lazy_findall/4).
  474sandbox:safe_meta_predicate(lazy_lists:lazy_list/2).
  475sandbox:safe_meta_predicate(lazy_lists:lazy_list/3).
  476
  477		 /*******************************
  478		 *  SUPPRESS AUTOLOAD WARNINGS	*
  479		 *******************************/
  480
  481'$nowarn_autoload'(_, _)