[m-rev.] for review: handle EXCP nodes in wrong and missing answer diagnosis

Ian MacLarty maclarty at cs.mu.OZ.AU
Wed Jan 19 01:26:14 AEDT 2005


On Mon, Jan 17, 2005 at 02:26:43PM +1100, Mark Brown wrote:
> Please post a full diff (including the change to add contour_children, which
> I haven't yet reviewed in detail).  Make sure you do a cvs update first,
> since there have been other changes committed since you posted this.
> 

Here you go. I might need to add some extra expected outputs for the new test
case in the debugging grades.  I am bootchecking those grades now.

Estimated hours taken: 5
Branches: main

Include EXCP nodes as wrong and missing answer children, instead of aborting.

browser/declarative_tree.m
	Change trace_parent to trace_last_parent in a comment and reformat.

	Record duplicate events when working out the number of events in an
	exception node, since the exits of the call that throws the exception
	may also appear in the EDT as siblings of the exception node.

	Use call_node_from_id instead of det_trace_node_from_id when looking
	up a call node in node_events.

	Instead of aborting when an EXCP node is encountered, add it as
	a child for both missing and wrong answer diagnosis.  If the call
	succeeded before generating the EXCP event then also add the EXIT 
	events as children in case the call was inside try_all/3.

	Since unexpected_exception_children and wrong_answer_children are now
	almost identical, replace them with one predicate contour_children.

	Since missing_answer_children is now also used to gather all the
	exits of a call in a try_all/3 that threw an exception, rename it to 
	stratum_chilren.

tests/debugger/declarative/catch.exp
tests/debugger/declarative/catch.inp
	This test doesn't abort with an error message anymore, but
	asks if the caught exception was expected.

	Note that I have not adjusted catch.exp2 since the catch test has been
	failing in the decldebug grade for a different reason, namely because 
	tracing information is not being included in the stack for 
	builtin_catch.

tests/debugger/declarative/exceptions.exp
tests/debugger/declarative/exceptions.inp
tests/debugger/declarative/exceptions.m
tests/debugger/declarative/Mercury.options
tests/debugger/declarative/Mmakefile
	Test finding the children in a contour with an exception event where
	the contour ends in an EXIT and also where the contour ends in an EXCP.
	Test finding the children in a stratum where the stratum contains an
	EXCP event.
	
	Compile this test with the strict sequential semantics so disjunctions
	are evaluated in the order given.

Index: browser/declarative_tree.m
===================================================================
RCS file: /home/mercury1/repository/mercury/browser/declarative_tree.m,v
retrieving revision 1.14
diff -u -r1.14 declarative_tree.m
--- browser/declarative_tree.m	18 Jan 2005 03:56:51 -0000	1.14
+++ browser/declarative_tree.m	18 Jan 2005 14:08:48 -0000
@@ -205,9 +205,10 @@
 	% since one EXIT event could belong to multiple children if it is in 
 	% a call which is backtracked over and each of these children could
 	% have different parents.  We return the last interface event of the
-	% parent CALL event as the parent.  This is okay since trace_parent is
-	% only used when an explicit subtree is generated which is above the
-	% previous subtree, so it doesn't really matter which parent we pick.
+	% parent CALL event as the parent.  This is okay since
+	% trace_last_parent is only used when an explicit subtree is generated
+	% which is above the previous subtree, so it doesn't really matter
+	% which parent we pick.
 	%
 :- pred trace_last_parent(wrap(S)::in, edt_node(R)::in, edt_node(R)::out) 
 	is semidet <= annotated_trace(S, R).
@@ -266,23 +267,23 @@
 	(
 		Node = fail(PrecId, CallId, _, _),
 		not_at_depth_limit(Store, CallId),
-		missing_answer_children(Store, PrecId, CallId, [], Children)
+		stratum_children(Store, PrecId, CallId, [], Children)
 	;
 		Node = exit(PrecId, CallId, _, Atom, _, _),
 		not_at_depth_limit(Store, CallId),
 		(
 			missing_answer_special_case(Atom)
 		->
-			missing_answer_children(Store, PrecId, CallId, [], 
+			stratum_children(Store, PrecId, CallId, [], 
 				Children)
 		;
-			wrong_answer_children(Store, PrecId, CallId, [], 
-				Children)
+			contour_children(normal, Store, PrecId, CallId, 
+				[], Children)
 		)
 	;
 		Node = excp(PrecId, CallId, _, _, _),
 		not_at_depth_limit(Store, CallId),
-		unexpected_exception_children(Store, PrecId, CallId, [],
+		contour_children(exception, Store, PrecId, CallId, [],
 			Children)
 	).
 
@@ -293,11 +294,12 @@
 	get_edt_call_node(Store, Ref, CallId),
 	\+ not_at_depth_limit(Store, CallId).
 
-:- pred trace_weight(wrap(S)::in, edt_node(R)::in, int::out, int::out)
-	is det <= annotated_trace(S, R).
+:- pred trace_weight(wrap(S)::in, edt_node(R)::in, int::out,
+	int::out) is det <= annotated_trace(S, R).
 
 trace_weight(Store, NodeId, Weight, ExcessWeight) :- 
-	node_events(Store, NodeId, 0, Weight, no, 0, 0, ExcessWeight).
+	node_events(Store, NodeId, 0, Weight, no, 0, 0,
+		ExcessWeight).
 
 	% Conservatively guess the number of events in the descendents of the
 	% call corresponding to the given final event plus the number of
@@ -307,7 +309,7 @@
 	%
 	% We include all the events between the final event and the last
 	% REDO before the final event, plus all the events between previous
-	% EXITs and REDOs and the initial CALL.  For EXIT and EXCP events
+	% EXITs and REDOs and the initial CALL.  For EXIT events
 	% this is an over approximation, but we can't know which events
 	% will be included in descendent contours when those descendent
 	% events are in unmaterialized portions of the annotated trace.
@@ -321,13 +323,13 @@
 	% of whether the final node was a FAIL or not - duplicates need only be
 	% recorded for FAIL nodes.  This should be `no' initially.  DupFactor
 	% keeps track of how many times the events before the last REDO could
-	% have been duplicated and should initially be zero.
+	% have been duplicated and should initially be zero.  
 	%
 :- pred node_events(wrap(S)::in, edt_node(R)::in, int::in, int::out, bool::in,
 	int::in, int::in, int::out) is det <= annotated_trace(S, R).
 
-node_events(wrap(Store), dynamic(Ref), PrevEvents, Events, RecordDups,
-		DupFactor, PrevDupEvents, DupEvents) :-
+node_events(wrap(Store), dynamic(Ref), PrevEvents, Events, 
+		RecordDups, DupFactor, PrevDupEvents, DupEvents) :-
 	det_trace_node_from_id(Store, Ref, Final),
 	(
 		(
@@ -338,7 +340,7 @@
 			NewRecordDups = yes
 		;
 			Final = excp(_, CallId, RedoId, _, FinalEvent),
-			NewRecordDups = RecordDups
+			NewRecordDups = yes
 		)
 	->
 		(
@@ -358,23 +360,16 @@
 				NewRecordDups, DupFactor + 1, 
 				NewPrevDupEvents, DupEvents)
 		;
-			det_trace_node_from_id(Store, CallId, Call),
+			call_node_from_id(Store, CallId, Call),
+			CallEvent = Call ^ call_event,
+			Events = PrevEvents + FinalEvent - CallEvent + 1,
 			(
-				CallEvent = Call ^ call_event
-			->
-				Events = PrevEvents + FinalEvent - CallEvent 
-					+ 1,
-				(
-					NewRecordDups = yes,
-					DupEvents = PrevDupEvents + DupFactor *
-						(FinalEvent - CallEvent + 1)
-				;
-					NewRecordDups = no,
-					DupEvents = 0
-				)
+				NewRecordDups = yes,
+				DupEvents = PrevDupEvents + DupFactor *
+					(FinalEvent - CallEvent + 1)
 			;
-				throw(internal_error("node_events",
-					"not a CALL"))
+				NewRecordDups = no,
+				DupEvents = 0
 			)
 		)
 	;
@@ -396,38 +391,55 @@
 	call_node_from_id(Store, Ref, CallNode),
 	CallNode ^ call_at_max_depth = no.
 
-:- pred wrong_answer_children(S, R, R, list(edt_node(R)), list(edt_node(R)))
-		<= annotated_trace(S, R).
-:- mode wrong_answer_children(in, in, in, in, out) is det.
+:- type contour_type
+			% The contour ends with an EXIT event.
+	--->	normal
+			% The contour ends with an EXCP event.
+	;	exception.
+
+:- pred contour_children(contour_type::in, S::in, R::in, R::in, 
+	list(edt_node(R))::in, list(edt_node(R))::out)  is det
+	<= annotated_trace(S, R).
 
-wrong_answer_children(Store, NodeId, StartId, Ns0, Ns) :-
+contour_children(ContourType, Store, NodeId, StartId, Ns0, Ns) :-
 	(
 		NodeId = StartId
 	->
 		Ns = Ns0
 	;
-		wrong_answer_children_2(Store, NodeId, StartId, Ns0, Ns)
+		contour_children_2(ContourType, Store, NodeId, StartId, 
+			Ns0, Ns)
 	).
 
-:- pred wrong_answer_children_2(S, R, R, list(edt_node(R)),
-	list(edt_node(R))) <= annotated_trace(S, R).
-:- mode wrong_answer_children_2(in, in, in, in, out) is det.
+:- pred contour_children_2(contour_type::in, S::in, R::in, R::in, 
+	list(edt_node(R))::in, list(edt_node(R))::out)  is det
+	<= annotated_trace(S, R).
 
-wrong_answer_children_2(Store, NodeId, StartId, Ns0, Ns) :-
+contour_children_2(ContourType, Store, NodeId, StartId, Ns0, Ns) :-
 	det_trace_node_from_id(Store, NodeId, Node),
 	(
-		( Node = call(_, _, _, _, _, _, _, _, _)
-		; Node = neg(_, _, _)
-		; Node = cond(_, _, failed)
+		( 
+			Node = call(_, _, _, _, _, _, _, _, _)
+		; 
+			%
+			% A non-failed NEGE could be encountered when gathering
+			% the children of an exception node, since the
+			% exception may have been thrown inside the negation.
+			%
+			(
+				ContourType = normal,
+				Node = neg(_, _, _)
+			;
+				ContourType = exception,
+				Node = neg(_, _, failed)
+			)
+		; 
+			Node = cond(_, _, failed)
 		)
 	->
-		throw(internal_error("wrong_answer_children_2",
+		throw(internal_error("contour_children_2",
 			"unexpected start of contour"))
 	;
-		Node = excp(_, _, _, _, _)
-	->
-		throw(unimplemented_feature("code that catches exceptions"))
-	;
 		Node = exit(_, _, _, _, _, _)
 	->
 			%
@@ -455,7 +467,7 @@
 			%
 		call_node_from_id(Store, CallId, Call),
 		NestedStartId = Call ^ call_preceding,
-		missing_answer_children(Store, NodeId, NestedStartId, Ns0, Ns1)
+		stratum_children(Store, NodeId, NestedStartId, Ns0, Ns1)
 	;
 		Node = neg_fail(Prec, NestedStartId)
 	->
@@ -466,7 +478,8 @@
 			% tell whether the call was in a negated context or
 			% backtracked over, so we have to assume the former.
 			%
-		wrong_answer_children(Store, Prec, NestedStartId, Ns0, Ns1)
+		contour_children(ContourType, Store, Prec, 
+			NestedStartId, Ns0, Ns1)
 	;
 		( Node = else(Prec, NestedStartId)
 		; Node = neg_succ(Prec, NestedStartId)
@@ -475,7 +488,34 @@
 			%
 			% There is a nested context.
 			%
-		missing_answer_children(Store, Prec, NestedStartId, Ns0, Ns1)
+		stratum_children(Store, Prec, NestedStartId, Ns0, Ns1)
+	; 
+		Node = excp(_, CallId, _, _, _)
+	->
+			%
+			% If the contour ends in an exception, then add this
+			% exception to the list of contour children and 
+			% continue along the contour, since in this case we are
+			% only interested in nodes that caused the exception to
+			% be thrown. 
+			%
+			% If the contour ends with an exit then the exception
+			% must have been caught by a try/2 or try_all/3 or
+			% similar.  In this case we want to add all the exits
+			% of the call that threw the exception to the list of
+			% children since one of the generated solutions may
+			% be incorrect.
+			%
+		(
+			ContourType = exception,
+			Ns1 = [dynamic(NodeId) | Ns0]
+		;
+			ContourType = normal,	
+			call_node_from_id(Store, CallId, Call),
+			NestedStartId = Call ^ call_preceding,
+			stratum_children(Store, NodeId, NestedStartId, 
+				Ns0, Ns1)
+		)
 	;
 			%
 			% This handles the following cases:
@@ -492,26 +532,26 @@
 		Ns1 = Ns0
 	),
 	Next = step_left_in_contour(Store, Node),
-	wrong_answer_children(Store, Next, StartId, Ns1, Ns).
+	contour_children(ContourType, Store, Next, StartId, Ns1, Ns).
 
-:- pred missing_answer_children(S, R, R, list(edt_node(R)), list(edt_node(R)))
+:- pred stratum_children(S, R, R, list(edt_node(R)), list(edt_node(R)))
 		<= annotated_trace(S, R).
-:- mode missing_answer_children(in, in, in, in, out) is det.
+:- mode stratum_children(in, in, in, in, out) is det.
 
-missing_answer_children(Store, NodeId, StartId, Ns0, Ns) :-
+stratum_children(Store, NodeId, StartId, Ns0, Ns) :-
 	(
 		NodeId = StartId
 	->
 		Ns = Ns0
 	;
-		missing_answer_children_2(Store, NodeId, StartId, Ns0, Ns)
+		stratum_children_2(Store, NodeId, StartId, Ns0, Ns)
 	).
 
-:- pred missing_answer_children_2(S, R, R, list(edt_node(R)), list(edt_node(R)))
+:- pred stratum_children_2(S, R, R, list(edt_node(R)), list(edt_node(R)))
 	<= annotated_trace(S, R).
-:- mode missing_answer_children_2(in, in, in, in, out) is det.
+:- mode stratum_children_2(in, in, in, in, out) is det.
 
-missing_answer_children_2(Store, NodeId, StartId, Ns0, Ns) :-
+stratum_children_2(Store, NodeId, StartId, Ns0, Ns) :-
 	det_trace_node_from_id(Store, NodeId, Node),
 	(
 		( Node = call(_, _, _, _, _, _, _, _, _)
@@ -519,15 +559,12 @@
 		; Node = cond(_, _, failed)
 		)
 	->
-		throw(internal_error("missing_answer_children_2",
+		throw(internal_error("stratum_children_2",
 			"unexpected start of contour"))
 	;
-		Node = excp(_, _, _, _, _)
-	->
-		throw(unimplemented_feature("code that catches exceptions"))
-	;
 		( Node = exit(_, _, _, _, _, _)
 		; Node = fail(_, _, _, _)
+		; Node = excp(_, _, _, _, _)
 		)
 	->
 			%
@@ -540,7 +577,8 @@
 			%
 			% There is a nested successful context.
 			%
-		wrong_answer_children(Store, Prec, NestedStartId, Ns0, Ns1)
+		contour_children(normal, Store, Prec, 
+			NestedStartId, Ns0, Ns1)
 	;
 		( Node = else(Prec, NestedStartId)
 		; Node = neg_succ(Prec, NestedStartId)
@@ -549,7 +587,7 @@
 			%
 			% There is a nested failed context.
 			%
-		missing_answer_children(Store, Prec, NestedStartId, Ns0, Ns1)
+		stratum_children(Store, Prec, NestedStartId, Ns0, Ns1)
 	;
 			%
 			% This handles the following cases:
@@ -560,103 +598,7 @@
 		Ns1 = Ns0
 	),
 	Next = step_in_stratum(Store, Node),
-	missing_answer_children(Store, Next, StartId, Ns1, Ns).
-
-:- pred unexpected_exception_children(S, R, R, list(edt_node(R)),
-		list(edt_node(R))) <= annotated_trace(S, R).
-:- mode unexpected_exception_children(in, in, in, in, out) is det.
-
-unexpected_exception_children(Store, NodeId, StartId, Ns0, Ns) :-
-	(
-		NodeId = StartId
-	->
-		Ns = Ns0
-	;
-		unexpected_exception_children_2(Store, NodeId, StartId, Ns0, Ns)
-	).
-
-:- pred unexpected_exception_children_2(S, R, R, list(edt_node(R)),
-	list(edt_node(R))) <= annotated_trace(S, R).
-:- mode unexpected_exception_children_2(in, in, in, in, out) is det.
-
-unexpected_exception_children_2(Store, NodeId, StartId, Ns0, Ns) :-
-	det_trace_node_from_id(Store, NodeId, Node),
-	(
-		( Node = call(_, _, _, _, _, _, _, _, _)
-		; Node = neg(_, _, failed)
-		; Node = cond(_, _, failed)
-		)
-	->
-		throw(internal_error("unexpected_exception_children_2",
-			"unexpected start of contour"))
-	;
-		( Node = exit(_, _, _, _, _, _)
-		; Node = excp(_, _, _, _, _)
-		)
-	->
-			%
-			% Add a child for this node.
-			%
-		Ns1 = [dynamic(NodeId) | Ns0]
-	;
-		Node = fail(_, CallId, _, _)
-	->
-			%
-			% Fail events can be reached here if there
-			% were events missing due to a parent being
-			% shallow traced.  In this case, we can't tell
-			% whether the call was in a negated context
-			% or backtracked over, so we have to assume
-			% the former.
-			%
-			% Fail events can also be reached here if the
-			% parent was a variant of solutions/2.
-			%
-			% If this really is in a negated context, the start of
-			% the context would be just before the entry to this
-			% failed call, modulo any det/semidet code which
-			% succeeded.
-			%
-		call_node_from_id(Store, CallId, Call),
-		NestedStartId = Call ^ call_preceding,
-		missing_answer_children(Store, NodeId, NestedStartId, Ns0, Ns1)
-	;
-		Node = neg_fail(Prec, NestedStartId)
-	->
-			%
-			% There is a nested context.  Neg_fail events can be
-			% reached here if there were events missing due to a
-			% parent being shallow traced.  In this case, we can't
-			% tell whether the call was in a negated context or
-			% backtracked over, so we have to assume the former.
-			%
-		wrong_answer_children(Store, Prec, NestedStartId, Ns0, Ns1)
-	;
-		( Node = else(Prec, NestedStartId)
-		; Node = neg_succ(Prec, NestedStartId)
-		)
-	->
-			%
-			% There is a nested context.
-			%
-		missing_answer_children(Store, Prec, NestedStartId, Ns0, Ns1)
-	;
-			%
-			% This handles the following cases:
-			% redo, switch, first_disj, later_disj, and
-			% then.  Also handles neg and cond when the
-			% status is anything other than failed.
-			%
-			% Redo events can be reached here if there
-			% were missing events due to a shallow tracing.
-			% In this case, we have to scan over the entire
-			% previous contour, since there is no way to
-			% tell how much of it was backtracked over.
-			%
-		Ns1 = Ns0
-	),
-	Next = step_left_in_contour(Store, Node),
-	unexpected_exception_children(Store, Next, StartId, Ns1, Ns).
+	stratum_children(Store, Next, StartId, Ns1, Ns).
 
 %-----------------------------------------------------------------------------%
 %
Index: tests/debugger/declarative/Mercury.options
===================================================================
RCS file: /home/mercury1/repository/tests/debugger/declarative/Mercury.options,v
retrieving revision 1.9
diff -u -r1.9 Mercury.options
--- tests/debugger/declarative/Mercury.options	19 Nov 2004 11:54:23 -0000	1.9
+++ tests/debugger/declarative/Mercury.options	18 Jan 2005 04:30:59 -0000
@@ -2,3 +2,4 @@
 MCFLAGS-shallow_2=--trace shallow
 MCFLAGS-tabled_read_decl=--trace rep --trace-table-io-all
 MCFLAGS-untraced_subgoal_sub=--trace minimum
+MCFLAGS-exceptions=--strict-sequential
Index: tests/debugger/declarative/Mmakefile
===================================================================
RCS file: /home/mercury1/repository/tests/debugger/declarative/Mmakefile,v
retrieving revision 1.71
diff -u -r1.71 Mmakefile
--- tests/debugger/declarative/Mmakefile	18 Jan 2005 03:56:52 -0000	1.71
+++ tests/debugger/declarative/Mmakefile	18 Jan 2005 12:19:31 -0000
@@ -23,6 +23,7 @@
 	dependency2		\
 	divide_and_query1	\
 	empty_command		\
+	exceptions		\
 	explicit_subtree	\
 	failed_cond		\
 	family			\
@@ -248,6 +249,11 @@
 
 empty_command.out: empty_command empty_command.inp
 	$(MDB) ./empty_command < empty_command.inp > empty_command.out 2>&1 \
+	|| { grep . $@ /dev/null; exit 1; }
+
+exceptions.out: exceptions exceptions.inp
+	$(MDB_STD) ./exceptions < exceptions.inp \
+		> exceptions.out 2>&1 \
 	|| { grep . $@ /dev/null; exit 1; }
 
 explicit_subtree.out: explicit_subtree explicit_subtree.$(DEBUG_INP)
Index: tests/debugger/declarative/catch.exp
===================================================================
RCS file: /home/mercury1/repository/tests/debugger/declarative/catch.exp,v
retrieving revision 1.5
diff -u -r1.5 catch.exp
--- tests/debugger/declarative/catch.exp	6 Jan 2005 03:20:11 -0000	1.5
+++ tests/debugger/declarative/catch.exp	18 Jan 2005 05:46:08 -0000
@@ -17,19 +17,24 @@
 being omitted from the trace.
 p(1, exception(univ_cons("q: bad input")))
 Valid? no
-Sorry, the diagnosis cannot continue because it requires support for
-the following: code that catches exceptions.
-The debugger is a work in progress, and this is not supported in the
-current version.
+Call q(1, _)
+Throws "q: bad input"
+Expected? no
+Found unhandled exception:
+q(1, _)
+"q: bad input"
+Is this a bug? yes
+      E4:     C3 EXCP pred catch.q/2-0 (det) e;c3; catch.m:29
+mdb> continue
 mdb: warning: reached unknown label
 This may result in some exception events
 being omitted from the trace.
       E3:     C2 EXIT pred catch.p/2-0 (cc_multi) catch.m:18 (catch.m:9)
 mdb> continue
 exception(univ_cons("q: bad input"))
-      E4:     C3 CALL pred catch.p/2-0 (cc_multi) catch.m:18 (catch.m:12)
+      E5:     C4 CALL pred catch.p/2-0 (cc_multi) catch.m:18 (catch.m:12)
 mdb> finish
-      E5:     C3 EXIT pred catch.p/2-0 (cc_multi) catch.m:18 (catch.m:12)
+      E6:     C4 EXIT pred catch.p/2-0 (cc_multi) catch.m:18 (catch.m:12)
 mdb> dd
 p(2, succeeded(2))
 Valid? no
@@ -39,6 +44,6 @@
 q(2, 2)
 p(2, succeeded(2))
 Is this a bug? yes
-      E5:     C3 EXIT pred catch.p/2-0 (cc_multi) catch.m:18 (catch.m:12)
+      E6:     C4 EXIT pred catch.p/2-0 (cc_multi) catch.m:18 (catch.m:12)
 mdb> continue
 succeeded(2)
Index: tests/debugger/declarative/catch.inp
===================================================================
RCS file: /home/mercury1/repository/tests/debugger/declarative/catch.inp,v
retrieving revision 1.1
diff -u -r1.1 catch.inp
--- tests/debugger/declarative/catch.inp	13 Sep 2002 04:17:47 -0000	1.1
+++ tests/debugger/declarative/catch.inp	4 Jan 2005 06:01:09 -0000
@@ -5,6 +5,9 @@
 finish
 dd
 no
+no
+yes
+continue
 continue
 finish
 dd
Index: tests/debugger/declarative/exceptions.exp
===================================================================
RCS file: tests/debugger/declarative/exceptions.exp
diff -N tests/debugger/declarative/exceptions.exp
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/debugger/declarative/exceptions.exp	18 Jan 2005 05:43:49 -0000
@@ -0,0 +1,95 @@
+      E1:     C1 CALL pred exceptions.main/2-0 (cc_multi) exceptions.m:13
+mdb> mdb> Contexts will not be printed.
+mdb> echo on
+Command echo enabled.
+mdb> break q
+ 0: + stop  interface pred exceptions.q/2-0 (cc_multi)
+mdb> c
+      E2:     C2 CALL pred exceptions.q/2-0 (cc_multi)
+mdb> f
+mdb: warning: reached unknown label
+This may result in some exception events
+being omitted from the trace.
+      E3:     C2 EXIT pred exceptions.q/2-0 (cc_multi)
+mdb> delete *
+ 0: E stop  interface pred exceptions.q/2-0 (cc_multi)
+mdb> dd
+mdb: warning: reached unknown label
+This may result in some exception events
+being omitted from the trace.
+q(yes(univ_cons("Error")), [1, 2, 3])
+Valid? n
+p(1)
+Valid? y
+p(2)
+Valid? y
+p(3)
+Valid? y
+Call p(_)
+Throws "Error"
+Expected? y
+Found incorrect contour:
+q(yes(univ_cons("Error")), [1, 2, 3])
+Is this a bug? y
+mdb: warning: reached unknown label
+This may result in some exception events
+being omitted from the trace.
+      E3:     C2 EXIT pred exceptions.q/2-0 (cc_multi)
+mdb> break r
+ 0: + stop  interface pred exceptions.r/1-0 (semidet)
+mdb> c
+      E4:     C3 CALL pred exceptions.r/1-0 (semidet)
+mdb> f
+mdb: warning: reached unknown label
+This may result in some exception events
+being omitted from the trace.
+      E5:     C3 FAIL pred exceptions.r/1-0 (semidet)
+mdb> delete *
+ 0: E stop  interface pred exceptions.r/1-0 (semidet)
+mdb> dd
+mdb: warning: reached unknown label
+This may result in some exception events
+being omitted from the trace.
+Call r(_)
+No solutions.
+Complete? n
+t({yes(univ_cons("Error")), [4, 5, 6]})
+Valid? n
+s(4)
+Valid? y
+s(5)
+Valid? y
+s(6)
+Valid? y
+Call s(_)
+Throws "Error"
+Expected? y
+Found incorrect contour:
+t({yes(univ_cons("Error")), [4, 5, 6]})
+Is this a bug? y
+mdb: warning: reached unknown label
+This may result in some exception events
+being omitted from the trace.
+      E6:     C4 EXIT pred exceptions.t/1-0 (cc_multi)
+mdb> break v
+ 0: + stop  interface pred exceptions.v/1-0 (nondet)
+mdb> c
+no
+      E7:     C5 CALL pred exceptions.v/1-0 (nondet)
+mdb> f
+      E8:     C5 EXCP pred exceptions.v/1-0 (nondet) c2;
+mdb> dd
+Call v(_)
+Throws "Error"
+Expected? n
+y(1)
+Valid? y
+Call u(_)
+Throws "Error"
+Expected? y
+Found unhandled exception:
+v(_)
+"Error"
+Is this a bug? y
+      E8:     C5 EXCP pred exceptions.v/1-0 (nondet) c2;
+mdb> quit -y
Index: tests/debugger/declarative/exceptions.inp
===================================================================
RCS file: tests/debugger/declarative/exceptions.inp
diff -N tests/debugger/declarative/exceptions.inp
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/debugger/declarative/exceptions.inp	18 Jan 2005 05:42:23 -0000
@@ -0,0 +1,35 @@
+register --quiet
+context none
+echo on
+break q
+c
+f
+delete *
+dd
+n
+y
+y
+y
+y
+y
+break r
+c
+f
+delete *
+dd
+n
+n
+y
+y
+y
+y
+y
+break v
+c
+f
+dd
+n
+y
+y
+y
+quit -y
Index: tests/debugger/declarative/exceptions.m
===================================================================
RCS file: tests/debugger/declarative/exceptions.m
diff -N tests/debugger/declarative/exceptions.m
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/debugger/declarative/exceptions.m	18 Jan 2005 05:39:39 -0000
@@ -0,0 +1,84 @@
+:- module exceptions.
+
+:- interface.
+
+:- import_module io.
+
+:- pred main(io::di, io::uo) is cc_multi.
+
+:- implementation.
+
+:- import_module int, exception, std_util, list.
+
+main(!IO) :-
+	% Test finding wrong answer children with a try_all.
+	q(MaybeExcp, Solutions),
+	(
+		% Test finding missing answer children with a try_all.
+		r(_)
+	->
+		io.write_string("yes\n", !IO)
+	;
+		io.write_string("no\n", !IO)
+	),
+	(
+		% Test finding exception children when there is backtracking.
+		v(X)
+	->
+		io.write_int(X, !IO)
+	;
+		io.write_string("no\n", !IO)
+	),
+	io.write({MaybeExcp, Solutions}, !IO),
+	io.nl(!IO).
+
+:- pred p(int::out) is multi.
+
+p(X) :- X = 1 ; X = 2 ; X = 3 ; throw("Error").
+
+:- pred q(maybe(univ)::out, list(int)::out) is cc_multi.
+
+q(MaybeExcp, Solutions) :-
+	try_all(p, MaybeExcp, Solutions).
+
+:- pred r({maybe(univ), list(int)}::out) is semidet.
+
+r(Sols) :-
+	% This is a lie, but is the only way I seem to be able to call try_all 
+	% in a failing context.
+	Sols = promise_only_solution(t),
+	semidet_fail.
+
+:- pred s(int::out) is multi.
+
+s(X) :- X = 4 ; X = 5 ; X = 6 ; throw("Error").
+
+:- pred t({maybe(univ), list(int)}::out) is cc_multi.
+
+t(S) :-
+	try_all(s, MaybeExcp, Solutions),
+	S = {MaybeExcp, Solutions}.
+
+:- pred u(int::out) is multi.
+
+u(X) :- X = 7 ; X = 8 ; X = 9 ; throw("Error").
+
+:- pred v(int::out) is nondet.
+
+v(X) :-
+	y(Z),
+	u(Y),
+	x(Y),
+	add(Y, Z, X).
+
+:- pred x(int::in) is semidet.
+
+x(1).
+
+:- pred add(int::in, int::in, int::out) is det.
+
+add(X, Y, X + Y).
+
+:- pred y(int::out) is det.
+
+y(1).
--------------------------------------------------------------------------
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