declare meta-predicate call arguments (Paulo Moura).

This commit is contained in:
Vitor Santos Costa 2010-04-22 20:45:57 +01:00
parent 49c783cc10
commit 3cb5e57833
6 changed files with 89 additions and 79 deletions

View File

@ -25,7 +25,7 @@
del_max_assoc/4 del_max_assoc/4
]). ]).
:- meta_predicate map_assoc(:, +, -), map_assoc(:, +). :- meta_predicate map_assoc(2, +, -), map_assoc(1, +).
:- use_module(library(rbtrees), [ :- use_module(library(rbtrees), [
rb_empty/1, rb_empty/1,

View File

@ -15,7 +15,11 @@
process/2 process/2
]). ]).
:- meta_predicate filter(+,+,:), file_filter(+,+,:), file_filter_with_init(+,+,:,+,:), process(+,:). :- meta_predicate
filter(+,+,2),
file_filter(+,+,2),
file_filter_with_init(+,+,2,+,:),
process(+,1).
:- use_module(library(lists), :- use_module(library(lists),
[member/2, [member/2,

View File

@ -33,28 +33,28 @@
:- meta_predicate :- meta_predicate
selectlist(:,+,-), selectlist(2,+,-),
checklist(:,+), checklist(1,+),
maplist(:,+), maplist(1,+),
maplist(:,+,-), maplist(2,+,-),
maplist(:,+,+,-), maplist(3,+,+,-),
maplist(:,+,+,+,-), maplist(4,+,+,+,-),
convlist(:,+,-), convlist(2,+,-),
mapargs(:,+,-), mapargs(2,+,-),
mapargs_args(:,+,-,+), mapargs_args(2,+,-,+),
sumargs(:,+,+,-), sumargs(3,+,+,-),
sumargs_args(:,+,+,-,+), sumargs_args(3,+,+,-,+),
mapnodes(:,+,-), mapnodes(2,+,-),
mapnodes_list(:,+,-), mapnodes_list(2,+,-),
checknodes(:,+), checknodes(1,+),
checknodes_list(:,+), checknodes_list(1,+),
sumlist(:,+,+,-), sumlist(3,+,+,-),
sumnodes(:,+,+,-), sumnodes(3,+,+,-),
sumnodes_body(:,+,+,-,+,+), sumnodes_body(3,+,+,-,+,+),
include(:,+,-), include(1,+,-),
exclude(:,+,-), exclude(1,+,-),
partition(:,+,-,-), partition(2,+,-,-),
partition(:,+,-,-,-). partition(2,+,-,-,-).
:- use_module(library(lists), [append/3]). :- use_module(library(lists), [append/3]).
@ -215,7 +215,7 @@ mapnodes(Pred, TermIn, TermOut) :-
TermOut =.. [Func|ArgsOut]. TermOut =.. [Func|ArgsOut].
mapnodes_list(_, [], []). mapnodes_list(_, [], []).
appnodes_list(Pred, [TermIn|ArgsIn], [TermOut|ArgsOut]) :- mapnodes_list(Pred, [TermIn|ArgsIn], [TermOut|ArgsOut]) :-
mapnodes(Pred, TermIn, TermOut), mapnodes(Pred, TermIn, TermOut),
mapnodes_list(Pred, ArgsIn, ArgsOut). mapnodes_list(Pred, ArgsIn, ArgsOut).

View File

@ -61,7 +61,9 @@ form colour(Left, Key, Value, Right), where _colour_ is one of =red= or
@author Vitor Santos Costa, Jan Wielemaker @author Vitor Santos Costa, Jan Wielemaker
*/ */
:- meta_predicate rb_map(+,:,-), rb_partial_map(+,+,:,-), rb_apply(+,+,:,-). :- meta_predicate rb_map(+,2,-),
rb_partial_map(+,+,2,-),
rb_apply(+,+,2,-).
/* /*
:- use_module(library(type_check)). :- use_module(library(type_check)).
@ -773,8 +775,7 @@ visit(black(L,K,V,R),L0,Lf) :-
visit(L,[K-V|L1],Lf), visit(L,[K-V|L1],Lf),
visit(R,L0,L1). visit(R,L0,L1).
:- meta_predicate rb_map(?,:,?). % this is not strictly required :- meta_predicate map(?,2,?,?). % this is required.
:- meta_predicate map(?,:,?,?). % this is required.
%% rb_map(+T, :Goal) is semidet. %% rb_map(+T, :Goal) is semidet.
% %
@ -794,8 +795,8 @@ map(black(L,K,V,R),Goal,black(NL,K,NV,NR),Nil) :-
map(L,Goal,NL,Nil), map(L,Goal,NL,Nil),
map(R,Goal,NR,Nil). map(R,Goal,NR,Nil).
:- meta_predicate rb_map(?,:). % this is not strictly required :- meta_predicate rb_map(?,1). % this is not strictly required
:- meta_predicate map(?,:). % this is required. :- meta_predicate map(?,1). % this is required.
%% rb_map(+T, :G, -TN) is semidet. %% rb_map(+T, :G, -TN) is semidet.
% %

View File

@ -19,4 +19,9 @@ test(read, [ setup(create_file(Tmp)),
read_file_to_terms(Tmp, Terms, []), read_file_to_terms(Tmp, Terms, []),
Terms =@= [hello(_)]. Terms =@= [hello(_)].
%:- end_tests(read). :- end_tests(read).
:- trace,run_tests.

View File

@ -527,12 +527,12 @@ source_module(Mod) :-
'$current_module'(Mod). '$current_module'(Mod).
% comma has its own problems. % comma has its own problems.
:- '$install_meta_predicate'((:,:), prolog). :- '$install_meta_predicate'((0,0), prolog).
:- meta_predicate :- meta_predicate
abolish(:), abolish(:),
abolish(:,+), abolish(:,+),
all(?,:,?), all(?,0,-),
assert(:), assert(:),
assert(:,+), assert(:,+),
assert_static(:), assert_static(:),
@ -542,80 +542,80 @@ source_module(Mod) :-
assertz(:), assertz(:),
assertz(:,+), assertz(:,+),
assertz_static(:), assertz_static(:),
bagof(?,:,?), bagof(?,0,-),
bb_get(:,-), bb_get(:,-),
bb_put(:,+), bb_put(:,+),
bb_delete(:,?), bb_delete(:,?),
bb_update(:,?,?), bb_update(:,?,?),
call(:), call(0),
call(:,?), call(1,?),
call(:,?,?), call(2,?,?),
call(:,?,?,?), call(3,?,?,?),
call_with_args(:), call_with_args(0),
call_with_args(:,?), call_with_args(1,?),
call_with_args(:,?,?), call_with_args(2,?,?),
call_with_args(:,?,?,?), call_with_args(3,?,?,?),
call_with_args(:,?,?,?,?), call_with_args(4,?,?,?,?),
call_with_args(:,?,?,?,?,?), call_with_args(5,?,?,?,?,?),
call_with_args(:,?,?,?,?,?,?), call_with_args(6,?,?,?,?,?,?),
call_with_args(:,?,?,?,?,?,?,?), call_with_args(7,?,?,?,?,?,?,?),
call_with_args(:,?,?,?,?,?,?,?,?), call_with_args(8,?,?,?,?,?,?,?,?),
call_with_args(:,?,?,?,?,?,?,?,?,?), call_with_args(9,?,?,?,?,?,?,?,?,?),
format(+,:), call_cleanup(0,0),
format(+,+,:), call_cleanup(0,?,0),
call_cleanup(:,:), call_residue(0,?),
call_cleanup(:,?,:), call_residue_vars(0,?),
setup_call_cleanup(:,:,:), catch(0,?,0),
setup_call_catcher_cleanup(:,:,?,:),
call_residue(:,?),
call_residue_vars(:,?),
catch(:,+,:),
clause(:,?), clause(:,?),
clause(:,?,?), clause(:,?,?),
compile(:), compile(:),
consult(:), consult(:),
current_predicate(:), current_predicate(:),
current_predicate(?,:), current_predicate(?,:),
depth_bound_call(:,+), depth_bound_call(0,+),
discontiguous(:), discontiguous(:),
ensure_loaded(:), ensure_loaded(:),
findall(?,:,?), findall(?,0,-),
findall(?,:,?,?), findall(?,0,-,?),
forall(:,:), forall(0,0),
freeze(?,:), format(+,:),
format(+,+,:),
freeze(?,0),
hide_predicate(:), hide_predicate(:),
if(:,:,:), if(0,0,0),
ignore(:), ignore(0),
incore(:), incore(0),
listing(:), listing(:),
multifile(:), multifile(:),
nospy(:), nospy(:),
not(:), not(0),
once(:), once(0),
phrase(:,?), phrase(2,?),
phrase(:,?,+), phrase(2,?,+),
predicate_property(:,?), predicate_property(:,?),
predicate_statistics(:,-,-,-), predicate_statistics(:,-,-,-),
on_exception(+,:,:), on_exception(+,0,0),
reconsult(:), reconsult(:),
retract(:), retract(:),
retract(:,?), retract(:,?),
retractall(:), retractall(:),
reconsult(:), reconsult(:),
setof(?,:,?), setof(?,0,-),
setup_call_cleanup(0,0,0),
setup_call_catcher_cleanup(0,0,?,0),
spy(:), spy(:),
unknown(+,:), unknown(+,:),
use_module(:), use_module(:),
use_module(:,?), use_module(:,?),
use_module(?,:,?), use_module(?,:,?),
when(?,:), when(+,0),
with_mutex(+,:), with_mutex(+,0),
with_output_to(?,:), with_output_to(?,0),
(: -> :), (0 -> 0),
(: *-> :), (0 *-> 0),
(: ; :), (0 ; 0),
^(+,:), ^(+,0),
\+ : . \+ 0 .
% %
% get rid of a module and of all predicates included in the module. % get rid of a module and of all predicates included in the module.