00001: /*  Part of SWI-Prolog
00002:
00003:     Author:        Jan Wielemaker
00004:     E-mail:        J.Wielemaker@vu.nl
00005:     WWW:           http://www.swi-prolog.org
00006:     Copyright (C): 1985-2012, University of Amsterdam
00007:                               VU University Amsterdam
00008:
00009:     This program is free software; you can redistribute it and/or
00010:     modify it under the terms of the GNU General Public License
00011:     as published by the Free Software Foundation; either version 2
00012:     of the License, or (at your option) any later version.
00013:
00014:     This program is distributed in the hope that it will be useful,
00015:     but WITHOUT ANY WARRANTY; without even the implied warranty of
00016:     MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
00017:     GNU General Public License for more details.
00018:
00019:     You should have received a copy of the GNU General Public
00020:     License along with this library; if not, write to the Free Software
00021:     Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
00022:
00023:     As a special exception, if you link this library with other files,
00024:     compiled with a Free Software compiler, to produce an executable, this
00025:     library does not by itself cause the resulting executable to be covered
00026:     by the GNU General Public License. This exception does not however
00027:     invalidate any other reasons why the executable file might be covered by
00028:     the GNU General Public License.
00029: */
00030:
00031: :- module(apply,
00032:           [ include/3,                  % :Pred, +List, -Ok
00033:             exclude/3,                  % :Pred. +List, -NotOk
00034:             partition/4,                % :Pred, +List, -Included, -Excluded
00035:             partition/5,                % :Pred, +List, ?Less, ?Equal, ?Greater
00036:             maplist/2,                  % :Pred, +List
00037:             maplist/3,                  % :Pred, ?List, ?List
00038:             maplist/4,                  % :Pred, ?List, ?List, ?List
00039:             maplist/5,                  % :Pred, ?List, ?List, ?List, ?List
00040:             foldl/4,                    % :Pred, +List, ?V0, ?V
00041:             foldl/5,                    % :Pred, +List1, +List2, ?V0, ?V
00042:             foldl/6,                    % :Pred, +List1, +List2, +List3, ?V0, ?V
00043:             foldl/7,                    % :Pred, +List1, +List2, +List3, +List4,
00044:                                         % ?V0, ?V
00045:             scanl/4,                    % :Pred, +List, ?V0, ?Vs
00046:             scanl/5,                    % :Pred, +List1, +List2, ?V0, ?Vs
00047:             scanl/6,                    % :Pred, +List1, +List2, +List3, ?V0, ?Vs
00048:             scanl/7                     % :Pred, +List1, +List2, +List3, +List4,
00049:                                         % ?V0, ?Vs
00050:           ]).
00051: :- use_module(library(error)).
00052:
00053: /** <module> Apply predicates on a list
00054:
00055: This module defines meta-predicates  that  apply   a  predicate  on  all
00056: members of a list.
00057:
00058: @see    apply_macros.pl provides compile-time expansion for part of this
00059:         library.
00060: @see    http://www.cs.otago.ac.nz/staffpriv/ok/pllib.htm
00061: @tbd    Add include/4, include/5, exclude/4, exclude/5
00062: */
00063:
00064: :- meta_predicate
00065:         include(1, +, -),
00066:         exclude(1, +, -),
00067:         partition(1, +, -, -),
00068:         partition(2, +, -, -, -),
00069:         maplist(1, ?),
00070:         maplist(2, ?, ?),
00071:         maplist(3, ?, ?, ?),
00072:         maplist(4, ?, ?, ?, ?),
00073:         foldl(3, +, +, -),
00074:         foldl(4, +, +, +, -),
00075:         foldl(5, +, +, +, +, -),
00076:         foldl(6, +, +, +, +, +, -),
00077:         scanl(3, +, +, -),
00078:         scanl(4, +, +, +, -),
00079:         scanl(5, +, +, +, +, -),
00080:         scanl(6, +, +, +, +, +, -).
00081:
00082:
00083: %%      include(:Goal, +List1, ?List2) is det.
00084: %
00085: %       Filter elements for which Goal succeeds.  True if List2 contains
00086: %       those elements Xi of List1 for which call(Goal, Xi) succeeds.
00087: %
00088: %       @see    Older versions of SWI-Prolog had sublist/3 with the same
00089: %               arguments and semantics.
00090:
00091: include(Goal, List, Included) :-
00092:         include_(List, Goal, Included).
00093:
00094: include_([], _, []).
00095: include_([X1|Xs1], P, Included) :-
00096:         (   call(P, X1)
00097:         ->  Included = [X1|Included1]
00098:         ;   Included = Included1
00099:         ),
00100:         include_(Xs1, P, Included1).
00101:
00102:
00103: %%      exclude(:Goal, +List1, ?List2) is det.
00104: %
00105: %       Filter elements for which Goal fails.  True if List2 contains
00106: %       those elements Xi of List1 for which call(Goal, Xi) fails.
00107:
00108: exclude(Goal, List, Included) :-
00109:         exclude_(List, Goal, Included).
00110:
00111: exclude_([], _, []).
00112: exclude_([X1|Xs1], P, Included) :-
00113:         (   call(P, X1)
00114:         ->  Included = Included1
00115:         ;   Included = [X1|Included1]
00116:         ),
00117:         exclude_(Xs1, P, Included1).
00118:
00119:
00120: %%      partition(:Pred, +List, ?Included, ?Excluded) is det.
00121: %
00122: %       Filter elements of List according  to   Pred.  True  if Included
00123: %       contains all elements  for  which   call(Pred,  X)  succeeds and
00124: %       Excluded contains the remaining elements.
00125:
00126: partition(Pred, List, Included, Excluded) :-
00127:         partition_(List, Pred, Included, Excluded).
00128:
00129: partition_([], _, [], []).
00130: partition_([H|T], Pred, Incl, Excl) :-
00131:         (   call(Pred, H)
00132:         ->  Incl = [H|I],
00133:             partition_(T, Pred, I, Excl)
00134:         ;   Excl = [H|E],
00135:             partition_(T, Pred, Incl, E)
00136:         ).
00137:
00138:
00139: %%      partition(:Pred, +List, ?Less, ?Equal, ?Greater) is semidet.
00140: %
00141: %       Filter List according to Pred in three sets. For each element Xi
00142: %       of List, its destination is determined by call(Pred, Xi, Place),
00143: %       where Place must be unified to  one   of  =|<|=, =|=|= or =|>|=.
00144: %       Pred must be deterministic.
00145:
00146: partition(Pred, List, Less, Equal, Greater) :-
00147:         partition_(List, Pred, Less, Equal, Greater).
00148:
00149: partition_([], _, [], [], []).
00150: partition_([H|T], Pred, L, E, G) :-
00151:         call(Pred, H, Diff),
00152:         partition_(Diff, H, Pred, T, L, E, G).
00153:
00154: partition_(<, H, Pred, T, [H|L], E, G) :- !,
00155:         partition_(T, Pred, L, E, G).
00156: partition_(=, H, Pred, T, L, [H|E], G) :- !,
00157:         partition_(T, Pred, L, E, G).
00158: partition_(>, H, Pred, T, L, E, [H|G]) :- !,
00159:         partition_(T, Pred, L, E, G).
00160: partition_(Diff, _, _, _, _, _, _) :-
00161:         must_be(oneof([<.=,>]), Diff).
00162:
00163:
00164:                  /*******************************
00165:                  *          MAPLIST/2...        *
00166:                  *******************************/
00167:
00168: %%      maplist(:Goal, ?List)
00169: %
00170: %       True if Goal can successfully  be   applied  on  all elements of
00171: %       List. Arguments are reordered to gain  performance as well as to
00172: %       make the predicate deterministic under normal circumstances.
00173:
00174: maplist(Goal, List) :-
00175:         maplist_(List, Goal).
00176:
00177: maplist_([], _).
00178: maplist_([Elem|Tail], Goal) :-
00179:         call(Goal, Elem),
00180:         maplist_(Tail, Goal).
00181:
00182: %%      maplist(:Goal, ?List1, ?List2)
00183: %
00184: %       As maplist/2, operating on pairs of elements from two lists.
00185:
00186: maplist(Goal, List1, List2) :-
00187:         maplist_(List1, List2, Goal).
00188:
00189: maplist_([], [], _).
00190: maplist_([Elem1|Tail1], [Elem2|Tail2], Goal) :-
00191:         call(Goal, Elem1, Elem2),
00192:         maplist_(Tail1, Tail2, Goal).
00193:
00194: %%      maplist(:Goal, ?List1, ?List2, ?List3)
00195: %
00196: %       As maplist/2, operating on triples of elements from three lists.
00197:
00198: maplist(Goal, List1, List2, List3) :-
00199:         maplist_(List1, List2, List3, Goal).
00200:
00201: maplist_([], [], [], _).
00202: maplist_([Elem1|Tail1], [Elem2|Tail2], [Elem3|Tail3], Goal) :-
00203:         call(Goal, Elem1, Elem2, Elem3),
00204:         maplist_(Tail1, Tail2, Tail3, Goal).
00205:
00206:
00207: %%      maplist(:Goal, ?List1, ?List2, ?List3, ?List4)
00208: %
00209: %       As maplist/2, operating on  quadruples   of  elements  from four
00210: %       lists.
00211:
00212: maplist(Goal, List1, List2, List3, List4) :-
00213:         maplist_(List1, List2, List3, List4, Goal).
00214:
00215: maplist_([], [], [], [], _).
00216: maplist_([Elem1|Tail1], [Elem2|Tail2], [Elem3|Tail3], [Elem4|Tail4], Goal) :-
00217:         call(Goal, Elem1, Elem2, Elem3, Elem4),
00218:         maplist_(Tail1, Tail2, Tail3, Tail4, Goal).
00219:
00220:
00221:                  /*******************************
00222:                  *            FOLDL             *
00223:                  *******************************/
00224:
00225: %%      foldl(:Goal, +List, +V0, -V).
00226: %%      foldl(:Goal, +List1, +List2, +V0, -V).
00227: %%      foldl(:Goal, +List1, +List2, +List3, +V0, -V).
00228: %%      foldl(:Goal, +List1, +List2, +List3, +List4, +V0, -V).
00229: %
00230: %       Fold a list, using arguments of the   list as left argument. The
00231: %       foldl family of predicates is defined by:
00232: %
00233: %         ==
00234: %         foldl(P, [X11,...,X1n], ..., [Xm1,...,Xmn], V0, Vn) :-
00235: %               P(X11, ..., Xm1, V0, V1),
00236: %               ...
00237: %               P(X1n, ..., Xmn, V', Vn).
00238: %         ==
00239:
00240: foldl(Goal, List, V0, V) :-
00241:         foldl_(List, Goal, V0, V).
00242:
00243: foldl_([], _, V, V).
00244: foldl_([H|T], Goal, V0, V) :-
00245:         call(Goal, H, V0, V1),
00246:         foldl_(T, Goal, V1, V).
00247:
00248:
00249: foldl(Goal, List1, List2, V0, V) :-
00250:         foldl_(List1, List2, Goal, V0, V).
00251:
00252: foldl_([], [], _, V, V).
00253: foldl_([H1|T1], [H2|T2], Goal, V0, V) :-
00254:         call(Goal, H1, H2, V0, V1),
00255:         foldl_(T1, T2, Goal, V1, V).
00256:
00257:
00258: foldl(Goal, List1, List2, List3, V0, V) :-
00259:         foldl_(List1, List2, List3, Goal, V0, V).
00260:
00261: foldl_([], [], [], _, V, V).
00262: foldl_([H1|T1], [H2|T2], [H3|T3], Goal, V0, V) :-
00263:         call(Goal, H1, H2, H3, V0, V1),
00264:         foldl_(T1, T2, T3, Goal, V1, V).
00265:
00266:
00267: foldl(Goal, List1, List2, List3, List4, V0, V) :-
00268:         foldl_(List1, List2, List3, List4, Goal, V0, V).
00269:
00270: foldl_([], [], [], [], _, V, V).
00271: foldl_([H1|T1], [H2|T2], [H3|T3], [H4|T4], Goal, V0, V) :-
00272:         call(Goal, H1, H2, H3, H4, V0, V1),
00273:         foldl_(T1, T2, T3, T4, Goal, V1, V).
00274:
00275:
00276:                  /*******************************
00277:                  *             SCANL            *
00278:                  *******************************/
00279:
00280: %%      scanl(:Goal, +List, +V0, -Values).
00281: %%      scanl(:Goal, +List1, +List2, +V0, -Values).
00282: %%      scanl(:Goal, +List1, +List2, +List3, +V0, -Values).
00283: %%      scanl(:Goal, +List1, +List2, +List3, +List4, +V0, -Values).
00284: %
00285: %       Left scan of  list.  The  scanl   family  of  higher  order list
00286: %       operations is defined by:
00287: %
00288: %         ==
00289: %         scanl(P, [X11,...,X1n], ..., [Xm1,...,Xmn], V0,
00290: %               [V0,V1,...,Vn]) :-
00291: %               P(X11, ..., Xmn, V0, V1),
00292: %               ...
00293: %               P(X1n, ..., Xmn, V', Vn).
00294: %         ==
00295:
00296: scanl(Goal, List, V0, [V0|Values]) :-
00297:         scanl_(List, Goal, V0, Values).
00298:
00299: scanl_([], _, _, []).
00300: scanl_([H|T], Goal, V, [VH|VT]) :-
00301:         call(Goal, H, V, VH),
00302:         scanl_(T, Goal, VH, VT).
00303:
00304:
00305: scanl(Goal, List1, List2, V0, [V0|Values]) :-
00306:         scanl_(List1, List2, Goal, V0, Values).
00307:
00308: scanl_([], [], _, _, []).
00309: scanl_([H1|T1], [H2|T2], Goal, V, [VH|VT]) :-
00310:         call(Goal, H1, H2, V, VH),
00311:         scanl_(T1, T2, Goal, VH, VT).
00312:
00313:
00314: scanl(Goal, List1, List2, List3, V0, [V0|Values]) :-
00315:         scanl_(List1, List2, List3, Goal, V0, Values).
00316:
00317: scanl_([], [], [], _, _, []).
00318: scanl_([H1|T1], [H2|T2], [H3|T3], Goal, V, [VH|VT]) :-
00319:         call(Goal, H1, H2, H3, V, VH),
00320:         scanl_(T1, T2, T3, Goal, VH, VT).
00321:
00322:
00323: scanl(Goal, List1, List2, List3, List4, V0, [V0|Values]) :-
00324:         scanl_(List1, List2, List3, List4, Goal, V0, Values).
00325:
00326: scanl_([], [], [], [], _, _, []).
00327: scanl_([H1|T1], [H2|T2], [H3|T3], [H4|T4], Goal, V, [VH|VT]) :-
00328:         call(Goal, H1, H2, H3, H4, V, VH),
00329:         scanl_(T1, T2, T3, T4, Goal, VH, VT).