Lazy lists with explicit metacalls.

This module provides an alternate implementation of lazy lists where the tail of the list is expanded by a metacall.

llist(A) ---> lnil ; lcons(A, pred(llist(A))).

*/

   10:- module(lazy, 
   11   [  map/3
   12   ,  map/4
   13   ,  member/2
   14   ,  repeat/2
   15   ,  to_llist/2
   16   ,  to_list/2
   17   ,  take/3
   18   ,  decons/3
   19   ,  head/2
   20   ,  tail/2
   21   ,  singleton/2
   22   ,  empty/1
   23   ]).   24
   25
   26singleton(X, lcons(X,=(lnil))).
   27cons(H,TT,lcons(H,TT)).
   28empty(lnil).
 head(+List:llist(A), -Head:A) is semidet
   31head(lcons(X,_),X).
 tail(+List:llist(A), -Tail:llist(A)) is semidet
   34tail(lcons(_,XP),T) :- call(XP,T).
 decons(+List:llist(A), -Head:A, -Tail:llist(A)) is semidet
   37decons(lcons(X,XP),X,T) :- call(XP,T).
 repeat(+X:A, -List:llist(A)) is det
Create a list of infinitely repeating X
   41repeat(X, lcons(X,repeat(X))).
 take(+N:natural, +L1:llist(A), -L2:llist(A)) is semidet
L2 consists of the first N elements of L1. Traversal of L2 will fail if L1 has fewer than N elements.
   46take(0, _, lnil).
   47take(N, lcons(X,XP),lcons(X,lazy:take(M,XT))) :- succ(M,N), call(XP,XT).
   48
   49take1(0, _, =(lnil)).
   50take1(N, XP, =(lcons(X,lazy:take1(M,XT)))) :- succ(M,N), call(XP,lcons(X,XT)).
 to_llist(+L1:llist(A), -L2:list(A)) is det
Conversion from llist(A) to a Prolog list with delayed tail evaluation.
   54to_llist(lnil,[]).
   55to_llist(lcons(X,XP),[X|XX]) :- call(XP,XT), freeze(XX,to_llist(XT,XX)).
 to_list(+L1:llist(A), -L2:list(A)) is det
Conversion from llist(A) to a normal, fully evaluated Prolog list.
   59to_list(lnil,[]).
   60to_list(lcons(X,XP),[X|XX]) :- call(XP,XT), to_list(XT,XX).
 map(+P:pred(A,B), +LA:llist(A), -LB:llist(B)) is det
   63map(_,lnil,lnil).
   64map(P,lcons(X,XP),lcons(Y,lazy:map(P,XT))) :- 
   65   call(P,X,Y), call(XP,XT).  
 map(+P:pred(A,B,C), +LA:llist(A), +LB:llist(B), -LC:llist(C)) is det
   68map(_,lnil,lnil,nil).
   69map(P,lcons(X,XP),lcons(Y,YP),lcons(Z,lazy:map(P,XT,YT))) :- 
   70   call(P,X,Y,Z), call(XP,XT), call(YP,YT).  
 member(-X:A, +List:llist(A)) is nondet
   73member(X,lcons(X,_)).
   74member(X,lcons(_,XP)) :- call(XP,XT), member(X,XT)