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