1:- module(list_util,
    2          [ cycle/2
    3          , drop/3
    4          , drop_while/3
    5          , group/2
    6          , group_by/3
    7          , group_with/3
    8          , iterate/3
    9          , keysort_r/2
   10          , lazy_findall/3
   11          , lazy_include/3
   12          , lazy_maplist/3
   13          , lines/2
   14          , map_include/3
   15          , map_include/4
   16          , map_include/5
   17          , maximum/2
   18          , maximum_by/3
   19          , maximum_with/3
   20          , minimum/2
   21          , minimum_by/3
   22          , minimum_with/3
   23          , msort_r/2
   24          , oneof/2
   25          , positive_integers/1
   26          , repeat/2
   27          , replicate/3
   28          , sort_by/3
   29          , sort_r/2
   30          , sort_with/3
   31          , span/4
   32          , span/5
   33          , split/3
   34          , split_at/4
   35          , take/3
   36          , take_while/3
   37          , xfy_list/3
   38          ]).   39:- use_module(library(apply_macros)).  % for faster maplist/2
   40:- use_module(library(pairs), [group_pairs_by_key/2, map_list_to_pairs/3, pairs_values/2]).   41:- use_module(library(readutil), [read_line_to_string/2]).   42:- use_module(library(when), [when/2]).   43
   44:- include(nblist).   45:- include(lazy_findall).   46:- include(lines).   47
   48% TODO look through list library of Amzi! Prolog for ideas: http://www.amzi.com/manuals/amzi/libs/list.htm
   49% TODO look through ECLiPSe list library: http://www.eclipseclp.org/doc/bips/lib/lists/index.html
 split(?Combined:list, ?Separator, ?Separated:list(list)) is det
True if lists in Separated joined together with Separator form Combined. Can be used to split a list into sublists or combine several sublists into a single list.

For example,

?- portray_text(true).

?- split("one,two,three", 0',, Parts).
Parts = ["one", "two", "three"].

?- split(Codes, 0',, ["alpha", "beta"]).
Codes = "alpha,beta".
   67split([], _, [[]]) :-
   68    !.  % optimization
   69split([Div|T], Div, [[]|Rest]) :-
   70    split(T, Div, Rest),  % implies: dif(Rest, [])
   71    !.
   72split([H|T], Div, [[H|First]|Rest]) :-
   73    split(T, Div, [First|Rest]).
 take(+N:nonneg, ?List:list, ?Front:list) is det
True if Front contains the first N elements of List. If N is larger than List's length, List=Front.

For example,

?- take(2, [1,2,3,4], L).
L = [1, 2].

?- take(2, [1], L).
L = [1].

?- take(2, L, [a,b]).
L = [a, b|_G1055].
   92take(N, List, Front) :-
   93    split_at(N, List, Front, _).
 split_at(+N:nonneg, ?Xs:list, ?Take:list, ?Rest:list)
True if Take is a list containing the first N elements of Xs and Rest contains the remaining elements. If N is larger than the length of Xs, Xs = Take.

For example,

?- split_at(3, [a,b,c,d], Take, Rest).
Take = [a, b, c],
Rest = [d].

?- split_at(5, [a,b,c], Take, Rest).
Take = [a, b, c],
Rest = [].

?- split_at(2, Xs, Take, [c,d]).
Xs = [_G3219, _G3225, c, d],
Take = [_G3219, _G3225].

?- split_at(1, Xs, Take, []).
Xs = Take, Take = [] ;
Xs = Take, Take = [_G3810].
  120split_at(N,Xs,Take,Rest) :-
  121    split_at_(Xs,N,Take,Rest).
  122
  123split_at_(Rest, 0, [], Rest) :- !. % optimization
  124split_at_([], N, [], []) :-
  125    % cannot optimize here because (+, -, -, -) would be wrong,
  126    % which could possibly be a useful generator.
  127    N > 0.
  128split_at_([X|Xs], N, [X|Take], Rest) :-
  129    N > 0,
  130    succ(N0, N),
  131    split_at_(Xs, N0, Take, Rest).
 take_while(:Goal, +List1:list, -List2:list) is det
True if List2 is the longest prefix of List1 for which Goal succeeds. For example,
even(X) :- 0 is X mod 2.

?- take_while(even, [2,4,6,9,12], Xs).
Xs = [2,4,6].
  145:- meta_predicate take_while(1,+,-).  146take_while(Goal, List, Prefix) :-
  147    span(Goal,List,Prefix,_).
  148
  149
  150% Define an empty_list type to assist with drop/3 documentation
  151:- multifile error:has_type/2.  152error:has_type(empty_list, []).
 drop(+N:nonneg, ?List:list, ?Rest:list) is det
drop(+N:positive_integer, -List:list, +Rest:empty_list) is multi
True if Rest is what remains of List after dropping the first N elements. If N is greater than List's length, Rest = [].

For example,

?- drop(1, [a,b,c], L).
L = [b, c].

?- drop(10, [a,b,c], L).
L = [].

?- drop(1, L, [2,3]).
L = [_G1054, 2, 3].

?- drop(2, L, []).
L = [] ;
L = [_G1024] ;
L = [_G1024, _G1027].
  177drop(N, List, Rest) :-
  178    % see Note_drop_as_split
  179    drop_(List, N, Rest).
  180
  181drop_(L, 0, L) :-
  182    !.  % optimization
  183drop_([], N, []) :-
  184    N > 0.
  185drop_([_|T], N1, Rest) :-
  186    N1 > 0,
  187    succ(N0, N1),
  188    drop_(T, N0, Rest).
  189
  190% Note_drop_as_split:
  191%
  192% drop/3 could be implemented as `split_at(N,List,_,Rest)`.  Unfortunately, that
  193% consumes memory building up a list of dropped elements only to throw it away.
  194% That would make something like drop(1_000_000,List,Rest) too expensive.
 drop_while(:Goal, +List1:list, -List2:list) is det
True if List2 is the suffix remaining after take_while(Goal,List1,_). For example,
even(X) :- 0 is X mod 2.

?- drop_while(even, [2,4,6,9,12], Xs).
Xs = [9,12].
  208:- meta_predicate drop_while(1,+,-).  209drop_while(Goal, List, Suffix) :-
  210    span(Goal,List,_,Suffix).
 span(:Goal, +List:list, -Prefix:list, -Suffix:list) is det
span(:Goal, +List:list, +Prefix:list, -Suffix:list) is semidet
span(:Goal, +List:list, -Prefix:list, +Suffix:list) is semidet
span(:Goal, +List:list, +Prefix:list, +Suffix:list) is semidet
True if Prefix is the longest prefix of List for which Goal succeeds and Suffix is the rest. For any Goal, it is true that append(Prefix,Suffix,List). span/4 behaves as if it were implement as follows (but it's more efficient):
span(Goal,List,Prefix,Suffix) :-
    take_while(Goal,List,Prefix),
    drop_while(Goal,List,Suffix).

For example,

even(X) :- 0 is X mod 2.

?- span(even, [2,4,6,9,12], Prefix, Suffix).
Prefix = [2,4,6],
Suffix = [9,12].
  236:- meta_predicate span(1,+,-,-).  237span(Goal, List, Prefix, Suffix) :-
  238    span_(List, Prefix, [], Suffix, Goal).
 span(:Goal, +List:list, -Prefix:list, ?Tail:list, -Suffix:list) is semidet
This is a version of span/4 that supports difference lists.
?- span(==(a), [a,a,b,c,a], Prefix, Tail, Suffix).
Prefix = [a, a|Tail],
Suffix = [b, c, a].
  250:- meta_predicate span(1,+,-,?,-), span_(+,-,?,-,1).  251span(Goal, List, Prefix, Tail, Suffix) :-
  252    span_(List, Prefix, Tail, Suffix, Goal).
  253
  254span_([], Tail, Tail, [], _).
  255span_([H|Rest], Prefix, Tail, Suffix, Goal) :-
  256    ( call(Goal, H) ->
  257        Prefix = [H|Pre],
  258        span_(Rest, Pre, Tail, Suffix, Goal)
  259    ; % otherwise ->
  260        Suffix = [H|Rest],
  261        Tail = Prefix
  262    ).
 replicate(?N:nonneg, ?X:T, ?Xs:list(T))
True only if Xs is a list containing only the value X repeated N times. If N is less than zero, Xs is the empty list.

For example,

?- replicate(4, q, Xs).
Xs = [q, q, q, q] ;
false.

?- replicate(N, X, [1,1]).
N = 2,
X = 1.

?- replicate(0, ab, []).
true.

?- replicate(N, X, Xs).
N = 0,
Xs = [] ;
N = 1,
Xs = [X] ;
N = 2,
Xs = [X, X] ;
N = 3,
Xs = [X, X, X] ;
... etc.
  293replicate(N,X,Xs) :-
  294    length(Xs,N),
  295    maplist(=(X),Xs).
 repeat(?X, -Xs:list)
True if Xs is an infinite lazy list that only contains occurences of X. If X is nonvar on entry, then all members of Xs will be constrained to be the same term.

For example,

?- repeat(term(X), Rs), Rs = [term(2),term(2)|_].
X = 2
Rs = [term(2), term(2)|_G3041]

?- repeat(X, Rs), take(4, Rs, Repeats).
Rs = [X, X, X, X|_G3725],
Repeats = [X, X, X, X]

?- repeat(12, Rs), take(2, Rs, Repeats).
Rs = [12, 12|_G3630],
Repeats = [12, 12]
  318repeat(X, Xs) :-
  319    cycle([X], Xs).
 cycle(?Sequence, +Xs:list)
True if Xs is an infinite lazy list that contains Sequence, repeated cyclically.

For example,

?- cycle([a,2,z], Xs), take(5, Xs, Cycle).
Xs = [a, 2, z, a, 2|_G3765],
Cycle = [a, 2, z, a, 2]

?- dif(X,Y), cycle([X,Y], Xs), take(3, Xs, Cycle), X = 1, Y = 12.
X = 1,
Y = 12,
Xs = [1, 12, 1|_G3992],
Cycle = [1, 12, 1]
  338cycle(Sequence, Cycle) :-
  339    iterate(stack, Sequence-Sequence, Cycle).
  340
  341% The state is best described as a stack that pops X and updates the state of the
  342% stack to Xs. If the state of the stack is empty, then the stack is reset to the
  343% full stack.
  344stack([]-[X|Xs], Xs-[X|Xs], X).
  345stack([X|Xs]-Stack, Xs-Stack, X).
 oneof(List:list(T), Element:T) is semidet
Same as memberchk/2 with argument order reversed. This form is helpful when used as the first argument to predicates like include/3 and exclude/3.
  353oneof(Xs,X) :-
  354    memberchk(X, Xs).
 map_include(:Goal:callable, +In:list, -Out:list) is det
True if Out (elements Yi) contains those elements of In (Xi) for which call(Goal, Xi, Yi) is true. If call(Goal, Xi, Yi) fails, the corresponding element is omitted from Out. If Goal generates multiple solutions, only the first one is taken.

For example, assuming f(X,Y) :- number(X), succ(X,Y)

?- map_include(f, [1,a,3], L).
L = [2, 4].
  370:- meta_predicate map_include(2, +, -).  371:- meta_predicate map_include_(+, -, 2).  372map_include(F, L0, L) :-
  373    map_include_(L0, L, F).
  374
  375map_include_([], [], _).
  376map_include_([H0|T0], List, F) :-
  377    (   call(F, H0, H)
  378    ->  List = [H|T],
  379        map_include_(T0, T, F)
  380    ;   map_include_(T0, List, F)
  381    ).
 map_include(:Goal:callable, +In0:list, +In1:list, -Out:list) is det
Same as map_include/3, except Goal is binary argument meta predicate.
  386:- meta_predicate map_include(3, +, +, -).  387:- meta_predicate map_include_(+, +, -, 3).  388map_include(F, L0, L1, L) :-
  389    map_include_(L0, L1, L, F).
  390
  391map_include_([], [], [], _).
  392map_include_([H0|T0], [H1|T1], List, F) :-
  393    (  call(F, H0, H1, H)
  394    -> List = [H|T],
  395       map_include_(T0, T1, T, F)
  396    ;  map_include_(T0, T1, List, F)
  397    ).
 map_include(:Goal:callable, +In0:list, +In1:list, +In2:list, -Out:list) is det
Same as map_include/3, except Goal is tertiary argument meta predicate.
  402:- meta_predicate map_include(4, +, +, +, -).  403:- meta_predicate map_include_(+, +, +, -, 4).  404map_include(F, L0, L1, L2, L) :-
  405    map_include_(L0, L1, L2, L, F).
  406
  407map_include_([], [], [], [], _).
  408map_include_([H0|T0], [H1|T1], [H2|T2], List, F) :-
  409    (  call(F, H0, H1, H2, H)
  410    -> List = [H|T],
  411       map_include_(T0, T1, T2, T, F)
  412    ;  map_include_(T0, T1, T2, List, F)
  413    ).
 maximum(?List:list, ?Maximum) is semidet
True if Maximum is the largest element of List, according to compare/3. The same as maximum_by(compare, List, Maximum).
  420maximum(List, Maximum) :-
  421    maximum_by(compare, List, Maximum).
 maximum_with(:Goal, ?List:list, ?Maximum) is semidet
True if Maximum is the largest projected value (according to compare/3) of each element in the list. The projected values are found by applying Goal to each list element.
  428:- meta_predicate maximum_with(2,?,?).  429maximum_with(Project, List, Maximum) :-
  430    map_list_to_pairs(Project, List, Pairs),
  431    maximum_by(compare, Pairs, _-Maximum).
 maximum_by(+Compare, ?List:list, ?Maximum) is semidet
True if Maximum is the largest element of List, according to Compare. Compare should be a predicate with the same signature as compare/3.

If List is not ground the constraint is delayed until List becomes ground.

  441:- meta_predicate maximum_by(3,?,?).  442:- meta_predicate maximum_by(?,3,?,?).  443maximum_by(Compare, List, Maximum) :-
  444    \+ ground(List),
  445    !,
  446    when(ground(List), maximum_by(Compare,List,Maximum)).
  447maximum_by(Compare,[H|T],Maximum) :-
  448    maximum_by(T, Compare, H, Maximum).
  449maximum_by([], _, Maximum, Maximum).
  450maximum_by([H|T], Compare, MaxSoFar, Maximum) :-
  451    call(Compare, Order, H, MaxSoFar),
  452    ( Order = (>) ->
  453        maximum_by(T, Compare, H, Maximum)
  454    ; % otherwise ->
  455        maximum_by(T, Compare, MaxSoFar, Maximum)
  456    ).
 minimum(?List:list, ?Minimum) is semidet
True if Minimum is the smallest element of List, according to compare/3. The same as minimum_by(compare, List, Minimum).
  463minimum(List, Minimum) :-
  464    minimum_by(compare, List, Minimum).
 minimum_with(:Goal, ?List:list, ?Minimum) is semidet
True if Minimum is the largest projected value (according to compare/3) of each element in the list. The projected values are found by applying Goal to each list element.
  472:- meta_predicate minimum_with(2,?,?).  473minimum_with(Project, List, Minimum) :-
  474    map_list_to_pairs(Project, List, Pairs),
  475    minimum_by(compare, Pairs, _-Minimum).
 minimum_by(+Compare, ?List:list, ?Minimum) is semidet
True if Minimum is the smallest element of List, according to Compare. Compare should be a predicate with the same signature as compare/3.

If List is not ground the constraint is delayed until List becomes ground.

  485:- meta_predicate minimum_by(3,?,?).  486:- meta_predicate minimum_by(?,3,?,?).  487minimum_by(Compare, List, Minimum) :-
  488    \+ ground(List),
  489    !,
  490    when(ground(List), minimum_by(Compare,List,Minimum)).
  491minimum_by(Compare,[H|T],Minimum) :-
  492    minimum_by(T, Compare, H, Minimum).
  493minimum_by([], _, Minimum, Minimum).
  494minimum_by([H|T], Compare, MinSoFar, Minimum) :-
  495    call(Compare, Order, H, MinSoFar),
  496    ( Order = (<) ->
  497        minimum_by(T, Compare, H, Minimum)
  498    ; % otherwise ->
  499        minimum_by(T, Compare, MinSoFar, Minimum)
  500    ).
 iterate(:Goal, +State, -List:list)
List is a lazy (possibly infinite) list whose elements are the result of repeatedly applying Goal to State. Goal may fail to end the list. Goal is called like
call(Goal, State0, State, Value)

The first value in List is the value produced by calling Goal with State. For example, a lazy, infinite list of positive integers might be defined with:

incr(A,B,A) :- succ(A,B).
integers(Z) :- iterate(incr,1,Z). % Z = [1,2,3,...]

Calling iterate/3 with a mode different than described in the modeline throws an exception. Other modes may be supported in the future, so don't rely on the exception to catch your mode errors.

  521:- meta_predicate iterate(3,+,?), iterate_(3,+,?).  522iterate(Goal, State, List) :-
  523    must_be(nonvar, Goal),
  524    must_be(nonvar, State),
  525    freeze(List, iterate_(Goal, State, List)).
  526
  527iterate_(Goal, State0, List) :-
  528    ( call(Goal, State0, State, X) ->
  529        List = [X|Xs],
  530        iterate(Goal, State, Xs)
  531    ; % goal failed, list is done ->
  532        List = []
  533    ).
 positive_integers(-List:list(positive_integer)) is det
Unifies List with a lazy, infinite list of all positive integers.
  538positive_integers(List) :-
  539    iterate(positive_integers_, 1, List).
  540
  541positive_integers_(A,B,A) :-
  542    succ(A,B).
 lazy_include(+Goal, +List1:list, -List2:list) is det
Like include/3 but produces List2 lazily. This predicate is helpful when List1 is infinite or very large.
  549:- meta_predicate lazy_include(1,+,-), lazy_include_(+,1,-).  550lazy_include(Goal, Original, Lazy) :-
  551    freeze(Lazy, lazy_include_(Original, Goal, Lazy)).
  552
  553lazy_include_([], _, []).
  554lazy_include_([H|T], Goal, Lazy) :-
  555    ( call(Goal, H) ->
  556        Lazy = [H|Rest],
  557        freeze(Rest, lazy_include_(T, Goal, Rest))
  558    ; % exclude this element ->
  559        lazy_include_(T, Goal, Lazy)
  560    ).
 lazy_maplist(:Goal, ?List1:list, ?List2:list)
True if List2 is a list of elements that all satisfy Goal applied to each element of List1. This is a lazy version of maplist/3.
  567:- meta_predicate lazy_maplist(2, ?, ?), lazy_maplist_(?,?,2).  568lazy_maplist(Goal, Xs, Ys) :-
  569    freeze(Ys, freeze(Xs, lazy_maplist_(Xs, Ys, Goal))).
  570
  571lazy_maplist_([], [], _).
  572lazy_maplist_([X|Xs], [Y|Ys], Goal) :-
  573    call(Goal, X, Y),
  574    lazy_maplist(Goal, Xs, Ys).
 group_with(:Goal, +List:list, -Grouped:list(list)) is det
Groups elements of List using Goal to project something out of each element. Elements are first sorted based on the projected value (like sort_with/3) and then placed into groups for which the projected values unify. Goal is invoked as call(Goal,Elem,Projection).

For example,

?- group_with(atom_length, [a,hi,bye,b], Groups).
Groups = [[a,b],[hi],[bye]]
  589:- meta_predicate group_with(2,+,-).  590group_with(Goal,List,Groups) :-
  591    map_list_to_pairs(Goal, List, Pairs),
  592    keysort(Pairs, Sorted),
  593    group_pairs_by_key(Sorted, KeyedGroups),
  594    pairs_values(KeyedGroups, Groups).
 group_by(:Goal, +List:list, -Groups:list(list)) is det
group_by(:Goal, -List:list, +Groups:list(list)) is semidet
Groups elements of List using a custom Goal predicate to test for equality. If Goal is true, then two elements compare as equal. Goal takes the form

call(Goal, X, Y)

Adjacent and equal elements of List will be grouped together if and only if Goal is true

For example,

?- group_by(==, `Mississippi`, Gs),
maplist([Codes,String]>>string_codes(String,Codes), Gs, Groups).

Groups = ["M", "i", "ss", "i", "ss", "i", "pp", "i"].
  615:- meta_predicate group_by(2, +, -), group_by_(+,2,-), group_by_(?,?,2,?,?).  616group_by(Goal,List,Groups) :-
  617    ( var(List), var(Groups) ->
  618        instantiation_error(List)
  619    ; otherwise ->
  620        group_by_(List,Goal,Groups)
  621    ).
  622
  623group_by_([],_,[]) :- !.
  624group_by_([X|Rest],Goal,[[X|Group]|Groups]) :-
  625    group_by_(Rest,X,Goal,Group,Groups).
  626
  627group_by_([],_,_,[],[]) :- !.
  628group_by_([Y|Rest],X,Goal,[Y|Group],Groups) :-
  629    call(Goal,X,Y),
  630    !,
  631    group_by_(Rest,Y,Goal,Group,Groups).
  632group_by_([Y|Rest],_,Goal,[],[[Y|Group]|Groups]) :-
  633    group_by_(Rest,Y,Goal,Group,Groups).
 group(+List:list, -Groups:list(list)) is semidet
True if Groups is a compressed version of the elements in List. This predicate uses term equality per ==/2 as the comparison goal for group_by/2. See the description of group_by/2.
  641group(List, Groups) :-
  642    group_by(==, List, Groups).
 sort_by(:Goal, +List:list, -Sorted:list) is det
See sort_with/3. This name was assigned to the wrong predicate in earlier versions of this library. It now throws an exception. It will eventually be replaced with a different implementation.
  649:- meta_predicate sort_by(2,+,-).  650sort_by(_,_,_) :-
  651    throw("Predicate sort_by/2 does not exist. Use sort_with/2 instead").
 sort_with(:Goal, +List:list, -Sorted:list) is det
Sort a List of elements using Goal to project something out of each element. This is often more natural than creating an auxiliary predicate for predsort/3. For example, to sort a list of atoms by their length:
?- sort_with(atom_length, [cat,hi,house], Atoms).
Atoms = [hi,cat,house].

Standard term comparison is used to compare the results of Goal. Duplicates are not removed. The sort is stable.

If Goal is expensive, sort_with/3 is more efficient than predsort/3 because Goal is called once per element, O(N), rather than repeatedly per element, O(N log N).

  669:- meta_predicate sort_with(2,+,-).  670sort_with(Goal, List, Sorted) :-
  671    map_list_to_pairs(Goal, List, Pairs),
  672    keysort(Pairs, SortedPairs),
  673    pairs_values(SortedPairs, Sorted).
 sort_r(+List:list, -ReverseSorted:list) is det
Like sort/2 but produces a list sorted in reverse order.
  678sort_r --> sort, reverse.
 msort_r(+List:list, -ReverseSorted:list) is det
Like msort/2 but produces a list sorted in reverse order.
  684msort_r --> msort, reverse.
 keysort_r(+List:list, -ReverseSorted:list) is det
Like keysort/2 but produces a list sorted in reverse order.
  690keysort_r --> keysort, reverse.
 xfy_list(?Op:atom, ?Term, ?List) is det
True if elements of List joined together with xfy operator Op gives Term. Usable in all directions.

For example,

?- xfy_list(',', (a,b,c), L).
L = [a, b, c].

?- xfy_list(Op, 4^3^2, [4,3,2]).
Op = (^).
  707xfy_list(Op, Term, [Left|List]) :-
  708    Term =.. [Op, Left, Right],
  709    xfy_list(Op, Right, List),
  710    !.
  711xfy_list(_, Term, [Term])