From 3cb5e57833df13e7b2bf265b0be2af46f176d8b3 Mon Sep 17 00:00:00 2001
From: Vitor Santos Costa <vsc@dcc.fc.up.pt>
Date: Thu, 22 Apr 2010 20:45:57 +0100
Subject: [PATCH] declare meta-predicate call arguments (Paulo Moura).

---
 library/assoc.yap                |  2 +-
 library/lineutils.yap            |  6 +-
 library/maplist.yap              | 46 +++++++--------
 library/rbtrees.yap              | 11 ++--
 packages/plunit/examples/read.pl |  7 ++-
 pl/modules.yap                   | 96 ++++++++++++++++----------------
 6 files changed, 89 insertions(+), 79 deletions(-)

diff --git a/library/assoc.yap b/library/assoc.yap
index e01e4a266..2c0d6a193 100644
--- a/library/assoc.yap
+++ b/library/assoc.yap
@@ -25,7 +25,7 @@
 	del_max_assoc/4
     ]).
 
-:- meta_predicate map_assoc(:, +, -), map_assoc(:, +).
+:- meta_predicate map_assoc(2, +, -), map_assoc(1, +).
 
 :- use_module(library(rbtrees), [
 	rb_empty/1,
diff --git a/library/lineutils.yap b/library/lineutils.yap
index b5f8790d1..c6f56d7f0 100644
--- a/library/lineutils.yap
+++ b/library/lineutils.yap
@@ -15,7 +15,11 @@
 	   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),
 	      [member/2,
diff --git a/library/maplist.yap b/library/maplist.yap
index 97ff21cd1..a70f3e4c0 100644
--- a/library/maplist.yap
+++ b/library/maplist.yap
@@ -33,28 +33,28 @@
 
 
 :- meta_predicate
-	selectlist(:,+,-),
-	checklist(:,+),
-	maplist(:,+),
-	maplist(:,+,-),
-	maplist(:,+,+,-),
-	maplist(:,+,+,+,-),
-	convlist(:,+,-),
-	mapargs(:,+,-),
-	mapargs_args(:,+,-,+),
-	sumargs(:,+,+,-),
-	sumargs_args(:,+,+,-,+),
-	mapnodes(:,+,-),
-	mapnodes_list(:,+,-),
-	checknodes(:,+),
-	checknodes_list(:,+),
-	sumlist(:,+,+,-),
-	sumnodes(:,+,+,-),
-	sumnodes_body(:,+,+,-,+,+),
-	include(:,+,-),
-	exclude(:,+,-),
-	partition(:,+,-,-),
-	partition(:,+,-,-,-).
+	selectlist(2,+,-),
+	checklist(1,+),
+	maplist(1,+),
+	maplist(2,+,-),
+	maplist(3,+,+,-),
+	maplist(4,+,+,+,-),
+	convlist(2,+,-),
+	mapargs(2,+,-),
+	mapargs_args(2,+,-,+),
+	sumargs(3,+,+,-),
+	sumargs_args(3,+,+,-,+),
+	mapnodes(2,+,-),
+	mapnodes_list(2,+,-),
+	checknodes(1,+),
+	checknodes_list(1,+),
+	sumlist(3,+,+,-),
+	sumnodes(3,+,+,-),
+	sumnodes_body(3,+,+,-,+,+),
+	include(1,+,-),
+	exclude(1,+,-),
+	partition(2,+,-,-),
+	partition(2,+,-,-,-).
 	
 	
 :- use_module(library(lists), [append/3]).
@@ -215,7 +215,7 @@ mapnodes(Pred, TermIn, TermOut) :-
     TermOut =.. [Func|ArgsOut].
 
 mapnodes_list(_, [], []).
-appnodes_list(Pred, [TermIn|ArgsIn], [TermOut|ArgsOut]) :-
+mapnodes_list(Pred, [TermIn|ArgsIn], [TermOut|ArgsOut]) :-
     mapnodes(Pred, TermIn, TermOut),
     mapnodes_list(Pred, ArgsIn, ArgsOut).
 
diff --git a/library/rbtrees.yap b/library/rbtrees.yap
index 4e2bb6655..fe348ae8e 100644
--- a/library/rbtrees.yap
+++ b/library/rbtrees.yap
@@ -61,7 +61,9 @@ form colour(Left, Key, Value, Right), where _colour_  is one of =red= or
 @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)).
@@ -773,8 +775,7 @@ visit(black(L,K,V,R),L0,Lf) :-
 	visit(L,[K-V|L1],Lf),
 	visit(R,L0,L1).
 
-:- meta_predicate rb_map(?,:,?). % this is not strictly required
-:- meta_predicate map(?,:,?,?).  % this is required.
+:- meta_predicate map(?,2,?,?).  % this is required.
 
 %%	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(R,Goal,NR,Nil).
 
-:- meta_predicate rb_map(?,:). % this is not strictly required
-:- meta_predicate map(?,:).  % this is required.
+:- meta_predicate rb_map(?,1). % this is not strictly required
+:- meta_predicate map(?,1).  % this is required.
 
 %%	rb_map(+T, :G, -TN) is semidet.
 %
diff --git a/packages/plunit/examples/read.pl b/packages/plunit/examples/read.pl
index e373407f6..a3ab885a0 100644
--- a/packages/plunit/examples/read.pl
+++ b/packages/plunit/examples/read.pl
@@ -19,4 +19,9 @@ test(read, [ setup(create_file(Tmp)),
 	read_file_to_terms(Tmp, Terms, []),
 	Terms =@= [hello(_)].
 
-%:- end_tests(read).
+:- end_tests(read).
+
+:- trace,run_tests.
+
+
+
diff --git a/pl/modules.yap b/pl/modules.yap
index 01b7a47cc..700841d9a 100644
--- a/pl/modules.yap
+++ b/pl/modules.yap
@@ -527,12 +527,12 @@ source_module(Mod) :-
 	'$current_module'(Mod).
 
 % comma has its own problems.
-:- '$install_meta_predicate'((:,:), prolog).
+:- '$install_meta_predicate'((0,0), prolog).
 
 :- meta_predicate
 	abolish(:),
 	abolish(:,+),
-	all(?,:,?),
+	all(?,0,-),
 	assert(:),
 	assert(:,+),
 	assert_static(:),
@@ -542,80 +542,80 @@ source_module(Mod) :-
 	assertz(:),
 	assertz(:,+),
 	assertz_static(:),
-	bagof(?,:,?),
+	bagof(?,0,-),
 	bb_get(:,-),
 	bb_put(:,+),
 	bb_delete(:,?),
 	bb_update(:,?,?),
-	call(:),
-	call(:,?),
-	call(:,?,?),
-	call(:,?,?,?),
-	call_with_args(:),
-	call_with_args(:,?),
-	call_with_args(:,?,?),
-	call_with_args(:,?,?,?),
-	call_with_args(:,?,?,?,?),
-	call_with_args(:,?,?,?,?,?),
-	call_with_args(:,?,?,?,?,?,?),
-	call_with_args(:,?,?,?,?,?,?,?),
-	call_with_args(:,?,?,?,?,?,?,?,?),
-	call_with_args(:,?,?,?,?,?,?,?,?,?),
-	format(+,:),
-	format(+,+,:),
-	call_cleanup(:,:),
-	call_cleanup(:,?,:),
-	setup_call_cleanup(:,:,:),
-	setup_call_catcher_cleanup(:,:,?,:),
-	call_residue(:,?),
-	call_residue_vars(:,?),
-	catch(:,+,:),
+	call(0),
+	call(1,?),
+	call(2,?,?),
+	call(3,?,?,?),
+	call_with_args(0),
+	call_with_args(1,?),
+	call_with_args(2,?,?),
+	call_with_args(3,?,?,?),
+	call_with_args(4,?,?,?,?),
+	call_with_args(5,?,?,?,?,?),
+	call_with_args(6,?,?,?,?,?,?),
+	call_with_args(7,?,?,?,?,?,?,?),
+	call_with_args(8,?,?,?,?,?,?,?,?),
+	call_with_args(9,?,?,?,?,?,?,?,?,?),
+	call_cleanup(0,0),
+	call_cleanup(0,?,0),
+	call_residue(0,?),
+	call_residue_vars(0,?),
+	catch(0,?,0),
 	clause(:,?),
 	clause(:,?,?),
 	compile(:),
 	consult(:),
 	current_predicate(:),
 	current_predicate(?,:),
-	depth_bound_call(:,+),
+	depth_bound_call(0,+),
 	discontiguous(:),
 	ensure_loaded(:),
-	findall(?,:,?),
-	findall(?,:,?,?),
-	forall(:,:),
-	freeze(?,:),
+	findall(?,0,-),
+	findall(?,0,-,?),
+	forall(0,0),
+	format(+,:),
+	format(+,+,:),
+	freeze(?,0),
 	hide_predicate(:),
-	if(:,:,:),
-	ignore(:),
-	incore(:),
+	if(0,0,0),
+	ignore(0),
+	incore(0),
 	listing(:),
 	multifile(:),
 	nospy(:),
-        not(:),
-        once(:),
-        phrase(:,?),
-        phrase(:,?,+),
+        not(0),
+        once(0),
+        phrase(2,?),
+        phrase(2,?,+),
 	predicate_property(:,?),
 	predicate_statistics(:,-,-,-),
-	on_exception(+,:,:),
+	on_exception(+,0,0),
 	reconsult(:),
 	retract(:),
 	retract(:,?),
 	retractall(:),
 	reconsult(:),
-	setof(?,:,?),
+	setof(?,0,-),
+	setup_call_cleanup(0,0,0),
+	setup_call_catcher_cleanup(0,0,?,0),
 	spy(:),
 	unknown(+,:),
 	use_module(:),
 	use_module(:,?),
 	use_module(?,:,?),
-	when(?,:),
-	with_mutex(+,:),
-	with_output_to(?,:),
-	(: -> :),
-	(: *-> :),
-	(: ; :),
-	^(+,:),
-	\+ : .
+	when(+,0),
+	with_mutex(+,0),
+	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.