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