[m-rev.] for review: syntactically correct goals in decl debug

Mark Brown dougl at cs.mu.OZ.AU
Wed Oct 16 11:07:53 AEST 2002


Hi,

This change was requested by Zoltan in last Monday's meeting, and is
for review by Zoltan.

Cheers,
Mark.

Estimated hours taken: 1.5
Branches: main

Change the declarative debugger so it always prints syntactically
correct goals.

browser/declarative_user.m:
	Print atoms using browse__print_synthetic. This means that goals
	will always be syntactically correct, even if they are printed
	in the multi-line form.

	Make the predicates write_decl{_init,_final,}_atom take an argument
	of type browse_caller_type.  When printing a single goal use the
	caller type "print", and when printing a sequence of goals use
	"print_all".

browser/browse.m:
	When writing out a synthetic term using io__write_univ, check for
	arguments with type util__unbound.  Print such values as a single
	unquoted underscore (io__write_univ would print an underscore in
	single quotes, which means something different).

browser/util.m:
	Export functions is_predicate and is_function to convert values of
	type pred_or_func to values of type bool.

tests/debugger/print_goal.exp:
tests/debugger/queens_rep.exp:
	Update the output of these tests after the change to browse.m.

tests/debugger/declarative/app.exp:
tests/debugger/declarative/app.exp2:
tests/debugger/declarative/filter.exp:
tests/debugger/declarative/filter.exp2:
tests/debugger/declarative/input_term_dep.exp:
tests/debugger/declarative/input_term_dep.exp2:
tests/debugger/declarative/output_term_dep.exp:
tests/debugger/declarative/output_term_dep.exp2:
tests/debugger/declarative/queens.exp:
tests/debugger/declarative/tabled_read_decl.exp:
tests/debugger/declarative/tabled_read_decl.exp2:
	Update the output of these test cases.

Index: browser/browse.m
===================================================================
RCS file: /home/mercury1/repository/mercury/browser/browse.m,v
retrieving revision 1.29
diff -u -r1.29 browse.m
--- browser/browse.m	3 Jul 2002 08:25:02 -0000	1.29
+++ browser/browse.m	16 Oct 2002 00:47:50 -0000
@@ -538,7 +538,13 @@
 	;
 		io__write_string("("),
 		io__write_list(Args, ", ", pred(U::in, di, uo) is cc_multi -->
-			io__write_univ(Stream, include_details_cc, U)),
+			(
+				{ univ_to_type(U, _ `with_type` unbound) }
+			->
+				io__write_char(Stream, '_')
+			;
+				io__write_univ(Stream, include_details_cc, U)
+			)),
 		io__write_string(")")
 	),
 	(
Index: browser/declarative_user.m
===================================================================
RCS file: /home/mercury1/repository/mercury/browser/declarative_user.m,v
retrieving revision 1.21
diff -u -r1.21 declarative_user.m
--- browser/declarative_user.m	3 Oct 2002 07:34:26 -0000	1.21
+++ browser/declarative_user.m	15 Oct 2002 10:49:42 -0000
@@ -426,21 +426,21 @@
 	io__state::di, io__state::uo) is cc_multi.
 
 write_decl_question(wrong_answer(_, Atom), User) -->
-	write_decl_final_atom(User, "", Atom).
+	write_decl_final_atom(User, "", print, Atom).
 	
 write_decl_question(missing_answer(_, Call, Solns), User) -->
-	write_decl_init_atom(User, "Call ", Call),
+	write_decl_init_atom(User, "Call ", print, Call),
 	(
 		{ Solns = [] }
 	->
 		io__write_string(User ^ outstr, "No solutions.\n")
 	;
 		io__write_string(User ^ outstr, "Solutions:\n"),
-		list__foldl(write_decl_final_atom(User, "\t"), Solns)
+		list__foldl(write_decl_final_atom(User, "\t", print_all), Solns)
 	).
 
 write_decl_question(unexpected_exception(_, Call, Exception), User) -->
-	write_decl_init_atom(User, "Call ", Call),
+	write_decl_init_atom(User, "Call ", print, Call),
 	io__write_string(User ^ outstr, "Throws "),
 	io__write(User ^ outstr, include_details_cc, univ_value(Exception)),
 	io__nl(User ^ outstr).
@@ -452,16 +452,16 @@
 	(
 		{ EBug = incorrect_contour(Atom, _, _) },
 		io__write_string(User ^ outstr, "Found incorrect contour:\n"),
-		write_decl_final_atom(User, "", Atom)
+		write_decl_final_atom(User, "", print, Atom)
 	;
 		{ EBug = partially_uncovered_atom(Atom, _) },
 		io__write_string(User ^ outstr,
 				"Found partially uncovered atom:\n"),
-		write_decl_init_atom(User, "", Atom)
+		write_decl_init_atom(User, "", print, Atom)
 	;
 		{ EBug = unhandled_exception(Atom, Exception, _) },
 		io__write_string(User ^ outstr, "Found unhandled exception:\n"),
-		write_decl_init_atom(User, "", Atom),
+		write_decl_init_atom(User, "", print, Atom),
 		io__write(User ^ outstr, include_details_cc,
 				univ_value(Exception)),
 		io__nl(User ^ outstr)
@@ -470,94 +470,54 @@
 write_decl_bug(i_bug(IBug), User) -->
 	{ IBug = inadmissible_call(Parent, _, Call, _) },
 	io__write_string(User ^ outstr, "Found inadmissible call:\n"),
-	write_decl_atom(User, "Parent ", init(Parent)),
-	write_decl_atom(User, "Call ", init(Call)).
+	write_decl_atom(User, "Parent ", print, init(Parent)),
+	write_decl_atom(User, "Call ", print, init(Call)).
 
-:- pred write_decl_init_atom(user_state::in, string::in, init_decl_atom::in,
-	io__state::di, io__state::uo) is cc_multi.
+:- pred write_decl_init_atom(user_state::in, string::in, browse_caller_type::in,
+	init_decl_atom::in, io__state::di, io__state::uo) is cc_multi.
 
-write_decl_init_atom(User, Indent, InitAtom) -->
-	write_decl_atom(User, Indent, init(InitAtom)).
+write_decl_init_atom(User, Indent, CallerType, InitAtom) -->
+	write_decl_atom(User, Indent, CallerType, init(InitAtom)).
 
-:- pred write_decl_final_atom(user_state::in, string::in, final_decl_atom::in,
-	io__state::di, io__state::uo) is cc_multi.
+:- pred write_decl_final_atom(user_state::in, string::in,
+	browse_caller_type::in, final_decl_atom::in, io__state::di,
+	io__state::uo) is cc_multi.
 
-write_decl_final_atom(User, Indent, FinalAtom) -->
-	write_decl_atom(User, Indent, final(FinalAtom)).
+write_decl_final_atom(User, Indent, CallerType, FinalAtom) -->
+	write_decl_atom(User, Indent, CallerType, final(FinalAtom)).
 
-:- pred write_decl_atom(user_state::in, string::in, some_decl_atom::in,
-	io__state::di, io__state::uo) is cc_multi.
+:- pred write_decl_atom(user_state::in, string::in, browse_caller_type::in,
+	some_decl_atom::in, io__state::di, io__state::uo) is cc_multi.
 
-write_decl_atom(User, Indent, DeclAtom) -->
+write_decl_atom(User, Indent, CallerType, DeclAtom) -->
 	io__write_string(User ^ outstr, Indent),
-		%
-		% Check whether the atom is likely to fit on one line.
-		% If it's not, then call the browser to print the term
-		% to a limited depth.  If it is, then we prefer to print
-		% it out directly so that all arguments are put on the
-		% same line.
-		%
 	{ unravel_decl_atom(DeclAtom, TraceAtom, IoActions) },
+	{ TraceAtom = atom(PredOrFunc, Functor, Args0) },
 	{ Which = chosen_head_vars_presentation },
-	{ check_trace_atom_size(Indent, Which, TraceAtom, RemSize) },
-	(
-		{ RemSize > 0 },
-		{ IoActions = [] }
-	->
-		write_decl_atom_direct(User ^ outstr, TraceAtom, Which)
-	;
-		write_decl_atom_limited(User, DeclAtom, Which)
-	).
+	{ maybe_filter_headvars(Which, Args0, Args1) },
+	{ list__map(trace_atom_arg_to_univ, Args1, Args) },
+		%
+		% Call the term browser to print the atom as a goal.
+		%
+	browse__print_synthetic(Functor, Args, is_function(PredOrFunc),
+		User ^ outstr, CallerType, User ^ browser),
+	write_io_actions(User, IoActions).
 
-:- pred check_trace_atom_size(string::in, which_headvars::in, trace_atom::in,
-	int::out) is cc_multi.
+:- pred trace_atom_arg_to_univ(trace_atom_arg::in, univ::out) is det.
 
-check_trace_atom_size(Indent, Which, atom(_, Functor, Args), RemSize) :-
-	trace_atom_size_limit(RemSize0),
-	string__length(Indent, I),
-	string__length(Functor, F),
-	P = 2,		% parentheses
-	RemSize1 = RemSize0 - I - F - P,
-	size_left_after_args(Args, Which, RemSize1, RemSize).
-
-:- pred size_left_after_args(list(trace_atom_arg)::in, which_headvars::in,
-	int::in, int::out) is cc_multi.
-
-size_left_after_args([], _) -->
-	[].
-size_left_after_args([arg_info(UserVis, _, MaybeUniv) | Args], Which) -->
+trace_atom_arg_to_univ(TraceAtomArg, Univ) :-
+	MaybeUniv = TraceAtomArg ^ arg_value,
 	(
-		{ MaybeUniv = yes(Univ) },
-		(
-			{ Which = only_user_headvars },
-			{ UserVis = no }
-		->
-			% This argument won't be printed.
-			[]
-		;
-			term_size_left_from_max(Univ)
-		)
+		MaybeUniv = yes(Univ)
 	;
-		{ MaybeUniv = no }
-	),
-	size_left_after_args(Args, Which).
-
-:- pred trace_atom_size_limit(int).
-:- mode trace_atom_size_limit(out) is det.
-
-trace_atom_size_limit(79).
+		MaybeUniv = no,
+		Univ = univ('_' `with_type` unbound)
+	).
 
-:- pred write_decl_atom_limited(user_state::in, some_decl_atom::in,
-	which_headvars::in, io__state::di, io__state::uo) is cc_multi.
+:- pred write_io_actions(user_state::in, list(io_action)::in, io__state::di,
+	io__state::uo) is cc_multi.
 
-write_decl_atom_limited(User, DeclAtom, Which) -->
-	{ unravel_decl_atom(DeclAtom, TraceAtom, IoActions) },
-	{ TraceAtom = atom(PredOrFunc, Functor, Args0) },
-	write_decl_atom_category(User ^ outstr, PredOrFunc),
-	io__write_string(User ^ outstr, Functor),
-	io__nl(User ^ outstr),
-	{ maybe_filter_headvars(Which, Args0, Args) },
-	list__foldl(print_decl_atom_arg(User), Args),
+write_io_actions(User, IoActions) -->
 	{ list__length(IoActions, NumIoActions) },
 	( { NumIoActions = 0 } ->
 		[]
@@ -585,75 +545,5 @@
 	{ io_action_to_synthetic_term(IoAction, ProcName, Args, IsFunc) },
 	browse__print_synthetic(ProcName, Args, IsFunc, User ^ outstr,
 		print_all, User ^ browser).
-
-:- pred write_decl_atom_category(io__output_stream::in, pred_or_func::in,
-	io__state::di, io__state::uo) is det.
-
-write_decl_atom_category(OutStr, predicate) -->
-	io__write_string(OutStr, "pred ").
-write_decl_atom_category(OutStr, function) -->
-	io__write_string(OutStr, "func ").
-
-:- pred print_decl_atom_arg(user_state::in, trace_atom_arg::in,
-	io__state::di, io__state::uo) is cc_multi.
-
-print_decl_atom_arg(User, arg_info(_, _, MaybeArg)) -->
-	(
-		{ MaybeArg = yes(Arg) },
-		io__write_string(User ^ outstr, "\t"),
-		browse__print(univ_value(Arg), User ^ outstr, print_all,
-			User ^ browser)
-	;
-		{ MaybeArg = no },
-		io__write_string(User ^ outstr, "\t_\n")
-	).
-
-:- pred write_decl_atom_direct(io__output_stream::in, trace_atom::in,
-	which_headvars::in, io__state::di, io__state::uo) is cc_multi.
-
-write_decl_atom_direct(OutStr, atom(PredOrFunc, Functor, Args0), Which) -->
-	io__write_string(OutStr, Functor),
-	{ maybe_filter_headvars(Which, Args0, Args) },
-	(
-		{ Args = [] }
-	;
-		{ Args = [FirstArg | ArgsRest] },
-		io__write_char(OutStr, '('),
-		(
-			{ PredOrFunc = predicate },
-			io__write_list(OutStr, Args, ", ",
-					write_decl_atom_arg(OutStr)),
-			io__write_char(OutStr, ')')
-		;
-			{ PredOrFunc = function },
-			{ get_inputs_and_result(FirstArg, ArgsRest, Inputs,
-					Result) },
-			io__write_list(OutStr, Inputs, ", ",
-					write_decl_atom_arg(OutStr)),
-			io__write_string(OutStr, ") = "),
-			write_decl_atom_arg(OutStr, Result)
-		)
-	),
-	io__nl(OutStr).
-
-:- pred write_decl_atom_arg(io__output_stream, trace_atom_arg,
-		io__state, io__state).
-:- mode write_decl_atom_arg(in, in, di, uo) is cc_multi.
-
-write_decl_atom_arg(OutStr, arg_info(_, _, MaybeArg)) -->
-	(
-		{ MaybeArg = yes(Arg) },
-		io__write(OutStr, include_details_cc, univ_value(Arg))
-	;
-		{ MaybeArg = no },
-		io__write_char(OutStr, '_')
-	).
-
-:- pred get_inputs_and_result(T, list(T), list(T), T).
-:- mode get_inputs_and_result(in, in, out, out) is det.
-
-get_inputs_and_result(A, [], [], A).
-get_inputs_and_result(A1, [A2 | As], [A1 | Inputs0], Result) :-
-	get_inputs_and_result(A2, As, Inputs0, Result).
 
 %-----------------------------------------------------------------------------%
Index: browser/util.m
===================================================================
RCS file: /home/mercury1/repository/mercury/browser/util.m,v
retrieving revision 1.20
diff -u -r1.20 util.m
--- browser/util.m	16 Sep 2002 02:26:15 -0000	1.20
+++ browser/util.m	15 Oct 2002 10:47:40 -0000
@@ -8,7 +8,7 @@
 
 :- interface.
 
-:- import_module list, string, io.
+:- import_module list, string, io, bool.
 
 % The stuff defined below is similar to types goal_path and trace_port
 % defined in modules compiler/hlds_goal.m and compiler/trace.m.
@@ -42,6 +42,9 @@
 	--->	predicate
 	;	function.
 
+:- func util__is_predicate(pred_or_func) = bool.
+:- func util__is_function(pred_or_func) = bool.
+
 :- type goal_path_string == string.
 
 :- type line_number == int.
@@ -82,6 +85,12 @@
 :- implementation.
 
 :- import_module int, require.
+
+util__is_predicate(predicate) = yes.
+util__is_predicate(function) = no.
+
+util__is_function(predicate) = no.
+util__is_function(function) = yes.
 
 util__trace_getline(Prompt, Result) -->
 	io__input_stream(MdbIn),
Index: tests/debugger/print_goal.exp
===================================================================
RCS file: /home/mercury1/repository/tests/debugger/print_goal.exp,v
retrieving revision 1.4
diff -u -r1.4 print_goal.exp
--- tests/debugger/print_goal.exp	11 Sep 2002 07:20:30 -0000	1.4
+++ tests/debugger/print_goal.exp	15 Oct 2002 14:53:42 -0000
@@ -11,7 +11,7 @@
 mdb> c
       E2:     C2  2 CALL pred print_goal:big_data/1-0 (det)
 mdb> p goal
-big_data('_')
+big_data(_)
 mdb> finish
       E3:     C2  2 EXIT pred print_goal:big_data/1-0 (det)
 mdb> p goal
Index: tests/debugger/queens_rep.exp
===================================================================
RCS file: /home/mercury1/repository/tests/debugger/queens_rep.exp,v
retrieving revision 1.1
diff -u -r1.1 queens_rep.exp
--- tests/debugger/queens_rep.exp	3 Apr 2002 07:08:22 -0000	1.1
+++ tests/debugger/queens_rep.exp	15 Oct 2002 14:54:26 -0000
@@ -6,6 +6,6 @@
 mdb> goto 9
        9:      5  4 DISJ pred queens_rep:qdelete/3-0 (nondet) c2;d1;
 mdb> print
-qdelete('_', [1, 2, 3, 4, 5], '_')
+qdelete(_, [1, 2, 3, 4, 5], _)
 mdb> continue -n -S
 [1, 3, 5, 2, 4]
Index: tests/debugger/declarative/app.exp
===================================================================
RCS file: /home/mercury1/repository/tests/debugger/declarative/app.exp,v
retrieving revision 1.11
diff -u -r1.11 app.exp
--- tests/debugger/declarative/app.exp	25 Sep 2001 09:37:11 -0000	1.11
+++ tests/debugger/declarative/app.exp	15 Oct 2002 14:54:52 -0000
@@ -15,10 +15,7 @@
 mdb> finish -n
       16:      5  5 EXIT pred app:app/3-0 (det) app.m:26 (app.m:28)
 mdb> dd
-pred app
-	[4, 5]
-	[6, 7, 8]
-	[4, 5, 6, 7, 8]
+app([|](4, [|](5, [])), [|](6, [|](7, [|]/2)), [|](4, [|](5, [|]/2)))
 Valid? yes
 No bug found.
       16:      5  5 EXIT pred app:app/3-0 (det) app.m:26 (app.m:28)
@@ -29,26 +26,14 @@
 mdb> continue
       19:      2  2 EXIT pred app:app/3-0 (det) app.m:26 (app.m:13)
 mdb> dd
-pred app
-	[1, 2, 3, 4, 5]
-	[6, 7, 8]
-	[|](1, [|](2, [|](3, [|]/2)))
-Valid? no
-pred app
-	[2, 3, 4, 5]
-	[6, 7, 8]
-	[2, 3, 4, 5, 6, 7, 8]
-Valid? no
-pred app
-	[3, 4, 5]
-	[6, 7, 8]
-	[3, 4, 5, 6, 7, 8]
+app([|](1, [|](2, [|]/2)), [|](6, [|](7, [|]/2)), [|](1, [|](2, [|]/2)))
+Valid? no
+app([|](2, [|](3, [|]/2)), [|](6, [|](7, [|]/2)), [|](2, [|](3, [|]/2)))
+Valid? no
+app([|](3, [|](4, [|]/2)), [|](6, [|](7, [|]/2)), [|](3, [|](4, [|]/2)))
 Valid? no
 Found incorrect contour:
-pred app
-	[3, 4, 5]
-	[6, 7, 8]
-	[3, 4, 5, 6, 7, 8]
+app([|](3, [|](4, [|]/2)), [|](6, [|](7, [|]/2)), [|](3, [|](4, [|]/2)))
 Is this a bug? yes
       17:      4  4 EXIT pred app:app/3-0 (det) app.m:26 (app.m:28)
 mdb> continue
@@ -61,61 +46,28 @@
 mdb> finish -n
       67:      8  2 EXIT pred app:app/3-0 (det) app.m:26 (app.m:18)
 mdb> dd
-pred app
-	[|](1, [|](2, [|](3, [|]/2)))
-	[6, 7, 8]
-	[|](1, [|](2, [|](3, [|]/2)))
-Valid? no
-pred app
-	[|](2, [|](3, [|](4, [|]/2)))
-	[6, 7, 8]
-	[|](2, [|](3, [|](4, [|]/2)))
-Valid? no
-pred app
-	[|](3, [|](4, [|](5, [|]/2)))
-	[6, 7, 8]
-	[|](3, [|](4, [|](5, [|]/2)))
-Valid? no
-pred app
-	[|](4, [|](5, [|](6, [|]/2)))
-	[6, 7, 8]
-	[|](4, [|](5, [|](6, [|]/2)))
-Valid? no
-pred app
-	[|](5, [|](6, [|](7, [|]/2)))
-	[6, 7, 8]
-	[|](5, [|](6, [|](7, [|]/2)))
-Valid? no
-pred app
-	[|](6, [|](7, [|](8, [|]/2)))
-	[6, 7, 8]
-	[|](6, [|](7, [|](8, [|]/2)))
-Valid? no
-pred app
-	[|](7, [|](8, [|](9, [|]/2)))
-	[6, 7, 8]
-	[|](7, [|](8, [|](9, [|]/2)))
-Valid? no
-pred app
-	[|](8, [|](9, [|](0, [|]/2)))
-	[6, 7, 8]
-	[|](8, [|](9, [|](0, [|]/2)))
-Valid? no
-pred app
-	[9, 0, 1, 2, 3, 4, 5]
-	[6, 7, 8]
-	[|](9, [|](0, [|](1, [|]/2)))
-Valid? no
-pred app
-	[0, 1, 2, 3, 4, 5]
-	[6, 7, 8]
-	[|](0, [|](1, [|](2, [|]/2)))
+app([|](1, [|](2, [|]/2)), [|](6, [|](7, [|]/2)), [|](1, [|](2, [|]/2)))
+Valid? no
+app([|](2, [|](3, [|]/2)), [|](6, [|](7, [|]/2)), [|](2, [|](3, [|]/2)))
+Valid? no
+app([|](3, [|](4, [|]/2)), [|](6, [|](7, [|]/2)), [|](3, [|](4, [|]/2)))
+Valid? no
+app([|](4, [|](5, [|]/2)), [|](6, [|](7, [|]/2)), [|](4, [|](5, [|]/2)))
+Valid? no
+app([|](5, [|](6, [|]/2)), [|](6, [|](7, [|]/2)), [|](5, [|](6, [|]/2)))
+Valid? no
+app([|](6, [|](7, [|]/2)), [|](6, [|](7, [|]/2)), [|](6, [|](7, [|]/2)))
+Valid? no
+app([|](7, [|](8, [|]/2)), [|](6, [|](7, [|]/2)), [|](7, [|](8, [|]/2)))
+Valid? no
+app([|](8, [|](9, [|]/2)), [|](6, [|](7, [|]/2)), [|](8, [|](9, [|]/2)))
+Valid? no
+app([|](9, [|](0, [|]/2)), [|](6, [|](7, [|]/2)), [|](9, [|](0, [|]/2)))
+Valid? no
+app([|](0, [|](1, [|]/2)), [|](6, [|](7, [|]/2)), [|](0, [|](1, [|]/2)))
 Valid? no
 Found incorrect contour:
-pred app
-	[3, 4, 5]
-	[6, 7, 8]
-	[3, 4, 5, 6, 7, 8]
+app([|](3, [|](4, [|]/2)), [|](6, [|](7, [|]/2)), [|](3, [|](4, [|]/2)))
 Is this a bug? yes
       55:     20 14 EXIT pred app:app/3-0 (det) app.m:26 (app.m:28)
 mdb> continue
Index: tests/debugger/declarative/app.exp2
===================================================================
RCS file: /home/mercury1/repository/tests/debugger/declarative/app.exp2,v
retrieving revision 1.11
diff -u -r1.11 app.exp2
--- tests/debugger/declarative/app.exp2	25 Sep 2001 09:37:11 -0000	1.11
+++ tests/debugger/declarative/app.exp2	16 Oct 2002 00:39:00 -0000
@@ -15,10 +15,7 @@
 mdb> finish -n
       16:      5  5 EXIT pred app:app/3-0 (det) app.m:26 (app.m:28)
 mdb> dd
-pred app
-	[4, 5]
-	[6, 7, 8]
-	[4, 5, 6, 7, 8]
+app([|](4, [|](5, [])), [|](6, [|](7, [|]/2)), [|](4, [|](5, [|]/2)))
 Valid? yes
 No bug found.
       16:      5  5 EXIT pred app:app/3-0 (det) app.m:26 (app.m:28)
@@ -29,26 +26,14 @@
 mdb> continue
       19:      2  2 EXIT pred app:app/3-0 (det) app.m:26 (app.m:13)
 mdb> dd
-pred app
-	[1, 2, 3, 4, 5]
-	[6, 7, 8]
-	[|](1, [|](2, [|](3, [|]/2)))
-Valid? no
-pred app
-	[2, 3, 4, 5]
-	[6, 7, 8]
-	[2, 3, 4, 5, 6, 7, 8]
-Valid? no
-pred app
-	[3, 4, 5]
-	[6, 7, 8]
-	[3, 4, 5, 6, 7, 8]
+app([|](1, [|](2, [|]/2)), [|](6, [|](7, [|]/2)), [|](1, [|](2, [|]/2)))
+Valid? no
+app([|](2, [|](3, [|]/2)), [|](6, [|](7, [|]/2)), [|](2, [|](3, [|]/2)))
+Valid? no
+app([|](3, [|](4, [|]/2)), [|](6, [|](7, [|]/2)), [|](3, [|](4, [|]/2)))
 Valid? no
 Found incorrect contour:
-pred app
-	[3, 4, 5]
-	[6, 7, 8]
-	[3, 4, 5, 6, 7, 8]
+app([|](3, [|](4, [|]/2)), [|](6, [|](7, [|]/2)), [|](3, [|](4, [|]/2)))
 Is this a bug? yes
       17:      4  4 EXIT pred app:app/3-0 (det) app.m:26 (app.m:28)
 mdb> continue
@@ -61,61 +46,28 @@
 mdb> finish -n
       71:     10  2 EXIT pred app:app/3-0 (det) app.m:26 (app.m:18)
 mdb> dd
-pred app
-	[|](1, [|](2, [|](3, [|]/2)))
-	[6, 7, 8]
-	[|](1, [|](2, [|](3, [|]/2)))
-Valid? no
-pred app
-	[|](2, [|](3, [|](4, [|]/2)))
-	[6, 7, 8]
-	[|](2, [|](3, [|](4, [|]/2)))
-Valid? no
-pred app
-	[|](3, [|](4, [|](5, [|]/2)))
-	[6, 7, 8]
-	[|](3, [|](4, [|](5, [|]/2)))
-Valid? no
-pred app
-	[|](4, [|](5, [|](6, [|]/2)))
-	[6, 7, 8]
-	[|](4, [|](5, [|](6, [|]/2)))
-Valid? no
-pred app
-	[|](5, [|](6, [|](7, [|]/2)))
-	[6, 7, 8]
-	[|](5, [|](6, [|](7, [|]/2)))
-Valid? no
-pred app
-	[|](6, [|](7, [|](8, [|]/2)))
-	[6, 7, 8]
-	[|](6, [|](7, [|](8, [|]/2)))
-Valid? no
-pred app
-	[|](7, [|](8, [|](9, [|]/2)))
-	[6, 7, 8]
-	[|](7, [|](8, [|](9, [|]/2)))
-Valid? no
-pred app
-	[|](8, [|](9, [|](0, [|]/2)))
-	[6, 7, 8]
-	[|](8, [|](9, [|](0, [|]/2)))
-Valid? no
-pred app
-	[9, 0, 1, 2, 3, 4, 5]
-	[6, 7, 8]
-	[|](9, [|](0, [|](1, [|]/2)))
-Valid? no
-pred app
-	[0, 1, 2, 3, 4, 5]
-	[6, 7, 8]
-	[|](0, [|](1, [|](2, [|]/2)))
+app([|](1, [|](2, [|]/2)), [|](6, [|](7, [|]/2)), [|](1, [|](2, [|]/2)))
+Valid? no
+app([|](2, [|](3, [|]/2)), [|](6, [|](7, [|]/2)), [|](2, [|](3, [|]/2)))
+Valid? no
+app([|](3, [|](4, [|]/2)), [|](6, [|](7, [|]/2)), [|](3, [|](4, [|]/2)))
+Valid? no
+app([|](4, [|](5, [|]/2)), [|](6, [|](7, [|]/2)), [|](4, [|](5, [|]/2)))
+Valid? no
+app([|](5, [|](6, [|]/2)), [|](6, [|](7, [|]/2)), [|](5, [|](6, [|]/2)))
+Valid? no
+app([|](6, [|](7, [|]/2)), [|](6, [|](7, [|]/2)), [|](6, [|](7, [|]/2)))
+Valid? no
+app([|](7, [|](8, [|]/2)), [|](6, [|](7, [|]/2)), [|](7, [|](8, [|]/2)))
+Valid? no
+app([|](8, [|](9, [|]/2)), [|](6, [|](7, [|]/2)), [|](8, [|](9, [|]/2)))
+Valid? no
+app([|](9, [|](0, [|]/2)), [|](6, [|](7, [|]/2)), [|](9, [|](0, [|]/2)))
+Valid? no
+app([|](0, [|](1, [|]/2)), [|](6, [|](7, [|]/2)), [|](0, [|](1, [|]/2)))
 Valid? no
 Found incorrect contour:
-pred app
-	[3, 4, 5]
-	[6, 7, 8]
-	[3, 4, 5, 6, 7, 8]
+app([|](3, [|](4, [|]/2)), [|](6, [|](7, [|]/2)), [|](3, [|](4, [|]/2)))
 Is this a bug? yes
       59:     22 14 EXIT pred app:app/3-0 (det) app.m:26 (app.m:28)
 mdb> continue
Index: tests/debugger/declarative/filter.exp
===================================================================
RCS file: /home/mercury1/repository/tests/debugger/declarative/filter.exp,v
retrieving revision 1.5
diff -u -r1.5 filter.exp
--- tests/debugger/declarative/filter.exp	25 Sep 2001 09:37:11 -0000	1.5
+++ tests/debugger/declarative/filter.exp	15 Oct 2002 14:55:05 -0000
@@ -15,7 +15,7 @@
 Valid? yes
 s2([9])
 Valid? yes
-my_append([1, 2], [9], [1, 2, 9])
+my_append([|](1, [|](2, [])), [|](9, []), [|](1, [|](2, [|]/2)))
 Valid? yes
 Found incorrect contour:
 p([1, 2, 9])
@@ -30,10 +30,7 @@
 Valid? no
 s2([7, 8, 9])
 Valid? yes
-pred my_append
-	[1, 2]
-	[7, 8, 9]
-	[1, 2, 7, 8, 9]
+my_append([|](1, [|](2, [])), [|](7, [|](8, [|]/2)), [|](1, [|](2, [|]/2)))
 Valid? yes
 Found incorrect contour:
 p([1, 2, 7, 8, 9])
@@ -48,10 +45,7 @@
 Valid? no
 s1([1, 2, 3])
 Valid? yes
-pred my_append
-	[1, 2, 3]
-	[9]
-	[1, 2, 3, 9]
+my_append([|](1, [|](2, [|]/2)), [|](9, []), [|](1, [|](2, [|]/2)))
 Valid? yes
 Found incorrect contour:
 p([1, 2, 3, 9])
@@ -64,10 +58,7 @@
 mdb> dd
 p([1, 2, 3, 7, 8, 9])
 Valid? no
-pred my_append
-	[1, 2, 3]
-	[7, 8, 9]
-	[1, 2, 3, 7, 8, 9]
+my_append([|](1, [|](2, [|]/2)), [|](7, [|](8, [|]/2)), [|](1, [|](2, [|]/2)))
 Valid? yes
 Found incorrect contour:
 p([1, 2, 3, 7, 8, 9])
Index: tests/debugger/declarative/filter.exp2
===================================================================
RCS file: /home/mercury1/repository/tests/debugger/declarative/filter.exp2,v
retrieving revision 1.5
diff -u -r1.5 filter.exp2
--- tests/debugger/declarative/filter.exp2	25 Sep 2001 09:37:11 -0000	1.5
+++ tests/debugger/declarative/filter.exp2	16 Oct 2002 00:39:54 -0000
@@ -15,7 +15,7 @@
 Valid? yes
 s2([9])
 Valid? yes
-my_append([1, 2], [9], [1, 2, 9])
+my_append([|](1, [|](2, [])), [|](9, []), [|](1, [|](2, [|]/2)))
 Valid? yes
 Found incorrect contour:
 p([1, 2, 9])
@@ -30,10 +30,7 @@
 Valid? no
 s2([7, 8, 9])
 Valid? yes
-pred my_append
-	[1, 2]
-	[7, 8, 9]
-	[1, 2, 7, 8, 9]
+my_append([|](1, [|](2, [])), [|](7, [|](8, [|]/2)), [|](1, [|](2, [|]/2)))
 Valid? yes
 Found incorrect contour:
 p([1, 2, 7, 8, 9])
@@ -48,10 +45,7 @@
 Valid? no
 s1([1, 2, 3])
 Valid? yes
-pred my_append
-	[1, 2, 3]
-	[9]
-	[1, 2, 3, 9]
+my_append([|](1, [|](2, [|]/2)), [|](9, []), [|](1, [|](2, [|]/2)))
 Valid? yes
 Found incorrect contour:
 p([1, 2, 3, 9])
@@ -64,10 +58,7 @@
 mdb> dd
 p([1, 2, 3, 7, 8, 9])
 Valid? no
-pred my_append
-	[1, 2, 3]
-	[7, 8, 9]
-	[1, 2, 3, 7, 8, 9]
+my_append([|](1, [|](2, [|]/2)), [|](7, [|](8, [|]/2)), [|](1, [|](2, [|]/2)))
 Valid? yes
 Found incorrect contour:
 p([1, 2, 3, 7, 8, 9])
Index: tests/debugger/declarative/input_term_dep.exp
===================================================================
RCS file: /home/mercury1/repository/tests/debugger/declarative/input_term_dep.exp,v
retrieving revision 1.1
diff -u -r1.1 input_term_dep.exp
--- tests/debugger/declarative/input_term_dep.exp	23 Apr 2001 16:26:31 -0000	1.1
+++ tests/debugger/declarative/input_term_dep.exp	15 Oct 2002 14:55:23 -0000
@@ -40,9 +40,7 @@
 q([[2, 3], [], [1]])
 Valid? browse 1
 browser> mark 1/2
-pred qc
-	[[2, 3], [], [1]]
-	[[2, 3], [], [1]]
+qc([|]([|](2, [|]/2), [|]([], [|]/2)), [|]([|](2, [|]/2), [|]([], [|]/2)))
 Valid? browse 1
 browser> mark 1/2
 qa([[1], [2, 3]])
Index: tests/debugger/declarative/input_term_dep.exp2
===================================================================
RCS file: /home/mercury1/repository/tests/debugger/declarative/input_term_dep.exp2,v
retrieving revision 1.1
diff -u -r1.1 input_term_dep.exp2
--- tests/debugger/declarative/input_term_dep.exp2	23 Apr 2001 16:26:31 -0000	1.1
+++ tests/debugger/declarative/input_term_dep.exp2	16 Oct 2002 00:40:23 -0000
@@ -40,9 +40,7 @@
 q([[2, 3], [], [1]])
 Valid? browse 1
 browser> mark 1/2
-pred qc
-	[[2, 3], [], [1]]
-	[[2, 3], [], [1]]
+qc([|]([|](2, [|]/2), [|]([], [|]/2)), [|]([|](2, [|]/2), [|]([], [|]/2)))
 Valid? browse 1
 browser> mark 1/2
 qa([[1], [2, 3]])
Index: tests/debugger/declarative/output_term_dep.exp
===================================================================
RCS file: /home/mercury1/repository/tests/debugger/declarative/output_term_dep.exp,v
retrieving revision 1.3
diff -u -r1.3 output_term_dep.exp
--- tests/debugger/declarative/output_term_dep.exp	30 Apr 2002 10:12:44 -0000	1.3
+++ tests/debugger/declarative/output_term_dep.exp	15 Oct 2002 14:55:45 -0000
@@ -40,7 +40,7 @@
 mdb> finish
       20:      8  3 EXIT pred output_term_dep:q/1-0 (det)
 mdb> dd
-q([[1, 2, 3], [], [99]])
+q([|]([|](1, [|]/2), [|]([], [|]/2)))
 Valid? browse 1
 browser> mark 2/1
 qb([])
@@ -50,7 +50,7 @@
 qc([99])
 Valid? yes
 Found incorrect contour:
-q([[1, 2, 3], [], [99]])
+q([|]([|](1, [|]/2), [|]([], [|]/2)))
 Is this a bug? yes
       20:      8  3 EXIT pred output_term_dep:q/1-0 (det)
 mdb> continue
Index: tests/debugger/declarative/output_term_dep.exp2
===================================================================
RCS file: /home/mercury1/repository/tests/debugger/declarative/output_term_dep.exp2,v
retrieving revision 1.3
diff -u -r1.3 output_term_dep.exp2
--- tests/debugger/declarative/output_term_dep.exp2	30 Apr 2002 10:12:44 -0000	1.3
+++ tests/debugger/declarative/output_term_dep.exp2	16 Oct 2002 00:40:59 -0000
@@ -40,7 +40,7 @@
 mdb> finish
       32:     14  3 EXIT pred output_term_dep:q/1-0 (det)
 mdb> dd
-q([[1, 2, 3], [], [99]])
+q([|]([|](1, [|]/2), [|]([], [|]/2)))
 Valid? browse 1
 browser> mark 2/1
 qb([])
@@ -50,7 +50,7 @@
 qc([99])
 Valid? yes
 Found incorrect contour:
-q([[1, 2, 3], [], [99]])
+q([|]([|](1, [|]/2), [|]([], [|]/2)))
 Is this a bug? yes
       32:     14  3 EXIT pred output_term_dep:q/1-0 (det)
 mdb> continue
Index: tests/debugger/declarative/queens.exp
===================================================================
RCS file: /home/mercury1/repository/tests/debugger/declarative/queens.exp,v
retrieving revision 1.10
diff -u -r1.10 queens.exp
--- tests/debugger/declarative/queens.exp	25 Sep 2001 09:37:11 -0000	1.10
+++ tests/debugger/declarative/queens.exp	15 Oct 2002 14:55:57 -0000
@@ -17,22 +17,16 @@
 Call qperm([1, 2, 3, 4, 5], _)
 No solutions.
 Complete? no
-pred qdelete
-	1
-	[1, 2, 3, 4, 5]
-	[2, 3, 4, 5]
+qdelete(1, [|](1, [|](2, [|]/2)), [|](2, [|](3, [|]/2)))
 Valid? yes
-pred qdelete
-	2
-	[1, 2, 3, 4, 5]
-	[1, 3, 4, 5]
+qdelete(2, [|](1, [|](2, [|]/2)), [|](1, [|](3, [|]/2)))
 Valid? yes
 Call qperm([1, 3, 4, 5], _)
 No solutions.
 Complete? no
-qdelete(1, [1, 3, 4, 5], [3, 4, 5])
+qdelete(1, [|](1, [|](3, [|]/2)), [|](3, [|](4, [|]/2)))
 Valid? yes
-qdelete(3, [1, 3, 4, 5], [1, 4, 5])
+qdelete(3, [|](1, [|](3, [|]/2)), [|](1, [|](4, [|]/2)))
 Valid? yes
 Call qperm([1, 4, 5], _)
 No solutions.
Index: tests/debugger/declarative/tabled_read_decl.exp
===================================================================
RCS file: /home/mercury1/repository/tests/debugger/declarative/tabled_read_decl.exp,v
retrieving revision 1.2
diff -u -r1.2 tabled_read_decl.exp
--- tests/debugger/declarative/tabled_read_decl.exp	13 Sep 2002 03:37:45 -0000	1.2
+++ tests/debugger/declarative/tabled_read_decl.exp	15 Oct 2002 14:56:13 -0000
@@ -13,25 +13,16 @@
 mdb> finish -n
       32:      4  3 EXIT pred tabled_read_decl:test/4-0 (det)
 mdb> print
-test('<<c_pointer>>', 1123, '_', state('<<c_pointer>>'))
+test('<<c_pointer>>', 1123, _, state('<<c_pointer>>'))
 mdb> dd
-pred test
-	'<<c_pointer>>'
-	1123
-	_
-	state('<<c_pointer>>')
+test('<<c_pointer>>', 1123, _, state('<<c_pointer>>'))
 4 io actions:
 read_char_code('<<c_pointer>>', 49)
 read_char_code('<<c_pointer>>', 50)
 read_char_code('<<c_pointer>>', 51)
 read_char_code('<<c_pointer>>', 10)
 Valid? no
-pred test_2
-	'<<c_pointer>>'
-	1
-	1123
-	_
-	state('<<c_pointer>>')
+test_2('<<c_pointer>>', 1, 1123, _, state('<<c_pointer>>'))
 4 io actions:
 read_char_code('<<c_pointer>>', 49)
 read_char_code('<<c_pointer>>', 50)
@@ -39,11 +30,7 @@
 read_char_code('<<c_pointer>>', 10)
 Valid? yes
 Found incorrect contour:
-pred test
-	'<<c_pointer>>'
-	1123
-	_
-	state('<<c_pointer>>')
+test('<<c_pointer>>', 1123, _, state('<<c_pointer>>'))
 4 io actions:
 read_char_code('<<c_pointer>>', 49)
 read_char_code('<<c_pointer>>', 50)
Index: tests/debugger/declarative/tabled_read_decl.exp2
===================================================================
RCS file: /home/mercury1/repository/tests/debugger/declarative/tabled_read_decl.exp2,v
retrieving revision 1.2
diff -u -r1.2 tabled_read_decl.exp2
--- tests/debugger/declarative/tabled_read_decl.exp2	13 Sep 2002 03:37:45 -0000	1.2
+++ tests/debugger/declarative/tabled_read_decl.exp2	16 Oct 2002 00:41:24 -0000
@@ -13,25 +13,16 @@
 mdb> finish -n
       54:      4  3 EXIT pred tabled_read_decl:test/4-0 (det)
 mdb> print
-test('<<c_pointer>>', 1123, '_', state('<<c_pointer>>'))
+test('<<c_pointer>>', 1123, _, state('<<c_pointer>>'))
 mdb> dd
-pred test
-	'<<c_pointer>>'
-	1123
-	_
-	state('<<c_pointer>>')
+test('<<c_pointer>>', 1123, _, state('<<c_pointer>>'))
 4 io actions:
 read_char_code('<<c_pointer>>', 49)
 read_char_code('<<c_pointer>>', 50)
 read_char_code('<<c_pointer>>', 51)
 read_char_code('<<c_pointer>>', 10)
 Valid? no
-pred test_2
-	'<<c_pointer>>'
-	1
-	1123
-	_
-	state('<<c_pointer>>')
+test_2('<<c_pointer>>', 1, 1123, _, state('<<c_pointer>>'))
 4 io actions:
 read_char_code('<<c_pointer>>', 49)
 read_char_code('<<c_pointer>>', 50)
@@ -39,11 +30,7 @@
 read_char_code('<<c_pointer>>', 10)
 Valid? yes
 Found incorrect contour:
-pred test
-	'<<c_pointer>>'
-	1123
-	_
-	state('<<c_pointer>>')
+test('<<c_pointer>>', 1123, _, state('<<c_pointer>>'))
 4 io actions:
 read_char_code('<<c_pointer>>', 49)
 read_char_code('<<c_pointer>>', 50)
--------------------------------------------------------------------------
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