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 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 25 cartesian_product/2,
26 permutations/2,
27 permutations/3,
28 combinations/3,
29 combinations_with_replacement/3
30]). 31
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
54count(Start,N):-
55 count_check_args(Start,1,N).
61count(Start, Step, N):-
62 count_(Start,Step,N).
70cycle_([H|_],_,H).
71cycle_([_|T],L,H):-
72 cycle_(T,L,H).
73cycle_([],L,H):-
74 cycle_(L,L,H).
75
76cycle_check_args(L,C):-
77 must_be(list,L),
78 ( L = [] -> C = [] ; cycle_(L,L,C)).
79
80cycle(L,C):-
81 cycle_check_args(L,C).
88repeat_(V,V).
89repeat_(V,V):-
90 repeat_(V,V).
91
92repeat(V,V).
93repeat(V,V):-
94 repeat(V,V).
102repeat_(V, T, V):- T > 0.
103repeat_(V, T, V):-
104 T > 1,
105 T1 is T - 1,
106 repeat_(V, T1, V).
107
108repeat(N,Times,V):-
109 must_be(positive_integer, Times),
110 repeat_(N,Times,V).
120accumulate(times, L, V):-
121 must_be(list(number),L),
122 scanl(times, L, 1, [_|V]).
123accumulate(plus, L, V):-
124 must_be(list(number),L),
125 scanl(plus, L, 0, [_|V]).
134batched_([], Sz, _, L, L):- Sz > 0.
135batched_(_, 0, _, L, L).
136batched_([H|T], 0, Size, _, L):-
137 batched_([H|T], Size, Size, [], L).
138batched_([H|T], N, Size, L, LO):-
139 N > 0,
140 append(L,[H],LT),
141 N1 is N - 1,
142 batched_(T,N1,Size,LT,LO).
143
144batched_check_args(L, V, Batch):-
145 must_be(list,L),
146 must_be(positive_integer, V),
147 batched_(L, V, V, [], Batch).
148
149batched(L, V, Batch):-
150 batched_check_args(L, V, Batch).
158slice(L,End,Sublist):-
159 slice_check_args(L, 0, End, Sublist).
167slice_(L, Start, End, Sublist) :-
168 findall(V, (between(Start, End, I), nth1(I, L, V)), Sublist).
169
170slice_check_args(L, Start, End, Sublist):-
171 must_be(list,L),
172 must_be(nonneg, Start),
173 must_be(nonneg, End),
174 slice_(L, Start, End, Sublist).
175
176slice(L,Start,End,Sublist):-
177 slice_check_args(L, Start, End, Sublist).
185pairwise_([A,B|_],[A,B]).
186pairwise_([_,B|T],L):-
187 pairwise_([B|T],L).
188
189pairwise_check_args(L, Sublist):-
190 must_be(list,L),
191 pairwise_(L, Sublist).
192
193pairwise(L,LO):-
194 pairwise_check_args(L, LO).
195
196
207cartesian_product([],L,L).
208cartesian_product([List|T],LT,LO):-
209 member(El,List),
210 append(LT,[El],LT1),
211 cartesian_product(T,LT1,LO).
212
213cartesian_product(L,Res):-
214 cartesian_product(L,[],Res).
227permutations_(ToConsider,Len,Current,P):-
228 length(Current,N),
229 ( N >= Len ->
230 P = Current ;
231 select(El,ToConsider,Rem),
232 233 append(Current,[El],C1),
234 permutations_(Rem,Len,C1,P)
235 ).
236permutations(List,P):-
237 length(List,N),
238 permutations(List,N,P).
239permutations(List,Len,P):-
240 must_be(positive_integer, Len),
241 select(El,List,ToConsider),
242 permutations_(ToConsider,Len,[El],P).
252combinations(List,Len,P):-
253 must_be(positive_integer, Len),
254 combinations_(List,Len,P).
255combinations_([H|T],Len,P):-
256 permutations_(T,Len,[H],P).
257combinations_([_|T],Len,P):-
258 combinations(T,Len,P).
269combinations_with_replacement(List,Len,P):-
270 must_be(positive_integer, Len),
271 combinations_with_replacement_(List,Len,P).
272combinations_with_replacement_([H|T],Len,P):-
273 permutations_([H|T],Len,[H],P).
274combinations_with_replacement_([_|T],Len,P):-
275 combinations_with_replacement(T,Len,P).
276
279
293chunked_(L, Size, L):-
294 length(L,N),
295 Size > N,
296 N > 0.
297chunked_(List, Size, Chunk):-
298 length(Chunk,Size),
299 append(Chunk, _, List).
300chunked_(List, Size, Chunk):-
301 length(Chunk_,Size),
302 append(Chunk_, Rem, List),
303 chunked_(Rem, Size, Chunk).
304
305chunked(List, Size, Chunk):-
306 must_be(nonneg, Size),
307 chunked_(List, Size, Chunk).
322divide(List, Parts, Divided):-
323 must_be(nonneg, Parts),
324 length(List,N),
325 Parts > 0,
326 Parts =< N,
327 Chunk is ceil(N/Parts),
328 chunked_(List, Chunk, Divided).
344split_at_index(List,Index,L0,L1):-
345 must_be(nonneg, Index),
346 length(L0, Index),
347 append(L0,L1,List).
363window_(List,Size,_Step,Window):-
364 length(List, N),
365 N >= Size,
366 length(Window,Size),
367 append(Window,_,List).
368window_(List,Size,Step,Window):-
369 length(ToRemove,Step),
370 append(ToRemove,LRem,List),
371 window_(LRem,Size,Step,Window).
372window(List, Size, Window):-
373 window(List, Size, 1, Window).
374window(List, Size, Step, Window):-
375 must_be(nonneg, Size),
376 window_(List,Size,Step,Window).
387triplewise_([A,B,C|_],[A,B,C]).
388triplewise_([_,B|T],L):-
389 triplewise_([B|T],L).
390triplewise_check_args(L, Sublist):-
391 must_be(list,L),
392 triplewise_(L, Sublist).
393triplewise(L,LO):-
394 triplewise_check_args(L, LO).
407intersperse([],_,_,L,L):- !.
408intersperse(List, El, Step, LT, Res):-
409 length(L,Step),
410 length(List,N),
411 ( N >= Step ->
412 append(L,Rem,List),
413 append(L,[El],LTT),
414 append(LT,LTT,LO) ;
415 append(LT,List,LO),
416 Rem = []
417 ),
418 intersperse(Rem,El,Step,LO,Res).
419
420intersperse(List, El, Res):-
421 intersperse(List, El, 1, [], Res).
422intersperse(List, El, Step, Res):-
423 intersperse(List, El, Step, [], Res).
439padded_right(List,Element,TargetLen,Result):-
440 padded(List,Element,TargetLen,right,Result).
441padded_left(List,Element,TargetLen,Result):-
442 padded(List,Element,TargetLen,left,Result).
443padded(List,Element,TargetLen,Type,Result):-
444 must_be(integer, TargetLen),
445 length(List,N),
446 ( TargetLen =< N ->
447 Result = List ;
448 R is TargetLen - N,
449 findall(I, repeat(Element,R,I), LPad),
450 (Type = right ->
451 append(List,LPad,Result);
452 append(LPad,List,Result)
453 )
454 ).
465repeat_each_([],_,L,L).
466repeat_each_([H|T], Times, LT, Res):-
467 findnsols(Times, I, repeat(H,Times,I), LR), !,
468 append(LT, LR, LT1),
469 repeat_each_(T, Times, LT1, Res).
470repeat_each(L, Times, Res):-
471 must_be(positive_integer, Times),
472 repeat_each_(L, Times, [], Res).
479distribute(L, N, S):-
480 findall(V,batched(L, N, V),S).
487repeat_last([H],H).
488repeat_last([H|_],H).
489repeat_last([_|T],H):-
490 repeat_last(T,H)