1:- module(ltools, [
    2    count/2,
    3    count/3,
    4    cycle/2,
    5    repeat/2,
    6    repeat/3,
    7    accumulate/3,
    8    batched/3,
    9    slice/3,
   10    slice/4,
   11    pairwise/2,
   12    % more itertools
   13    chunked/3,
   14    divide/3,
   15    split_at_index/4,
   16    window/3,
   17    window/4,
   18    triplewise/2,
   19    intersperse/3,
   20    intersperse/4,
   21    padded_right/4,
   22    padded_left/4,
   23    repeat_each/3,
   24    % combinatorics
   25    cartesian_product/2,
   26    permutations/2,
   27    permutations/3,
   28    combinations/3,
   29    combinations_with_replacement/3
   30]).   31
   32% https://docs.python.org/3/library/itertools.html#itertools.count
   33% https://more-itertools.readthedocs.io/en/stable/api.html
   34
   35times(A,B,C):-
   36    C is B * A.
   43count_(N,_,N).
   44count_(N,Step,IIn):-
   45    N1 is N + Step,
   46    count_(N1,Step,IIn).
   47
   48count_check_args(Start,Step,N):-
   49    must_be(integer, Start),
   50    must_be(integer, Step),
   51    must_be(var, N),
   52    count_(Start,Step,N).
   53
   54
   55count(Start,N):-
   56    count_(Start,1,N).
   62count(Start, Step, N):-
   63    count_(Start,Step,N).
   71cycle_([H|_],_,H).
   72cycle_([_|T],L,H):-
   73    cycle_(T,L,H).
   74cycle_([],L,H):-
   75    cycle_(L,L,H).
   76
   77cycle_check_args(L,C):-
   78    must_be(list,L),
   79    must_be(var,C),
   80    ( L = [] -> C = _ ; cycle_(L,L,C)).
   81
   82cycle(L,C):-
   83    cycle_check_args(L,C).
   90repeat_(V,V).
   91repeat_(V,V):-
   92    repeat_(V,V).
   93
   94repeat(N,V):-
   95    must_be(var, V),
   96    repeat_(N,V).
  104repeat_(V, 1, V):-  !.
  105repeat_(V, T, V):-  T > 0.
  106repeat_(V, T, V):- 
  107    T > 0,
  108    T1 is T - 1,
  109    repeat_(V, T1, V).
  110
  111repeat(N,Times,V):-
  112    must_be(positive_integer, Times),
  113    must_be(var, V),
  114    repeat_(N,Times,V).
  124accumulate(times, L, V):-
  125    must_be(list(number),L),
  126    scanl(times, L, 1, [_|V]).
  127accumulate(plus, L, V):-
  128    must_be(list(number),L),
  129    scanl(plus, L, 0, [_|V]).
*/
  138batched_([], Sz, _, L, L):- Sz > 0.
  139batched_(_, 0, _, L, L).
  140batched_([H|T], 0, Size, _, L):-
  141    batched_([H|T], Size, Size, [], L).
  142batched_([H|T], N, Size, L, LO):-
  143    N > 0,
  144    append(L,[H],LT),
  145    N1 is N - 1,
  146    batched_(T,N1,Size,LT,LO).
  147
  148batched_check_args(L, V, Batch):-
  149    must_be(list,L),
  150    must_be(positive_integer, V),
  151    batched_(L, V, V, [], Batch).
  152
  153batched(L, V, Batch):-
  154    batched_check_args(L, V, Batch).
  162slice(L,End,Sublist):-
  163    slice_check_args(L, 0, End, Sublist).
  171slice_(L, Start, End, Sublist) :-
  172    findall(V, (between(Start, End, I), nth1(I, L, V)), Sublist).
  173
  174slice_check_args(L, Start, End, Sublist):-
  175    must_be(list,L),
  176    must_be(nonneg, Start),
  177    must_be(nonneg, End),
  178    slice_(L, Start, End, Sublist).
  179
  180slice(L,Start,End,Sublist):-
  181    slice_check_args(L, Start, End, Sublist).
  189pairwise_([A,B|_],[A,B]).
  190pairwise_([_,B|T],L):-
  191    pairwise_([B|T],L).
  192
  193pairwise_check_args(L, Sublist):-
  194    must_be(list,L),
  195    pairwise_(L, Sublist).
  196
  197pairwise(L,LO):-
  198    pairwise_check_args(L, LO).
  199
  200
  201%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  202% Combinatorics predicates
  211cartesian_product([],L,L).
  212cartesian_product([List|T],LT,LO):-
  213    member(El,List),
  214    append(LT,[El],LT1),
  215    cartesian_product(T,LT1,LO).
  216
  217cartesian_product(L,Res):-
  218    cartesian_product(L,[],Res).
  231permutations_(ToConsider,Len,Current,P):-
  232    length(Current,N),
  233    ( N >= Len ->
  234    	P = Current ;
  235    	select(El,ToConsider,Rem),
  236    	% member(El,ToConsider),
  237        append(Current,[El],C1),
  238        permutations_(Rem,Len,C1,P)
  239    ).
  240permutations(List,P):-
  241    length(List,N),
  242    permutations(List,N,P).
  243permutations(List,Len,P):-
  244    must_be(positive_integer, Len),
  245    select(El,List,ToConsider),
  246    permutations_(ToConsider,Len,[El],P).
  256combinations(List,Len,P):-
  257    must_be(positive_integer, Len),
  258    combinations_(List,Len,P).
  259combinations_([H|T],Len,P):-
  260    permutations_(T,Len,[H],P).
  261combinations_([_|T],Len,P):-
  262    combinations(T,Len,P).
  273combinations_with_replacement(List,Len,P):-
  274    must_be(positive_integer, Len),
  275    combinations_with_replacement_(List,Len,P).
  276combinations_with_replacement_([H|T],Len,P):-
  277    permutations_([H|T],Len,[H],P).
  278combinations_with_replacement_([_|T],Len,P):-
  279    combinations_with_replacement(T,Len,P).
  280
  281%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  282% more itertools
  283
  284/***
  285 * chunked(+List:list, +Size:int, -Chunk:list)
  286 * Splits the list List into chunks of size Size and unifies
  287 * the result with Chunk. If the length of the list is not
  288 * divisible by Size, the last chunk will be of length 
  289 * less than Size.
  290 * chunked([1, 2, 3, 4, 5, 6], 3, L).
  291 * L = [1, 2, 3] ;
  292 * L = [4, 5, 6]
  293 * chunked([1, 2, 3, 4, 5], 3, L).
  294 * L = [1, 2, 3]
  295 * L = [4, 5]
  296*/
  297chunked_(L, Size, L):-
  298    length(L,N),
  299    Size > N,
  300    N > 0.
  301chunked_(List, Size, Chunk):-
  302    length(Chunk,Size),
  303    append(Chunk, _, List).
  304chunked_(List, Size, Chunk):-
  305    length(Chunk_,Size),
  306    append(Chunk_, Rem, List),
  307    chunked_(Rem, Size, Chunk).
  308
  309chunked(List, Size, Chunk):-
  310    must_be(nonneg, Size),
  311    chunked_(List, Size, Chunk).
  326divide(List, Parts, Divided):-
  327    must_be(nonneg, Parts),
  328    length(List,N),
  329    Parts > 0, 
  330    Parts =< N,
  331    Chunk is ceil(N/Parts),
  332    chunked_(List, Chunk, Divided).
  348split_at_index(List,Index,L0,L1):-
  349    must_be(nonneg, Index),
  350    length(L0, Index),
  351    append(L0,L1,List).
  367window_(List,Size,_Step,Window):-
  368    length(List, N),
  369    N >= Size,
  370    length(Window,Size),
  371    append(Window,_,List).
  372window_(List,Size,Step,Window):-
  373    length(ToRemove,Step),
  374    append(ToRemove,LRem,List),
  375    window_(LRem,Size,Step,Window).
  376window(List, Size, Window):-
  377    window(List, Size, 1, Window).
  378window(List, Size, Step, Window):-
  379    must_be(nonneg, Size),
  380    window_(List,Size,Step,Window).
  391triplewise_([A,B,C|_],[A,B,C]).
  392triplewise_([_,B|T],L):-
  393    triplewise_([B|T],L).
  394triplewise_check_args(L, Sublist):-
  395    must_be(list,L),
  396    triplewise_(L, Sublist).
  397triplewise(L,LO):-
  398    triplewise_check_args(L, LO).
  411intersperse([],_,_,L,L):- !.
  412intersperse(List, El, Step, LT, Res):-
  413    length(L,Step),
  414    length(List,N),
  415    ( N >= Step ->  
  416    	append(L,Rem,List),
  417        append(L,[El],LTT),
  418    	append(LT,LTT,LO) ;
  419    	append(LT,List,LO),
  420        Rem = []
  421    ),
  422    intersperse(Rem,El,Step,LO,Res).
  423
  424intersperse(List, El, Res):-
  425    intersperse(List, El, 1, [], Res).
  426intersperse(List, El, Step, Res):-
  427    intersperse(List, El, Step, [], Res).
  443padded_right(List,Element,TargetLen,Result):-
  444    padded(List,Element,TargetLen,right,Result).
  445padded_left(List,Element,TargetLen,Result):-
  446    padded(List,Element,TargetLen,left,Result).
  447padded(List,Element,TargetLen,Type,Result):-
  448    must_be(integer, TargetLen),
  449    length(List,N),
  450    ( TargetLen =< N ->  
  451        Result = List ;
  452        R is TargetLen - N,
  453        findall(I, repeat(Element,R,I), LPad),
  454        (Type = right ->
  455            append(List,LPad,Result);
  456            append(LPad,List,Result)
  457        )
  458    ).
  469repeat_each_([],_,L,L).
  470repeat_each_([H|T], Times, LT, Res):-
  471    findnsols(Times, I, repeat(H,Times,I), LR),
  472    append(LT, LR, LT1),
  473    repeat_each_(T, Times, LT1, Res).
  474repeat_each(L, Times, Res):-
  475    must_be(positive_integer, Times),
  476    repeat_each_(L, Times, [], Res)