maplist and friends should be exported from apply, not builtins (obs from Jan Wielemaker).
This commit is contained in:
parent
dcf0c87e8a
commit
742979eb9c
@ -25,6 +25,16 @@
|
|||||||
nth1/3,
|
nth1/3,
|
||||||
nth0/3]).
|
nth0/3]).
|
||||||
|
|
||||||
|
:- use_module(library(apply),[maplist/2,
|
||||||
|
maplist/3,
|
||||||
|
maplist/4,
|
||||||
|
maplist/5,
|
||||||
|
include/3,
|
||||||
|
exclude/3,
|
||||||
|
partition/4,
|
||||||
|
partition/5
|
||||||
|
]).
|
||||||
|
|
||||||
:- use_module(library(system),
|
:- use_module(library(system),
|
||||||
[datime/1,
|
[datime/1,
|
||||||
mktime/2,
|
mktime/2,
|
||||||
@ -36,12 +46,6 @@
|
|||||||
:- use_module(library(apply_macros),
|
:- use_module(library(apply_macros),
|
||||||
[]).
|
[]).
|
||||||
|
|
||||||
:- use_module(library(maplist),
|
|
||||||
[maplist/2,
|
|
||||||
maplist/3,
|
|
||||||
maplist/4,
|
|
||||||
maplist/5]).
|
|
||||||
|
|
||||||
:- use_module(library(terms),
|
:- use_module(library(terms),
|
||||||
[subsumes/2,
|
[subsumes/2,
|
||||||
term_hash/2,
|
term_hash/2,
|
||||||
@ -97,6 +101,14 @@ swi_predicate_table(_,cyclic_term(X),terms,cyclic_term(X)).
|
|||||||
swi_predicate_table(_,acyclic_term(X),terms,acyclic_term(X)).
|
swi_predicate_table(_,acyclic_term(X),terms,acyclic_term(X)).
|
||||||
swi_predicate_table(_,genarg(X,Y,Z),arg,genarg(X,Y,Z)).
|
swi_predicate_table(_,genarg(X,Y,Z),arg,genarg(X,Y,Z)).
|
||||||
swi_predicate_table(_,tmp_file(X,Y),system,tmp_file(X,Y)).
|
swi_predicate_table(_,tmp_file(X,Y),system,tmp_file(X,Y)).
|
||||||
|
swi_predicate_table(_,maplist(X,Y),apply,maplist(X,Y)).
|
||||||
|
swi_predicate_table(_,maplist(X,Y,Z),apply,maplist(X,Y,Z)).
|
||||||
|
swi_predicate_table(_,maplist(X,Y,Z,A),apply,maplist(X,Y,Z,A)).
|
||||||
|
swi_predicate_table(_,maplist(X,Y,Z,A,B),apply,maplist(X,Y,Z,A,B)).
|
||||||
|
swi_predicate_table(_,include(X,Y,Z),apply,include(X,Y,Z)).
|
||||||
|
swi_predicate_table(_,exclude(X,Y,Z),apply,exclude(X,Y,Z)).
|
||||||
|
swi_predicate_table(_,partition(X,Y,Z,A),apply,partition(X,Y,Z,A)).
|
||||||
|
swi_predicate_table(_,partition(X,Y,Z,A,B),apply,partition(X,Y,Z,A,B)).
|
||||||
|
|
||||||
swi_mchk(X,Y) :- lists:memberchk(X,Y).
|
swi_mchk(X,Y) :- lists:memberchk(X,Y).
|
||||||
|
|
||||||
@ -330,61 +342,6 @@ lists:intersection([X|T], L, Intersect) :-
|
|||||||
lists:intersection([_|T], L, R) :-
|
lists:intersection([_|T], L, R) :-
|
||||||
lists:intersection(T, L, R).
|
lists:intersection(T, L, R).
|
||||||
|
|
||||||
|
|
||||||
% copied from SWI's boot/apply library
|
|
||||||
:- module_transparent
|
|
||||||
mpl/2,
|
|
||||||
mpl/3,
|
|
||||||
mpl/4,
|
|
||||||
mpl/5.
|
|
||||||
|
|
||||||
mpl(Goal, List) :-
|
|
||||||
maplist:maplist(Goal, List).
|
|
||||||
|
|
||||||
mpl(Goal, List1, List2) :-
|
|
||||||
maplist:maplist(Goal, List1, List2).
|
|
||||||
|
|
||||||
mpl(Goal, List1, List2, List3) :-
|
|
||||||
maplist:maplist(Goal, List1, List2, List3).
|
|
||||||
|
|
||||||
mpl(Goal, List1, List2, List3, List4) :-
|
|
||||||
maplist:maplist(Goal, List1, List2, List3, List4).
|
|
||||||
|
|
||||||
:- meta_predicate prolog:maplist(:,+), prolog:maplist(:,+,+), prolog:maplist(:,+,+,+), prolog:maplist(:,+,+,+).
|
|
||||||
|
|
||||||
% maplist(:Goal, +List)
|
|
||||||
%
|
|
||||||
% True if Goal can succesfully be applied on all elements of List.
|
|
||||||
% Arguments are reordered to gain performance as well as to make
|
|
||||||
% the predicate deterministic under normal circumstances.
|
|
||||||
|
|
||||||
prolog:maplist(Goal, List) :-
|
|
||||||
mpl(Goal, List).
|
|
||||||
|
|
||||||
% maplist(:Goal, ?List1, ?List2)
|
|
||||||
%
|
|
||||||
% True if Goal can succesfully be applied to all succesive pairs
|
|
||||||
% of elements of List1 and List2.
|
|
||||||
|
|
||||||
prolog:maplist(Goal, List1, List2) :-
|
|
||||||
mpl(Goal, List1, List2).
|
|
||||||
|
|
||||||
% maplist(:Goal, ?List1, ?List2, ?List3)
|
|
||||||
%
|
|
||||||
% True if Goal can succesfully be applied to all succesive triples
|
|
||||||
% of elements of List1..List3.
|
|
||||||
|
|
||||||
prolog:maplist(Goal, List1, List2, List3) :-
|
|
||||||
mpl(Goal, List1, List2, List3).
|
|
||||||
|
|
||||||
% maplist(:Goal, ?List1, ?List2, ?List3, List4)
|
|
||||||
%
|
|
||||||
% True if Goal can succesfully be applied to all succesive
|
|
||||||
% quadruples of elements of List1..List4
|
|
||||||
|
|
||||||
prolog:maplist(Goal, List1, List2, List3, List4) :-
|
|
||||||
mpl(Goal, List1, List2, List3, List4).
|
|
||||||
|
|
||||||
prolog:compile_aux_clauses([]).
|
prolog:compile_aux_clauses([]).
|
||||||
prolog:compile_aux_clauses([(:- G)|Cls]) :-
|
prolog:compile_aux_clauses([(:- G)|Cls]) :-
|
||||||
prolog_load_context(module, M),
|
prolog_load_context(module, M),
|
||||||
|
Reference in New Issue
Block a user