[m-rev.] Fix coverage monitors in Morphine

Erwan Jahier Erwan.Jahier at imag.fr
Tue Feb 5 20:53:34 AEDT 2002


Since Zoltan pointed out that bug, probably he wishes to have a look
at that change (well, at least at pred_cov.in and call_site_cov.in).

--
Estimated hours taken: 10

Branches: main, release

Fix the monitors that were computing coverage rates in Morphine.  The
problem was the following. In order to check that two successes and
one failure occur for a multi predicate, I was looking at two exits
and one fail; but this is wrong since, of course, the two exits can
be produced by different calls, and since all multi predicates ends
up with a fail event. To get it right, I need to associate the call
number to exit and fail events. To do that, I maintain at exit ports
the list of call numbers; when an exit event occurs, I consider it as
covered iff the current call number is in the list. On the contrary,
I consider a failure as covered at a fail port iff the current call
number is not in the list. This also holds for semidet and nondet
procedures.

extras/morphine/non-regression-tests/queens.exp:
	Update the new expected outputs.

extras/morphine/source/call_site_cov.in:
extras/morphine/source/pred_cov.in:
	Change the code so that it does what it is supposed to do.

	Also use a map instead of a list to store what has to be
	covered for each procedure.

extras/morphine/source/generate_pred_cov.m:
extras/morphine/source/generate_call_site_cov.m:
extras/morphine/source/coverage_util.m:
	Generate an initialize/1 predicate that uses map instead of lists.

extras/morphine/source/coverage.op:
	Coverage monitors now output assoc lists.


Index: extras/morphine/non-regression-tests/queens.exp
===================================================================
RCS file: /home/mercury1/repository/mercury/extras/morphine/non-regression-tests/queens.exp,v
retrieving revision 1.9
diff -u -r1.9 queens.exp
--- extras/morphine/non-regression-tests/queens.exp	29 Aug 2001 12:17:23 -0000	1.9
+++ extras/morphine/non-regression-tests/queens.exp	5 Feb 2002 09:41:53 -0000
@@ -12,17 +12,17 @@
   3:  2 [2] exit data([1, 2, 3, 4, 5]) []  16
   4:  3 [2] call queen([1, 2, 3, 4, 5], -) []  16
   5:   4 [3] call qperm([1, 2, 3, 4, 5], -) []  43
-  6:   4 [3] switch qperm([1, 2, 3, 4, 5], -) [s1]  47
+  6:   4 [3] switch qperm([1, 2, 3, 4, 5], -) [s2]  47
   7:    5 [4] call qdelete(-, [1, 2, 3, 4, 5], -) []  48
   8:    5 [4] disj qdelete(-, [1, 2, 3, 4, 5], -) [c2, d1]  52
   9:    5 [4] exit qdelete(1, [1, 2, 3, 4, 5], [2, 3, 4, 5]) []  48
  10:    6 [4] call qperm([2, 3, 4, 5], -) []  50
- 11:    6 [4] switch qperm([2, 3, 4, 5], -) [s1]  47
+ 11:    6 [4] switch qperm([2, 3, 4, 5], -) [s2]  47
  12:     7 [5] call nondet (predicate) {queens} queens: qdelete(-, [2, 3, 4, 5] {list__list(int)}, -)/3-0 []  48
  13:     7 [5] disj nondet (predicate) {queens} queens: qdelete(-, [2, 3, 4, 5] {list__list(int)}, -)/3-0 [c2, d1]  52
  14:     7 [5] exit nondet (predicate) {queens} queens: qdelete(2 {int}, [2, 3, 4, 5] {list__list(int)}, [3, 4, 5] {list__list(int)})/3-0 []  48
  15:     8 [5] call nondet (predicate) {queens} queens: qperm([3, 4, 5] {list__list(int)}, -)/2-0 []  50
- 16:     8 [5] switch nondet (predicate) {queens} queens: qperm([3, 4, 5] {list__list(int)}, -)/2-0 [s1]  47
+ 16:     8 [5] switch nondet (predicate) {queens} queens: qperm([3, 4, 5] {list__list(int)}, -)/2-0 [s2]  47
  17:      9 [6] call nondet (predicate) {queens} queens: qdelete(-, [3, 4, 5] {list__list(int)}, -)/3-0 []  48
  18:      9 [6] disj nondet (predicate) {queens} queens: qdelete(-, [3, 4, 5] {list__list(int)}, -)/3-0 [c2, d1]  52
  19:      9 [6] exit nondet (predicate) {queens} queens: qdelete(3 {int}, [3, 4, 5] {list__list(int)}, [4, 5] {list__list(int)})/3-0 []  48
@@ -274,24 +274,26 @@
   1: 1 [1] call main(state('<<c_pointer>>'), -) []  0
 [1, 3, 5, 2, 4]
 End of connection with the traced program
-Uncovered: 9
-To cover: 33
-The coverage rate is 72.7273
+Uncovered: 13
+To cover: 35
+The coverage rate is 62.8571
 Uncovered call sites are:
+csc(queens, fail, 66, [fail])
+csc(queens, fail, 68, [fail])
+csc(queens, qdelete, 48, [fail])
 csc(queens, qperm, 43, [fail])
+csc(queens, qperm, 50, [fail])
 csc(queens, queen, 16, [exit, fail])
+csc(queens, write_int, 94, [exit])
 csc(queens, write_string, 19, [exit])
-csc(queens, fail, 66, [])
-csc(queens, fail, 68, [])
 csc(queens, write_string, 82, [exit])
 csc(queens, write_string, 84, [exit])
 csc(queens, write_string, 86, [exit])
-csc(queens, write_int, 94, [exit])
 csc(queens, write_string, 100, [exit])

 *** call_site_cov: ok.

-Uncovered = [csc("queens", "qperm", 43, [fail]), csc("queens", "queen", 16, [exit, fail]), csc("queens", "write_string", 19, [exit]), csc("queens", "fail", 66, []), csc("queens", "fail", 68, []), csc("queens", "write_string", 82, [exit]), csc("queens", "write_string", 84, [exit]), csc("queens", "write_string", 86, [exit]), csc("queens", "write_int", 94, [exit]), csc("queens", "write_string", 100, [exit])]     More? (;)
+Uncovered = [csc("queens", "fail", 66, [fail]), csc("queens", "fail", 68, [fail]), csc("queens", "qdelete", 48, [fail]), csc("queens", "qperm", 43, [fail]), csc("queens", "qperm", 50, [fail]), csc("queens", "queen", 16, [exit, fail]), csc("queens", "write_int", 94, [exit]), csc("queens", "write_string", 19, [exit]), csc("queens", "write_string", 82, [exit]), csc("queens", "write_string", 84, [exit]), csc("queens", "write_string", 86, [exit]), csc("queens", "write_string", 100, [exit])]     More? (;)
 [morphine 10]:
 **************************************************
 **** Testing pred_cov...
@@ -299,15 +301,16 @@
   1: 1 [1] call main(state('<<c_pointer>>'), -) []  0
 [1, 3, 5, 2, 4]
 End of connection with the traced program
-Uncovered: 2
+Uncovered: 3
 To cover: 17
-The coverage rate is 88.2353
+The coverage rate is 82.3529
 Uncovered predicates are:
+pc(queens, qperm, [fail])
 pc(queens, queen, [exit, fail])

 *** pred_cov: ok.

-Uncovered = [pc("queens", "queen", [exit, fail])]     More? (;)
+Uncovered = [pc("queens", "qperm", [fail]), pc("queens", "queen", [exit, fail])]     More? (;)
 [morphine 11]:
 **************************************************
 **** Testing other Morphine commands...
Index: extras/morphine/source/call_site_cov.in
===================================================================
RCS file: /home/mercury1/repository/mercury/extras/morphine/source/call_site_cov.in,v
retrieving revision 1.2
diff -u -r1.2 call_site_cov.in
--- extras/morphine/source/call_site_cov.in	29 Aug 2001 15:01:22 -0000	1.2
+++ extras/morphine/source/call_site_cov.in	5 Feb 2002 09:41:53 -0000
@@ -1,26 +1,55 @@
-%
+:- import_module map, list, assoc_list.

-:- import_module string.
+:- type port == trace_port_type.
+:- type proc ---> p(declared_module_name, proc_name, line_number).
+:- type call_site_crit ---> csc(list(call_number), list(port)).
+:- type accumulator_type == map(proc, call_site_crit).

-:- type call_site_crit --->
-	csc(defined_module_name, proc_name, line_number, list(trace_port_type)).
-
-:- type accumulator_type == list(call_site_crit).
+filter(Event, Map0, Map) :-
+  Port = port(Event),
+  Proc = p(decl_module(Event), proc_name(Event), line_number(Event)),
+  CallN = call(Event),
+  ( if
+      ( Port = exit ; Port = fail ),
+      csc(CNL0, PL0) = map__search(Map0, Proc)
+    then
+      ( if
+          CNL0 = []
+        then
+          remove_port(Port, PL0, PL)
+        else if
+          member(CallN, CNL0)
+        then
+          ( if Port = exit then remove_port(exit, PL0, PL) else PL = PL0 )
+        else
+          % not member(CallN, CNL0) and not (CNL0 = [])
+          ( if Port = exit then PL = PL0 else remove_port(fail, PL0, PL) )
+      ),
+      ( if
+          PL = []
+        then
+          map__delete(Map0, Proc, Map)
+        else
+          ( if
+	      (Port = exit, not member(CallN, CNL0))
+	    then
+	      CNL = [CallN | CNL0]
+	    else
+	     CNL = CNL0
+	  ),
+	  map__update(Map0, Proc, csc(CNL, PL), Map)
+      )
+    else
+      Map = Map0
+  ).

-filter(Event, CSL0, CSL) :-
-	solutions(update_call_site_list(port(Event), def_module(Event),
-		proc_name(Event), line_number(Event), CSL0), Sol),
-	( Sol = [CSL1|_] -> CSL = CSL1 ; CSL = CSL0 ).
+:- pred remove_port(port::in, list(port)::in, list(port)::out) is det.
+remove_port(Port, List0, List) :-
+  ( if list__delete_first(List0, Port, List1)
+    then List = List1 else List = List0 ).
+
+:- type collected_type == assoc_list(proc, call_site_crit).
+post_process(Map, AssocList) :-
+	map__to_assoc_list(Map, AssocList).

-:- pred update_call_site_list(trace_port_type::in, string::in, string::in, int::in,
-	accumulator_type::in, accumulator_type::out) is nondet.
-update_call_site_list(Port, Mod, ProcName, Ln, CSL0, CSL) :-
-	( Port = exit ; Port = fail ),
-	list__delete(CSL0, csc(Mod, ProcName, Ln, Crit), CSL1),
-	list__delete(Crit, Port, NewCrit),
-	( NewCrit = [] ->
-	    CSL = CSL1
-	;
-	    list__insert(csc(Mod, ProcName, Ln, NewCrit), CSL1, CSL)
-	).


Index: extras/morphine/source/coverage.op
===================================================================
RCS file: /home/mercury1/repository/mercury/extras/morphine/source/coverage.op,v
retrieving revision 1.1
diff -u -r1.1 coverage.op
--- extras/morphine/source/coverage.op	29 Aug 2001 12:17:20 -0000	1.1
+++ extras/morphine/source/coverage.op	5 Feb 2002 09:41:53 -0000
@@ -22,7 +22,7 @@
 %-----------------------------------------------------------------------%
 opium_command(
 	name		: pred_cov,
-	arg_list	: [Module, Uncovered],
+	arg_list	: [Call, Uncovered],
 	arg_type_list	: [string, var],
 	abbrev		: pc,
 	interface	: menu,
@@ -30,8 +30,9 @@
 	implementation	: pred_cov_Op,
 	parameters	: [],
 	message		:
-"Takes a Mercury module name \"Module\", and unifies its 2nd argument with the \
-uncovered predicate criteria of \"Module\" and the modules it imports which \
+"Takes a call to Mercury program (compiled in a debug mode) \
+(\"Call\") and unifies its 2nd argument with the uncovered predicate \
+criteria of the called module as well as the modules it imports which \
 are in the current directory. A predicate criterion is a \
 3-tuple containing a module name, a procedure name, and a list of `exit' and \
 `fail' atoms; for example, the predicate criterion \
@@ -40,11 +41,11 @@
 \n\
 \n\
 pred_cov/2 works as follows; it calls `morphine/bin/generate_pred_cov \
-<Module>.m' which generates 2 files: \"Module__pred_cov\" that contains \
-a monitor to perform the coverage, and \"Module__pred\" that contains \
-the list of call sites of Module. Then it runs the \"Module__pred_cov\" \
+<Module>.m' which generates 2 files: \"<Module>__pred_cov\" that contains \
+a monitor to perform the coverage, and \"<Module>__pred\" that contains \
+the list of call sites of <Module>. Then it runs the \"<Module>__pred_cov\" \
 monitor, which outputs the list of uncovered call sites. The file \
-\"Module__pred\" is used to display the coverage ratio.\
+\"<Module>__pred\" is used to display the coverage ratio.\
 ").

 pred_cov_Op(ProgramCall, Uncovered) :-
@@ -129,7 +130,8 @@

 crit_cov(CovType, ProgramCall, MonitorName, CritListFile, Uncovered) :-
 	run(ProgramCall),
-	collect(MonitorName, Uncovered),
+	collect(MonitorName, Uncovered0),
+	assoc_list_to_crit(Uncovered0, Uncovered),
 	count_crit(CovType, Uncovered, UncoveredCard),
 	print("Uncovered: "), print(UncoveredCard), nl,
 	get_crit_list_from_file(CritListFile, ToCover),
@@ -158,4 +160,14 @@
 	count_crit(pred, Tail, N0),
 	N is N0 + L.

+assoc_list_to_crit(AssocList, CritList) :-
+	maplist(assoc_to_crit, AssocList, CritList).

+assoc_to_crit(Assoc, Crit) :-
+	(
+	  Assoc = p(Mod, Name) - pc(_, List),
+	  Crit = pc(Mod, Name, List), !
+	;
+	  Assoc = p(Mod, Name, LN) - csc(_, List),
+	  Crit = csc(Mod, Name, LN, List)
+	  ).

Index: extras/morphine/source/coverage_util.m
===================================================================
RCS file: /home/mercury1/repository/mercury/extras/morphine/source/coverage_util.m,v
retrieving revision 1.2
diff -u -r1.2 coverage_util.m
--- extras/morphine/source/coverage_util.m	22 Jan 2002 14:21:51 -0000	1.2
+++ extras/morphine/source/coverage_util.m	5 Feb 2002 09:41:53 -0000
@@ -16,6 +16,15 @@
 :- type exit_or_fail ---> exit ; fail ; exception.


+:- type pred_crit --->
+	pc(string, string, list(exit_or_fail)).
+
+
+:- type call_site_crit --->
+	csc(string, string, int, list(exit_or_fail)).
+
+:- type crit ---> pc(list(pred_crit)) ; csc(list(call_site_crit)).
+
 :- pred get_read_item_list(list(term__term)::out,
 	io__state::di, io__state::uo) is det.

@@ -38,7 +47,7 @@

 :- pred det_to_port_list(string::in, list(exit_or_fail)::out) is det.

-:- pred generate_monitor(string::in, list(T)::in, string::in,
+:- pred generate_monitor(string::in, crit::in, string::in,
 	io__state::di, io__state::uo) is det.

 :- implementation.
@@ -263,7 +272,7 @@
 %-----------------------------------------------------------------------%
 %-----------------------------------------------------------------------%

-generate_monitor(FileName0, CritList, CovType) -->
+generate_monitor(FileName0, Crit, CovType) -->
 	( { remove_suffix(FileName0, ".m", FileName1) } ->
 		{ FileName2 = FileName1 }
 	;
@@ -291,28 +300,27 @@
 		print("_cov.in'\n"),
 		io__seen
 	;
-	    io__read_file_as_string(BeginningResult),
-	    (
-		{ BeginningResult = error(_, Msg3) },
-		print(Msg3)
-	    ;
-		{ BeginningResult = ok(Beginning) },
-		print("% File automatically generated by get_"),
+		print("% File automatically generated by morphine/source/generate_"),
 	        print(CovType),
-		print(".m\n\n"),
+		print("_cov.m\n\n"),
+		io__read_file_as_string(Res),
+	        (
+		      { Res = ok(Beginning) }
+		;
+		      { Res = error(Beginning, _) }
+		),
 		print(Beginning),
-		print("initialize(Acc) :- \n\t list__condense(["),
-		% I do not generate the list of call site in the first place
-		% as the Mercury compiler has trouble to compile large list
-		% (square time in the size of the list).
-		% Therefore I cut the list into chunks and apply list__condense
-		% to it.
-		% XXX check if it really changes anything
-		print_crit_list(CritList, _),
-		print("], Acc)."),
+		print("initialize(Map) :- \n"),
+		print("\tmap__init(Map0)"),
+	        (
+		     { Crit = pc(PCritList) },
+		     print_pc_list(0, PCritList)
+		;
+		     { Crit = csc(CSCritList) },
+		     print_csc_list(0, CSCritList)
+		),
 		io__told,
 		io__seen
-	    )
 	),
 	{ append_list([FileName2, "__", CovType], FileName4) },
 	io__tell(FileName4, Res3),
@@ -321,39 +329,54 @@
 	->
 		print(Msg4)
 	;
-		print(CritList),
+		(
+		  { Crit = pc(PCcrit) },
+		  print(PCcrit)
+		;
+		  { Crit = csc(CSCcrit) },
+		  print(CSCcrit)
+		),
 		print(".\n"),
 		io__told
 	).

-:- pred print_crit_list(list(T)::in, list(T)::out,
+:- pred print_pc_list(int::in, list(pred_crit)::in,
 	io__state::di, io__state::uo) is det.
-print_crit_list(List0, List) -->
-	( { List0 = [] } ->
-		{ List = List0 }
-	;
-		print("["),
-		print_crit_list2(10, List0, List1),
-		( { List1 = [] } ->
-			print("\t\t] ")
-		;
-			print("\t\t], ")
-		),
-		print_crit_list(List1, List)
-	   ).
+print_pc_list(Cpt, List) -->
+	(
+	        { List = [] }
+	;
+	        { List = [pc(Mod, Name, PortList) | Tail] },
+		print(",\n\tmap__det_insert(Map"), print(Cpt),
+	        print(", p("), write(Mod), print(", "), write(Name), print(")"),
+	        print(", pc([], "), print(PortList), print("), Map"),
+	        ( if { Tail = [] } then
+		       print(").\n")
+	          else
+	               { NewCpt = Cpt+1 },
+	               print(NewCpt), print(")"),
+	               print_pc_list(NewCpt, Tail)
+		)
+	).

-:- pred print_crit_list2(int::in, list(T)::in, list(T)::out,
+:- pred print_csc_list(int::in, list(call_site_crit)::in,
 	io__state::di, io__state::uo) is det.
-print_crit_list2(_, [], [], S, S).
-print_crit_list2(N, [X|Xs], List) -->
-	( { N = 0 ; Xs = [] } ->
-		{ List = Xs },
-		print("\t\t"),
-		print(X),
-		print(" \n")
-	;
-		print("\t\t"),
-		print(X),
-		print(", \n"),
-		print_crit_list2(N-1, Xs, List)
+print_csc_list(Cpt, List) -->
+	(
+	        { List = [] },
+	        print("")
+	;
+	        { List = [csc(Mod, Name, LN, PortList) | Tail] },
+		print(",\n\tmap__det_insert(Map"), print(Cpt),
+	        print(", p("), write(Mod), print(", "), write(Name),
+	        print(", "), print(LN), print(")"),
+	        print(", csc([], "), print(PortList), print("), Map"),
+	        ( if { Tail = [] } then
+		       print(").\n")
+	          else
+	               { NewCpt = Cpt+1 },
+	               print(NewCpt), print(")"),
+	               print_csc_list(NewCpt, Tail)
+		)
 	).
+
Index: extras/morphine/source/generate_call_site_cov.m
===================================================================
RCS file: /home/mercury1/repository/mercury/extras/morphine/source/generate_call_site_cov.m,v
retrieving revision 1.2
diff -u -r1.2 generate_call_site_cov.m
--- extras/morphine/source/generate_call_site_cov.m	25 Sep 2001 09:37:00 -0000	1.2
+++ extras/morphine/source/generate_call_site_cov.m	5 Feb 2002 09:41:54 -0000
@@ -19,7 +19,7 @@
 %
 %    This program is largely untested, and hence almost certainly buggy.
 %
-%    High order calls not handled: e.g. solutions(foo, L) will miss the call
+%    Higher-order calls are not handled: e.g. solutions(foo, L) will miss the call
 %    to foo (should be easy to fix).
 %
 %    I suppose there is one mode per predicate or function; indeed, it is
@@ -93,7 +93,7 @@

 		    { get_call_site_list_criteria(DetList, CallSiteList,
 			CallSiteCritList) },
-		    generate_monitor(FileName, CallSiteCritList, "call_site")
+		    generate_monitor(FileName, csc(CallSiteCritList), "call_site")
 		;
 		    io__write_string("File does not exist\n")
 		 ))
@@ -104,7 +104,6 @@
     ).

 :- type call_site ---> cs(string, string, int).
-:- type call_site_crit ---> csc(string, string, int, list(exit_or_fail)).

 %-----------------------------------------------------------------------%
 %-----------------------------------------------------------------------%
@@ -138,7 +137,6 @@


 :- pred get_call_site(term__term::in, list(call_site)::out) is semidet.
-
 get_call_site(term__functor(Const, [_, TermBody], _context), CallSiteList) :-
 	( Const = atom(":-") ; Const = atom("-->") ),
 	get_call_site_body(TermBody, CallSiteList).
@@ -260,12 +258,23 @@
 	;
 		Pred = Pred0
 	),
-
-	( member(_Mod - Pred - Det, DetList) ->
+	(
+	        is_predefined(Pred, Det)
+	->
+	        det_to_port_list(Det, Crit)
+	;
+	        member(_Mod - Pred - Det, DetList)
+	->
 		det_to_port_list(Det, Crit)
 	;
-		Crit = []
+	        Crit = []
 	).
+
+
+% Some calls won't appear in user programs, neitheir in libs...
+:- pred is_predefined(string::in, string::out) is semidet.
+is_predefined("true", "multi").
+is_predefined("fail", "failure").

 %-----------------------------------------------------------------------%
 %-----------------------------------------------------------------------%
Index: extras/morphine/source/generate_pred_cov.m
===================================================================
RCS file: /home/mercury1/repository/mercury/extras/morphine/source/generate_pred_cov.m,v
retrieving revision 1.1
diff -u -r1.1 generate_pred_cov.m
--- extras/morphine/source/generate_pred_cov.m	29 Aug 2001 12:17:19 -0000	1.1
+++ extras/morphine/source/generate_pred_cov.m	5 Feb 2002 09:41:54 -0000
@@ -33,14 +33,14 @@
 		    get_all_imported_module_list("", ImpModList, ImpModList,
 			    AllModList, _),

-		    % we want the predicates define in the module it imports
+		    % we want the predicates defined in the module it imports
 		    % which are in the same directory
 		    { get_proc_det_list(FileName, ItemList, DetList1) },
 		    get_all_proc_det_list(AllModList, DetList2),
 		    { append(DetList1, DetList2, DetList) },

 		    { get_pred_list_criteria(DetList, PredCritList) },
-		    generate_monitor(FileName, PredCritList, "pred")
+		    generate_monitor(FileName, pc(PredCritList), "pred")
 		;
 		    io__write_string("File does not exist\n")
 		 ))
@@ -49,7 +49,6 @@
     ).


-:- type pred_crit ---> pc(string, string, list(exit_or_fail)).


 %-----------------------------------------------------------------------%
Index: extras/morphine/source/pred_cov.in
===================================================================
RCS file: /home/mercury1/repository/mercury/extras/morphine/source/pred_cov.in,v
retrieving revision 1.2
diff -u -r1.2 pred_cov.in
--- extras/morphine/source/pred_cov.in	29 Aug 2001 15:01:22 -0000	1.2
+++ extras/morphine/source/pred_cov.in	5 Feb 2002 09:41:54 -0000
@@ -1,26 +1,55 @@
-%
+:- import_module map, list, assoc_list.

-:- import_module string.
+:- type port == trace_port_type.
+:- type proc ---> p(declared_module_name, proc_name).
+:- type pred_crit ---> pc(list(call_number), list(port)).
+:- type accumulator_type == map(proc, pred_crit).

-:- type pred_crit --->
-	pc(declared_module_name, proc_name, list(trace_port_type)).
-
-:- type accumulator_type == list(pred_crit).
+filter(Event, Map0, Map) :-
+  Port = port(Event),
+  Proc = p(decl_module(Event), proc_name(Event)),
+  CallN = call(Event),
+  ( if
+      ( Port = exit ; Port = fail ),
+      pc(CNL0, PL0) = map__search(Map0, Proc)
+    then
+      ( if
+          CNL0 = []
+        then
+          remove_port(Port, PL0, PL)
+        else if
+          member(CallN, CNL0)
+        then
+          ( if Port = exit then remove_port(exit, PL0, PL)  else PL = PL0 )
+        else
+          % not member(CallN, CNL0) and not (CNL0 = [])
+          ( if Port = exit then PL = PL0 else remove_port(fail, PL0, PL) )
+      ),
+      ( if
+          PL = []
+        then
+          map__delete(Map0, Proc, Map)
+        else
+          ( if
+	      (Port = exit, not member(CallN, CNL0))
+	    then
+	      CNL = [CallN | CNL0]
+	    else
+	     CNL = CNL0
+	  ),
+	  map__update(Map0, Proc, pc(CNL, PL), Map)
+      )
+    else
+      Map = Map0
+  ).

-filter(Event, CSL0, CSL) :-
-	solutions(update_pred_list(port(Event), decl_module(Event),
-		proc_name(Event), CSL0), Sol),
-	( Sol = [CSL1|_] -> CSL = CSL1 ; CSL = CSL0 ).
+:- pred remove_port(port::in, list(port)::in, list(port)::out) is det.
+remove_port(Port, List0, List) :-
+  ( if list__delete_first(List0, Port, List1)
+    then List = List1 else List = List0 ).
+
+:- type collected_type == assoc_list(proc, pred_crit).
+post_process(Map, AssocList) :-
+	map__to_assoc_list(Map, AssocList).

-:- pred update_pred_list(trace_port_type::in, string::in, string::in,
-	accumulator_type::in, accumulator_type::out) is nondet.
-update_pred_list(Port, Mod, ProcName, CSL0, CSL) :-
-	( Port = exit ; Port = fail ),
-	list__delete(CSL0, pc(Mod, ProcName, Crit), CSL1),
-	list__delete(Crit, Port, NewCrit),
-	( NewCrit = [] ->
-	        CSL = CSL1
-	;
-	        list__insert(pc(Mod, ProcName, NewCrit), CSL1, CSL)
-	).



-- 
R1.


--------------------------------------------------------------------------
mercury-reviews mailing list
post:  mercury-reviews at cs.mu.oz.au
administrative address: owner-mercury-reviews at cs.mu.oz.au
unsubscribe: Address: mercury-reviews-request at cs.mu.oz.au Message: unsubscribe
subscribe:   Address: mercury-reviews-request at cs.mu.oz.au Message: subscribe
--------------------------------------------------------------------------



More information about the reviews mailing list