lazy_findall(:Template, +Goal, -List:list) is det
Like findall/3 but List is constructed lazily. This allows it to be used when Goal produces many (or infinite) solutions.

Goal is always executed at least once, even if it's not strictly necessary. Goal may be executed in advance, even if the associated value in List has not been demanded yet. This should only be important if Goal performs side effects whose timing is important to you.

If you don't consume all of List, it's likely that a worker thread will be left hanging. This is a temporary implementation detail which we hope to resolve.

   14:- meta_predicate lazy_findall(?,0,?), lazy_findall_search(+,?,0).   15lazy_findall(Template,Goal,List) :-
   16    lazy_findall_flow(Template,Goal,Flow),
   17    ( next(Flow,Value0) -> % eager first value (to detect instant failure)
   18        finalize_value(Flow,Value0,Value),
   19        List=[Value|Rest],
   20        flow_to_llist(Flow,Rest)
   21    ; otherwise ->
   22        List=[]
   23    ).
   24
   25lazy_findall_search(ResponseQ,Template,Goal) :-
   26    call_ended(Goal,Ended),
   27    ( Ended=more -> % Goal has unexplored choicepoints
   28        thread_get_message(send_a_solution),
   29        thread_send_message(ResponseQ,a_solution(Template)),
   30        fail % explore other choicepoints
   31    ; Ended=done -> % Goal found final solution
   32        lazy_findall_final(ResponseQ,just(Template))
   33    ; Ended=fail ->
   34        lazy_findall_final(ResponseQ,nothing)
   35    ; Ended=exception(E) ->
   36        lazy_findall_final(ResponseQ,exception(E))
   37    ).
   38
   39lazy_findall_final(ResponseQ,Solution) :-
   40    thread_send_message(ResponseQ,final_solution),
   41    thread_exit(Solution).
 call_ended(:Goal, -Status) is det
True if calling Goal ends as indicated by Status. Status is one of the following:
   53:- meta_predicate call_ended(0,?).   54call_ended(Goal,End) :-
   55    ( catch(call_cleanup(Goal,End=done),E,End=exception(E)) *->
   56        ( var(End) -> End=more ; ! )
   57    ; otherwise ->
   58        End=fail, !  % Goal failed immediately
   59    ).
   60call_ended(_,fail).  % Goal fails on backtracking
   61
   62
   63:- meta_predicate lazy_findall_flow(?,0,?).   64lazy_findall_flow(Template,Goal,Flow) :-
   65    gensym(lazy_findall_,ThreadAlias),  % see Note_findall_alias
   66    message_queue_create(ResponseQ,[max_size(1)]),
   67    thread_create(
   68        lazy_findall_search(ResponseQ,Template,Goal),
   69        _ThreadId,
   70        [alias(ThreadAlias)]
   71    ),
   72    Flow = findall_flow(ThreadAlias,ResponseQ).
   73
   74/*
   75Note_findall_alias:
   76
   77To implement flow:at_eof/1 we must be able to recognize when a thread no longer
   78exists. SWI-Prolog's default thread IDs are reused after a thread's resources
   79are garbage collected. If we used the default thread IDs, we might encounter the
   80following scenario:
   81
   82  1. we start lazy_findall/3
   83  2. our worker thread exits
   84  3. another thread starts
   85  4. at_eof/1 thinks the worker thread still exists
   86
   87By using gensym/2 and a thread alias, we can be certain that our thread ID is
   88never reused.
   89*/
   90
   91at_eof(findall_flow(Thread,_ResponseQ)) :-
   92    ( thread_exists(Thread) ->
   93        thread_property(Thread,status(exited(nothing))),
   94        thread_join(Thread,_)
   95    ; otherwise -> % worker is gone. flow is finished
   96        true
   97    ),
   98    % invariant at this point: worker thread is gone
   99    true.
  100
  101thread_exists(Thread) :-
  102    catch(thread_property(Thread,status(_)), _, fail).
  103
  104
  105next(findall_flow(Thread,ResponseQ),Solution) :-
  106    catch(thread_send_message(Thread,send_a_solution),_,true), % maybe thread's gone
  107    thread_get_message(ResponseQ,Response),
  108    findall_next(Response,Thread,Solution).
  109
  110findall_next(a_solution(X),_,just(X)).
  111findall_next(final_solution,Thread,Solution) :-
  112    % final solution is waiting. join worker thread to receive it
  113    thread_join(Thread,exited(MaybeSolution)),
  114    ( MaybeSolution=nothing ->
  115        fail  % final solution was a spurious choicepoint
  116    ; otherwise ->
  117        Solution=MaybeSolution
  118    ).
  119
  120
  121finalize_value(findall_flow(_,_),X0,X) :-
  122    lazy_findall_finalize_value(X0,X).
  123
  124lazy_findall_finalize_value(just(X),X).
  125lazy_findall_finalize_value(exception(E),_) :-
  126    throw(E)