35
36:- module(apply,
37 [ include/3, 38 exclude/3, 39 partition/4, 40 partition/5, 41 maplist/2, 42 maplist/3, 43 maplist/4, 44 maplist/5, 45 convlist/3, 46 foldl/4, 47 foldl/5, 48 foldl/6, 49 foldl/7, 50 51 scanl/4, 52 scanl/5, 53 scanl/6, 54 scanl/7 55 56 ]). 57:- use_module(library(error)).
70:- meta_predicate
71 include(1, +, -),
72 exclude(1, +, -),
73 partition(1, +, -, -),
74 partition(2, +, -, -, -),
75 maplist(1, ?),
76 maplist(2, ?, ?),
77 maplist(3, ?, ?, ?),
78 maplist(4, ?, ?, ?, ?),
79 convlist(2, +, -),
80 foldl(3, +, +, -),
81 foldl(4, +, +, +, -),
82 foldl(5, +, +, +, +, -),
83 foldl(6, +, +, +, +, +, -),
84 scanl(3, +, +, -),
85 scanl(4, +, +, +, -),
86 scanl(5, +, +, +, +, -),
87 scanl(6, +, +, +, +, +, -).
98include(Goal, List, Included) :-
99 include_(List, Goal, Included).
100
101include_([], _, []).
102include_([X1|Xs1], P, Included) :-
103 ( call(P, X1)
104 -> Included = [X1|Included1]
105 ; Included = Included1
106 ),
107 include_(Xs1, P, Included1).
115exclude(Goal, List, Included) :-
116 exclude_(List, Goal, Included).
117
118exclude_([], _, []).
119exclude_([X1|Xs1], P, Included) :-
120 ( call(P, X1)
121 -> Included = Included1
122 ; Included = [X1|Included1]
123 ),
124 exclude_(Xs1, P, Included1).
133partition(Pred, List, Included, Excluded) :-
134 partition_(List, Pred, Included, Excluded).
135
136partition_([], _, [], []).
137partition_([H|T], Pred, Incl, Excl) :-
138 ( call(Pred, H)
139 -> Incl = [H|I],
140 partition_(T, Pred, I, Excl)
141 ; Excl = [H|E],
142 partition_(T, Pred, Incl, E)
143 ).
153partition(Pred, List, Less, Equal, Greater) :-
154 partition_(List, Pred, Less, Equal, Greater).
155
156partition_([], _, [], [], []).
157partition_([H|T], Pred, L, E, G) :-
158 call(Pred, H, Diff),
159 partition_(Diff, H, Pred, T, L, E, G).
160
161partition_(<, H, Pred, T, L, E, G) :-
162 !,
163 L = [H|Rest],
164 partition_(T, Pred, Rest, E, G).
165partition_(=, H, Pred, T, L, E, G) :-
166 !,
167 E = [H|Rest],
168 partition_(T, Pred, L, Rest, G).
169partition_(>, H, Pred, T, L, E, G) :-
170 !,
171 G = [H|Rest],
172 partition_(T, Pred, L, E, Rest).
173partition_(Diff, _, _, _, _, _, _) :-
174 must_be(oneof([<,=,>]), Diff).
175
176
177
187maplist(Goal, List) :-
188 maplist_(List, Goal).
189
190maplist_([], _).
191maplist_([Elem|Tail], Goal) :-
192 call(Goal, Elem),
193 maplist_(Tail, Goal).
199maplist(Goal, List1, List2) :-
200 maplist_(List1, List2, Goal).
201
202maplist_([], [], _).
203maplist_([Elem1|Tail1], [Elem2|Tail2], Goal) :-
204 call(Goal, Elem1, Elem2),
205 maplist_(Tail1, Tail2, Goal).
211maplist(Goal, List1, List2, List3) :-
212 maplist_(List1, List2, List3, Goal).
213
214maplist_([], [], [], _).
215maplist_([Elem1|Tail1], [Elem2|Tail2], [Elem3|Tail3], Goal) :-
216 call(Goal, Elem1, Elem2, Elem3),
217 maplist_(Tail1, Tail2, Tail3, Goal).
225maplist(Goal, List1, List2, List3, List4) :-
226 maplist_(List1, List2, List3, List4, Goal).
227
228maplist_([], [], [], [], _).
229maplist_([Elem1|Tail1], [Elem2|Tail2], [Elem3|Tail3], [Elem4|Tail4], Goal) :-
230 call(Goal, Elem1, Elem2, Elem3, Elem4),
231 maplist_(Tail1, Tail2, Tail3, Tail4, Goal).
248convlist(Goal, ListIn, ListOut) :-
249 convlist_(ListIn, ListOut, Goal).
250
251convlist_([], [], _).
252convlist_([H0|T0], ListOut, Goal) :-
253 ( call(Goal, H0, H)
254 -> ListOut = [H|T],
255 convlist_(T0, T, Goal)
256 ; convlist_(T0, ListOut, Goal)
257 ).
258
259
260
279foldl(Goal, List, V0, V) :-
280 foldl_(List, Goal, V0, V).
281
282foldl_([], _, V, V).
283foldl_([H|T], Goal, V0, V) :-
284 call(Goal, H, V0, V1),
285 foldl_(T, Goal, V1, V).
286
287
288foldl(Goal, List1, List2, V0, V) :-
289 foldl_(List1, List2, Goal, V0, V).
290
291foldl_([], [], _, V, V).
292foldl_([H1|T1], [H2|T2], Goal, V0, V) :-
293 call(Goal, H1, H2, V0, V1),
294 foldl_(T1, T2, Goal, V1, V).
295
296
297foldl(Goal, List1, List2, List3, V0, V) :-
298 foldl_(List1, List2, List3, Goal, V0, V).
299
300foldl_([], [], [], _, V, V).
301foldl_([H1|T1], [H2|T2], [H3|T3], Goal, V0, V) :-
302 call(Goal, H1, H2, H3, V0, V1),
303 foldl_(T1, T2, T3, Goal, V1, V).
304
305
306foldl(Goal, List1, List2, List3, List4, V0, V) :-
307 foldl_(List1, List2, List3, List4, Goal, V0, V).
308
309foldl_([], [], [], [], _, V, V).
310foldl_([H1|T1], [H2|T2], [H3|T3], [H4|T4], Goal, V0, V) :-
311 call(Goal, H1, H2, H3, H4, V0, V1),
312 foldl_(T1, T2, T3, T4, Goal, V1, V).
313
314
315
335scanl(Goal, List, V0, [V0|Values]) :-
336 scanl_(List, Goal, V0, Values).
337
338scanl_([], _, _, []).
339scanl_([H|T], Goal, V, [VH|VT]) :-
340 call(Goal, H, V, VH),
341 scanl_(T, Goal, VH, VT).
342
343
344scanl(Goal, List1, List2, V0, [V0|Values]) :-
345 scanl_(List1, List2, Goal, V0, Values).
346
347scanl_([], [], _, _, []).
348scanl_([H1|T1], [H2|T2], Goal, V, [VH|VT]) :-
349 call(Goal, H1, H2, V, VH),
350 scanl_(T1, T2, Goal, VH, VT).
351
352
353scanl(Goal, List1, List2, List3, V0, [V0|Values]) :-
354 scanl_(List1, List2, List3, Goal, V0, Values).
355
356scanl_([], [], [], _, _, []).
357scanl_([H1|T1], [H2|T2], [H3|T3], Goal, V, [VH|VT]) :-
358 call(Goal, H1, H2, H3, V, VH),
359 scanl_(T1, T2, T3, Goal, VH, VT).
360
361
362scanl(Goal, List1, List2, List3, List4, V0, [V0|Values]) :-
363 scanl_(List1, List2, List3, List4, Goal, V0, Values).
364
365scanl_([], [], [], [], _, _, []).
366scanl_([H1|T1], [H2|T2], [H3|T3], [H4|T4], Goal, V, [VH|VT]) :-
367 call(Goal, H1, H2, H3, H4, V, VH),
368 scanl_(T1, T2, T3, T4, Goal, VH, VT).
369
370
371 374
375:- multifile
376 sandbox:safe_meta_predicate/1. 377
378safe_api(Name/Arity, sandbox:safe_meta_predicate(apply:Name/Arity)).
379
380term_expansion(safe_api, Clauses) :-
381 module_property(apply, exports(API)),
382 maplist(safe_api, API, Clauses).
383
384safe_api
Apply predicates on a list
This module defines meta-predicates that apply a predicate on all members of a list.
apply_macros.pl
provides compile-time expansion for part of this library.