[m-rev.] for review: divide and query search for declarative debugger

Ian MacLarty maclarty at cs.mu.OZ.AU
Fri Dec 31 17:02:40 AEDT 2004


On Thu, Dec 30, 2004 at 04:55:17PM +1100, Mark Brown wrote:
> > 
> > 	Add some functions to set the default search mode by calling the
> > 	predicate exported from declarative_debugger.m
> > 
> > 	Add a function to check in a search mode argument string is valid.
> 
> s/in a/that the/
> 

Fixed.

> > Index: browser/declarative_analyser.m
> > ===================================================================
> > RCS file: /home/mercury1/repository/mercury/browser/declarative_analyser.m,v
> > retrieving revision 1.17
> > diff -u -r1.17 declarative_analyser.m
> > --- browser/declarative_analyser.m	16 Dec 2004 00:12:38 -0000	1.17
> > +++ browser/declarative_analyser.m	21 Dec 2004 10:48:05 -0000
> > @@ -188,6 +214,12 @@
> >  				% oracle.
> >  			search_mode		:: search_mode,
> >  				
> > +				% The search mode to use by default. 
> > +				% This uses a different type since only
> > +				% non-parametized search modes can sensibly be
> 
> s/parametized/parametrized/
> 

Fixed.

> I think it would be clearer to use the same type for both, and leave it
> as an invariant that the default mode would only take certain values.
> Then you wouldn't need the 'search_mode_from_default' function below.
> 

I've made the change.

I've also renamed the default_search_mode field to fallback_search_mode which
hopefully also resolves some of your issues near the end of this review.

> > -		revise_root(SearchSpace, SearchSpace1),
> > +		revise_root(Store, SearchSpace, SearchSpace1),
> >  		!:Analyser = !.Analyser ^ search_space := SearchSpace1,
> >  		!:Analyser = !.Analyser ^ last_search_question := yes(RootId),
> > -		!:Analyser = !.Analyser ^ search_mode := top_down
> > +		set_default_search_mode(!.Analyser ^ default_search_mode,
> > +			!Analyser)
> 
> That's a little confusing, since it looks like the above call should be
> a no-op.  Perhaps add a new predicate set_search_mode_to_default/2 which
> just moves the default search mode into the current search mode.  This
> new predicate could be called from set_default_search_mode/3, since that
> predicate also sets the current search mode.
> 

Since they are now the same type I've changed the call to an assignment which
should be clearer.

> >  	;
> > -		%
> >  		% There must be a root, since a bug was found (and is now
> >  		% being revised).
> > -		%
> >  		throw(internal_error("revise_analysis", "no root"))
> >  	).
> >  
> > @@ -354,6 +398,9 @@
> >  	is det <= mercury_edt(S, T).
> >  
> >  decide_analyser_response(Store, Response, !Analyser) :-
> > +	% Check an invarients that should hold for the search space.
> 
> s/an invarients that should hold/the invariants/
> 
> In any case this comment is redundant, since the documentation for
> check_search_space_consistency already describes what it does.  If you want
> to put a comment here it should state why you do the sanity check here --
> that is, mention what could have gone wrong.
> 

Okay I've changed the comment to:
        % Do a sanity check before the search, so we can determine afterwards
        % if the search corrupted the search space.  If the search space is
        % corrupted at this point then the corruption must have occured in
        $ process_answer.
        % XXX this should be removed at some stage as it's relatively slow.

> > +	check_search_space_consistency(Store, !.Analyser ^ search_space,
> > +		"Start of decide_analyser_response"),
> >  	some [!SearchSpace] (
> >  		!:SearchSpace = !.Analyser ^ search_space,
> >  		(
> > @@ -409,7 +457,11 @@
> >  				)
> >  			)
> >  		)
> > -	).
> > +	),
> > +	% Check an invarients that should hold for the search space.
> 
> Same comment applies here as above.
> 

I changed the comment here to:
	% Do a sanity check after the search to determine if the search 
	% corrupted the search space at all. 
	% XXX this should be removed at some stage as it's relatively slow.

> > +
> > +	% find_middle_weight(Store, SuspectIds, TopId, MaybeLastUnknown,
> > +	%	!SearchSpace, Response).
> > +	% Find the suspect that splits the portion of the search space rooted
> > +	% at TopId into roughly equal portions by weight.  SuspectIds is 
> 
> Don't use "roughly"; be more specific about the meaning of this predicate.
> For example, you could add the sentence:
> 
> 	The weight of the chosen suspect will be as close to half the
> 	weight of TopId as any other suspect being considered.
> 
I've changed the comment to the following:
	% Find the first unknown suspect in the descendents of SuspectIds whose
	% weight is less than or equal to half the weight of TopId.  This is 
	% done by considering the heaviest suspect in SuspectIds and then the
	% heaviest child of the heaviest suspect in SuspectId and so on.
	% MaybeLastUnknown is the last node that was unknown in the search (if
	% any).  

> > +	->
> > +		(
> > +			children(Store, Heaviest, !SearchSpace, Children)
> > +		->
> > +			(
> > +				suspect_unknown(!.SearchSpace, Heaviest)
> > +			->
> > +				NewMaybeLastUnknown = yes(Heaviest)
> > +			;
> > +				NewMaybeLastUnknown = MaybeLastUnknown
> > +			),
> > +			find_middle_weight(Store, Children, TopId,
> > +				NewMaybeLastUnknown, !SearchSpace, Response)
> > +		;
> > +			Response = require_explicit_subtree(Heaviest)
> > +		)
> 
> Note that this if-then-else is quite similar to one in divide_and_query_search
> and one below.  The code would be simpler to read if you factor out the common
> code.  (This may require an extra map__search in the case that an explicit
> subtree is required, but readability is arguably more valuable than efficiency
> in this case.)
> 

That's a good point - I never noticed that.  I have added the following 
predicate and used it instead of the if-then-else. 

	% Call find_middle_weight/7 if we are able to find the children of the
	% given suspect id, otherwise return a require_explicit_subtree
	% search response in the last argument.
	%
:- pred find_middle_weight_if_children(S::in, suspect_id::in,
	maybe(suspect_id)::in, search_space(T)::in, search_space(T)::out,
	search_response::out) is det <= mercury_edt(S, T).

find_middle_weight_if_children(Store, SuspectId, MaybeLastUnknown,
		!SearchSpace, Response) :-
	(
		children(Store, SuspectId, !SearchSpace, Children)
	->
		find_middle_weight(Store, Children, SuspectId,
			MaybeLastUnknown, !SearchSpace, Response)
	;
		Response = require_explicit_subtree(SuspectId)
	).

> > +	% Start doing a default search of the search space.
> > +	%
> > +:- pred start_default_search(default_search_mode::in, S::in, 
> > +	search_space(T)::in, search_space(T)::out,
> > +	search_response::out, search_mode::out) is det <= mercury_edt(S, T).
> 
> For consistency, the argument order for this predicate should match that of
> search/6 (if you still need this predicate after addressing my above remarks).

This predicate is not necessary now that I've made search_mode and 
default_search_mode the same type, so I've removed it and used search/6
instead.

> >  		%
> > -	pred edt_topmost_node(S::in, T::in) is semidet
> > +	pred edt_topmost_node(S::in, T::in) is semidet,
> > + 
> > + 		% edt_weight(Store, Node, Weight, ExcessWeight).
> > +		% True if Weight is the weight of Node.  ExcessWeight is
> > +		% some extra weight that should be added to the ancestors of
> > +		% Node because the sum of the weights of the Node and its
> > +		% siblings might otherwise be bigger than Node's parent's 
> > +		% weight.  For example if the number of events in descendent
> > +		% nodes is being used as a weight, then for a FAIL node
> > +		% some events may be repeated in siblings of the FAIL node.
> > +		% In this case the number of duplicate events should be
> > +		% returned in ExcessWeight so they can be added to the
> > +		% ancestors.
> > + 		%
> > + 	pred edt_weight(S::in, T::in, int::out, int::out) is det
> 
> The concept of the weight of a node needs to be specified clearly -- I suggest
> you add to the comments at the top of this file.  In these comments you should
> also delineate any invariants that are assumed by the implementation (e.g.
> by the new code in declarative_analyser.m), in particular that the weight
> of a node must not be exceeded by the combined weight of its children.
> 

I've added the following comment to the top of the file:
%
% Each suspect in the search space can be assigned a weight to be used for
% divide and query search.  Any heuristic can be used, as long as the combined
% weight of all the children of a suspect does not exceed the suspect's own
% weight.  Sometimes the weight may depend on the weights of unmaterialized
% portions of the EDT resulting in the situation where the combined weight of
% the children of a suspect exceeds the parent's weight.  If this happens then
% an "excess weight" may be specified along with the normal weight which will
% be added to all the ancestor's of the overweight suspect.  For example if the
% number of events in descendent suspects is being used as a weight, then for a
% FAIL node some events may be repeated in siblings of the FAIL node.  In this
% case the duplicate events might not have been included in the ancestor's
% weights, so should be added.
%

And changed the comment above edt_weight/4 to:
		% Find the weight and excess weight for a node.  See the 
		% comment at the top of this module for the meaning of 
		% the weight of a node.
		%

> > @@ -729,6 +756,9 @@
> >  		adjust_unexplored_leaves(yes(Suspect ^ status), Status, 
> >  			!SearchSpace)
> >  	),
> > +	% Remove the suspect's weight from it's ancestors, since its weight is
> 
> s/it's/its/
> 

If only I had a dollar for each "its" I've got wrong... must have some
hardcoding in my brain somewhere...

> > +	% now zero.
> 
> It appears that the weight field does not actually get set to zero, even
> though the weight is considered to be zero at this point.  You should document
> above that the weight field doesn't contain a meaningful value if the suspect
> is valid.
> 

It IS set to zero near the top of the predicate:

+	map.set(!.SearchSpace ^ store, SuspectId, 
+		(Suspect ^ status := Status) ^ weight := 0, SuspectStore),

> > +	add_weight_to_ancestors(SuspectId, - Suspect ^ weight, !SearchSpace),
> >  	%
> >  	% If the suspect was erroneous or excluded because of another erronoeus
> >  	% suspect, then we should update the complement of the subtree rooted
> > @@ -770,32 +800,24 @@
> >  		adjust_unexplored_leaves(yes(Suspect ^ status), erroneous, 
> >  			!SearchSpace)
> >  	;
> > -		Suspect ^ children = yes(Children),
> > -		%
> > -		% If the suspect was correct, inadmissible or pruned then we
> > -		% should make all the descendents unknown again.
> > -		%
> > -		(
> > -			excluded_subtree(Suspect ^ status, yes)
> > -		->
> > -			list.foldl(propagate_status_downwards(unknown, 
> > -				[correct, inadmissible]), Children,
> > -				!SearchSpace)
> > -		;
> > -			true
> > -		)
> > +		Suspect ^ children = yes(_)
> >  	),
> > -	propagate_status_upwards(in_erroneous_subtree_complement, [erroneous], 
> > -		SuspectId, _, !SearchSpace),
> > +	propagate_status_upwards(in_erroneous_subtree_complement, 
> > +		[erroneous, correct, inadmissible], SuspectId, _,
> > +		!SearchSpace),
> >  	!:SearchSpace = !.SearchSpace ^ root := yes(SuspectId).
> 
> I don't understand these changes to assert_suspect_is_erroneous.  Could you
> please document it in the log message, or add comments to the code here, or
> preferably both?
> 

I've added the following to the CVS log:

	Remove some code that will never be executed in 
	assert_suspect_is_erroneous/3.  The code handles a case when 
	a correct or inadmissible suspect is marked erroneous.  This can
	only happen when a search is being revised in which case the
	correct or erroneous suspect would be marked unknown.

	When marking suspects as in the complement of an erroneous subtree
	stop marking if a correct or inadmissible node is encountered since
	descendents of these will already have been removed from the bug
	search.

> > @@ -804,27 +826,44 @@
> >  		skipped(N), Store),
> >  	!:SearchSpace = !.SearchSpace ^ store := Store.
> >  
> > -revise_root(!SearchSpace) :-
> > +revise_root(Store, !SearchSpace) :-
> >  	(
> >  		!.SearchSpace ^ root = yes(RootId),
> >  		force_propagate_status_downwards(unknown, 
> > -			[correct, inadmissible], RootId, Leaves, !SearchSpace),
> > -		list.foldl(force_propagate_status_downwards(unknown, [correct,
> > -			inadmissible]), Leaves, !SearchSpace),
> > -		propagate_status_upwards(unknown, [erroneous], RootId, Lowest, 
> > +			[correct, inadmissible], RootId, StopSuspects, 
> >  			!SearchSpace),
> > -		(
> > -			suspect_erroneous(!.SearchSpace, Lowest)
> > -		->
> > +		list.foldl(force_propagate_status_downwards(unknown, [correct,
> > +			inadmissible]), StopSuspects, !SearchSpace),
> > +		propagate_status_upwards(unknown, [erroneous, correct,
> > +			inadmissible], RootId, Lowest, !SearchSpace),
> > +		( suspect_erroneous(!.SearchSpace, Lowest) ->
> >  			!:SearchSpace = !.SearchSpace ^ root := yes(Lowest)
> >  		;
> >  			!:SearchSpace = !.SearchSpace ^ root := no
> > -		)
> > +		),
> > +		%
> > +		% Recompute the suspect weights from the bottom up.
> > +		%
> > +		map.keys(!.SearchSpace ^ store, AllSuspects),
> > +		list.filter(suspect_is_leaf(!.SearchSpace), AllSuspects, 
> > +			Leaves),
> > +		recalc_weights_upto_ancestor(Store, Lowest, Leaves, 
> > +			!SearchSpace)
> >  	;
> >  		!.SearchSpace ^ root = no,
> >  		throw(internal_error("revise_root", "no root"))
> >  	).
> 
> Likewise I don't fully understand the changes to revise_root.  The comment
> on the declaration of it probably needs to be updated.  I'll review these
> parts of the change after you post a relative diff.
> 

The only differences are that I changed a variable named Leaves to 
StopSuspects, reformatted an if-then-else and added the bit that recomputes the
weights of the suspects.

> > @@ -979,24 +1018,22 @@
> >  			"couldn't find suspect"))
> >  	).
> >  
> > -	% propagate_status_downwards(Status, StopStatusSet, SuspectId, Leaves, 
> > -	%	!SearchSpace). 
> > +	% propagate_status_downwards(Status, StopStatusSet, SuspectId, 
> > +	%	StopSuspects, !SearchSpace). 
> >  	% Sets the status of SuspectId and all it's descendents to Status.
> >  	% If a descendent (including the suspect) already has a status in
> >  	% StopStatusSet then propagate_status_downwards won't update any
> >  	% further descendents.  The list of all the children of the lowest
> > -	% updated suspects is returned in Leaves.
> > +	% updated suspects is returned in StopSuspects.
> >  	% 
> 
> The change of variable name from Leaves to StopSuspects here and below is okay,
> but probably should be mentioned in the log message.

Okay:
	Renamed the variable Leaves to StopSuspects in
	propagate_status_downwards, since the value of this variable is the
	list of the children of the lowest updated suspects which may or may
	not be leaves.
> 
> > @@ -1008,12 +1045,14 @@
> >  	propagate_status_downwards(Status, StopStatusSet, SuspectId, _, 
> >  		!SearchSpace).
> >  
> > +	% An accumulator version of propagate_status_downwards.
> > +	%
> >  :- pred propagate_status_downwards(suspect_status::in, 
> >  	list(suspect_status)::in, suspect_id::in, 
> >  	list(suspect_id)::in, list(suspect_id)::out, 
> >  	search_space(T)::in, search_space(T)::out) is det.
> 
> The conventional name for such a predicate would be
> propagate_status_downwards_2, by the way.
> 

I prefer to use this convention only when the predicate is just called from
the predicate with the same name but without the "_2".  In this case 
the accumulator version of propagate_status_downwards is also called from
force_propagate_status_downwards.

> > @@ -1169,9 +1208,157 @@
> >  			++ string(SearchSpace) ++ "\n Context is:\n" ++
> >  			Context))
> >  	;
> > +		check_search_space_weights(Store, SearchSpace)
> > +	->
> > +		% check_search_space_weights will never actually fail, but
> > +		% will throw an exception if the weights are inconsistent.
> 
> See my comment below.
> 
> > +		true
> > +	;
> >  		true
> >  	).
> > @@ -1191,11 +1378,59 @@
> >  calc_num_unexplored(SearchSpace) = NumUnexplored :-
> >  	Suspects = map.values(SearchSpace ^ store),
> >  	list.filter(
> > -		( pred(suspect(_, _, Status, _, no)::in) is semidet :- 
> > +		( pred(suspect(_, _, Status, _, no, _)::in) is semidet :- 
> >  			in_buggy_subtree(Status, yes)
> >  		), Suspects, Unexplored),
> >  	NumUnexplored = list.length(Unexplored).
> >  
> > +	% Check that the weights in the search space are correct and throw
> > +	% an exception if they aren't.
> > +	%
> > +:- pred check_search_space_weights(S::in, search_space(T)::in) 
> > +	is semidet <= mercury_edt(S, T).
> 
> This predicate isn't really semidet; presumably you have made it semidet
> so that the compiler won't optimise it away.  It would be better to write
> a predicate called, say, find_inconsistency_in_weights that fails if there
> is no inconsistency and succeeds with some suitable output if there is
> one.  Then let the caller construct the exception value and throw it if
> required.

That would be neater:

	% Try to find an inconsistency in the weights of the suspects.  If one
	% is found output an error message, otherwise fail.
	%
:- pred find_inconsistency_in_weights(S::in, search_space(T)::in, 
	string::out) is semidet <= mercury_edt(S, T).

find_inconsistency_in_weights(Store, SearchSpace, Message) :-
	( root(SearchSpace, RootId) ->
		find_inconsistency_in_weights_2(Store, SearchSpace, 
			RootId, Message)
	;
		topmost_det(SearchSpace, TopMostId),
		find_inconsistency_in_weights_2(Store, SearchSpace, 
			TopMostId, Message)
	).

	% Check that the weights are correct from the given suspect down.
	%
:- pred find_inconsistency_in_weights_2(S::in, search_space(T)::in,
	suspect_id::in, string::out) is semidet <= mercury_edt(S, T).

find_inconsistency_in_weights_2(Store, SearchSpace, SuspectId, Message) :-
	lookup_suspect(SearchSpace, SuspectId, Suspect),
	calc_suspect_weight(Store, Suspect ^ edt_node, Suspect ^ children,
		Suspect ^ status, SearchSpace, Weight, _),
	(
		Weight = Suspect ^ weight,
		Weight >= 0
	->
		Suspect ^ children = yes(Children),
		in_buggy_subtree(Suspect ^ status, yes),
		list.filter_map(find_inconsistency_in_weights_2(Store, 
			SearchSpace), Children, Messages),
		Messages = [Message | _]
	;
		Message = "Weights not consistent for suspect id " ++
			int_to_string(SuspectId) ++ ", Suspect = " ++ 
			string(Suspect) ++ " Calculated weight = " ++
			int_to_string(Weight)
	).
> 
> > Index: browser/declarative_tree.m
> > ===================================================================
> > RCS file: /home/mercury1/repository/mercury/browser/declarative_tree.m,v
> > retrieving revision 1.11
> > diff -u -r1.11 declarative_tree.m
> > --- browser/declarative_tree.m	16 Dec 2004 00:12:39 -0000	1.11
> > +++ browser/declarative_tree.m	21 Dec 2004 11:30:35 -0000
> > @@ -1,5 +1,5 @@
> >  %-----------------------------------------------------------------------------%
> > -% Copyright (C) 2002-2004 The University of Melbourne.
> > +% Copyright (C) 2002-2003 The University of Melbourne.
> >  % This file may only be copied under the terms of the GNU Library General
> >  % Public License - see the file COPYING.LIB in the Mercury distribution.
> >  %-----------------------------------------------------------------------------%
> 
> Wrong year, although the check-in script should fix this for you.
> 

I'm not sure why this got changed - I never changed it manually.  Would be nice to 
hear a possible explanation as this seems to happen from time to time, although
the check-in script does fix it.

> > @@ -284,6 +285,94 @@
> >  trace_is_implicit_root(wrap(Store), dynamic(Ref)) :-
> >  	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).
> > +
> > +trace_weight(Store, NodeId, Weight, 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
> > +	% internal body events for the call.  Also return the number of events
> > +	% that could be duplicated in siblings of the node in the EDT if the 
> > +	% node is a FAIL event.
> 
> Add an extra line break.
> 

Done.

> > +	% 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
> > +	% 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.
> > +	%
> > +	% node_events(Store, Node, PrevEvents, Events, RecordDups,
> > +	%	DupFactor, PrevDupEvents, DupEvents)
> > +	% True iff Events is the (conservative approximation of) the number of
> > +	% descendent events of Node and DupEvents is the number of events that
> > +	% could be duplicated in siblings.  PrevEvents and PrevDupEvents are
> > +	% accumlators which should initially be zero.  RecordDups keeps track
> 
> s/accumlators/accumulators/
> 

Fixed.

> > Index: doc/user_guide.texi
> > ===================================================================
> > RCS file: /home/mercury1/repository/mercury/doc/user_guide.texi,v
> > retrieving revision 1.404
> > diff -u -r1.404 user_guide.texi
> > --- doc/user_guide.texi	20 Dec 2004 01:15:48 -0000	1.404
> > +++ doc/user_guide.texi	21 Dec 2004 11:44:21 -0000
> > @@ -3256,7 +3257,7 @@
> >  @ref{Declarative debugging} for details.
> >  @sp 1
> >  @table @code
> > - at item dd
> > + at item dd [-d at var{depth} -s at var{strategy}]
> 
> The options are independently optional, so that should be:
> 
> @item dd [-d at var{depth}] [-s at var{strategy}]
> 

Yup.

> >  @c @item dd [--assume-all-io-is-tabled]
> >  @c The --assume-all-io-is-tabled option is for developers only. Specifying it
> >  @c makes an assertion, and if the assertion is incorrect, the resulting
> > @@ -3273,6 +3274,18 @@
> >  declarative debugger for long running programs since it will not have to rerun
> >  the program as much.
> >  @sp 1
> > +The @samp{-s at var{strategy}} or @samp{--default-search-mode
> 
> Either call it a search mode or a search strategy, don't switch between the
> two.
> 

Okay will use "mode" as that's what's used in the code.

> > + at var{strategy}} option tells the declarative debugger which 
> > +search strategy to use by default.
> 
> Either explain precisely what is meant by "default" here, or avoid the
> term altogether and just say that the option tells the debugger which search
> strategy to use.  (Also, see my comments below.)
> 

Left out the word "default".

> Either @samp{top-down} or 
> > + at samp{divide-and-query} may be specified.
> 
> Give a cross reference to the section on search strategies.  In fact, if you
> do this then the brief explanation of the strategies that you give here
> should probably be removed.
> 

Okay.

> @samp{top-down} search is more
> > +predicable and will ask you about the children of the last atom you
> 
> s/predicable/predictable/
> 

Fixed.

> > +asserted was erroneous (i.e. gave a `no' answer for), however this may
> > +mean that lots of questions will need to be answered before a bug is located.  
> > + at samp{divide-and-query} search tries to ask questions that will halve the
> > +search space with each answer resulting in quicker localization of the bug,
> > +however the questions asked may appear unrelated to each other.  
> > + at samp{top-down} is the default when this option is not given.
> 
> The use of the term "default" here is what I would normally understand it
> to mean.  Hence the use of the term "default" above (and indeed in the code
> itself), which has a different sense, is a bit confusing and I would try to
> avoid it.
> 

I have renamed the concept to "fallback search mode" in the code and have
removed "default" from the documentation, except here.

> > + at sp 1
> >  @item trust @var{module-name}|@var{proc-spec}
> >  @kindex trust (mdb command)
> >  Tells the declarative debugger to trust the given module, predicate or
> > @@ -3883,6 +3897,36 @@
> >  If the user aborts the diagnosis,
> >  they are returned to the event at which the @samp{dd} command was given.
> >  
> > + at node Search Strategies
> > + at subsection Search Strategies
> > +
> > +Currently the declarative debugger can employ one of two strategies when
> > +searching for a bug.  The initial strategy to use can be specified
> 
> "Initial" is better than "default".  However, you should explain why it is
> only the initial strategy (that is, point out that the strategy may
> automatically change to top-down if the current strategy is no longer
> applicable).
> 

Removed word "initial" and added the following:

The specified search mode will always be used
unless a sub-term is marked or the user hasn't answered `no' to any questions
yet (In which case top-down search is used until `no' is answered to at least
one question).

> > +as an option to the @samp{dd} command.  See 
> > + at ref{Declarative debugging mdb commands} for information on how to do this.
> > +
> > + at subsubsection Top-down Search
> > +
> > +Using this strategy the declarative debugger will ask about the children
> > +of the last atom who's assertion was false.  This makes the search more
> 
> s/who's/whose/
> 

Fixed.

> > +predictable from the user's point of view as the questions will more
> > +or less follow the program execution.  The drawback of top-down search is that
> > +it may require a lot of questions to be answered before a bug is found, 
> > +especially with deeply recursive program runs.  
> > +
> > +This search strategy is used by default when no other strategy is specified.
> > +
> > + at subsubsection Divide and Query Search
> > +
> > +With this strategy the declarative debugger will attempt to halve the size of
> > +the search space with each question.  In most cases this will result in the 
> 
> Can you really claim "most" here?  It would depend on the kind of programs
> being written.  "Many" would be a safer claim than "most".
> 

I'm sure most is probably correct here, since it might not be O(log(N)) only
when the code is nondeterministic, which is quite rare.  Have changed to
"many" anyway.

> > +bug being found after log(N) questions where N is the number of events
> 
> That should be O(log(N)).
> 

Right.

> >  
> >  This feature is also useful when using the procedural debugger.  For example,
> > -suppose that you come across a CALL event and you would like to know the source
> > -of a particular input to the call.  To find out you could first go to the final
> > -event by issuing a @samp{finish} command.  Invoke the declarative debugger with
> > -a @samp{dd} command and then mark the input term you are interested in.  The
> > -next question should be about the call that bound the term.  Issue a @samp{pd}
> > -command at this point to return to the procedural debugger. It will now show
> > -the final event of the call that bound the term.
> > +suppose that you come across a @samp{CALL} event and you would like to know the
> > +source of a particular input to the call.  To find out you could first go to
> > +the final event by issuing a @samp{finish} command.  Invoke the declarative
> > +debugger with a @samp{dd} command and then mark the input term you are
> > +interested in.  The next question should be about the call that bound the term.
> > +Issue a @samp{pd} command at this point to return to the procedural debugger.
> > +It will now show the final event of the call that bound the term.
> >  
> >  @subsubsection Trusting predicates, functions and modules
> >  
> 
> This part of the change is not mentioned in the log message.
> 

Added to log:
Put @samp{} around CALL.

> > Index: trace/mercury_trace_internal.c
> > ===================================================================
> > RCS file: /home/mercury1/repository/mercury/trace/mercury_trace_internal.c,v
> > retrieving revision 1.184
> > diff -u -r1.184 mercury_trace_internal.c
> > --- trace/mercury_trace_internal.c	16 Dec 2004 00:12:41 -0000	1.184
> > +++ trace/mercury_trace_internal.c	16 Dec 2004 00:28:48 -0000
> > @@ -5510,10 +5512,19 @@
> >  	MR_Event_Info *event_info, MR_Event_Details *event_details,
> >  	MR_Code **jumpaddr)
> >  {
> > +	MR_Decl_Default_Search_Mode	default_search_mode;
> > +
> >  	MR_trace_decl_assume_all_io_is_tabled = MR_FALSE;
> >  	MR_edt_depth_step_size = MR_TRACE_DECL_INITIAL_DEPTH;
> > +	if (! MR_trace_is_valid_search_mode_string("top_down", 
> > +			&default_search_mode))
> > +	{
> > +		MR_fatal_error("MR_trace_cmd_dd: top_down invalid");
> > +	}
> 
> That's a roundabout way of doing it.  Why not export a function from
> mercury_trace_declarative that returns the default, instead of doing
> a string comparison each time?
> 

Okay, have done that.

> > +		
> >  	if (! MR_trace_options_dd(&MR_trace_decl_assume_all_io_is_tabled,
> > -		&MR_edt_depth_step_size, &words, &word_count, "dd", "dd"))
> > +		&MR_edt_depth_step_size, &default_search_mode,
> > +		&words, &word_count, "dd", "dd"))
> >  	{
> >  		; /* the usage message has already been printed */
> >  	} else if (word_count == 1) {
> > @@ -5544,11 +5557,19 @@
> >  {
> >  	MR_Trace_Mode	trace_mode;
> >  	const char	*filename;
> > +	MR_Decl_Default_Search_Mode	default_search_mode;
> >  
> >  	MR_trace_decl_assume_all_io_is_tabled = MR_FALSE;
> > -	MR_edt_depth_step_size = 3;
> > +	MR_edt_depth_step_size = MR_TRACE_DECL_INITIAL_DEPTH;
> > +	if (! MR_trace_is_valid_search_mode_string("top_down",
> > +			&default_search_mode))
> > +	{
> > +		MR_fatal_error("MR_trace_cmd_dd_dd: top_down invalid");
> > +	}
> 
> Ditto.
> 

Done.

Here is a diff of the changes I've done since my original post:

Diffing .
Diffing analysis
Diffing bindist
Diffing boehm_gc
Diffing boehm_gc/Mac_files
Diffing boehm_gc/cord
Diffing boehm_gc/cord/private
Diffing boehm_gc/doc
Diffing boehm_gc/include
Diffing boehm_gc/include/private
Diffing boehm_gc/tests
Diffing browser
--- /home/jupiter/maclarty/ws50_1/browser/declarative_analyser.m	2004-12-31 16:47:00.000000000 +1100
+++ declarative_analyser.m	2004-12-31 16:35:46.000000000 +1100
@@ -51,12 +51,11 @@
 
 :- type analyser_state(T).
 
-	% The default search mode for the analyser.  The analyser will revert
-	% to this search mode if not told to do otherwise by the oracle.
-	%
-:- type default_search_mode 
-	--->	top_down
-	;	divide_and_query.
+:- type search_mode.
+
+:- func divide_and_query_search_mode = search_mode.
+
+:- func top_down_search_mode = search_mode.
 
 :- pred analyser_state_init(io_action_map::in, analyser_state(T)::out) is det.
 
@@ -64,10 +63,10 @@
 	%
 :- pred reset_analyser(analyser_state(T)::in, analyser_state(T)::out) is det.
 
-	% Make the given default search mode the default search mode
+	% Make the given search mode the fallback search mode
 	% and the current search mode for the analyser.
 	%
-:- pred set_default_search_mode(default_search_mode::in, 
+:- pred set_fallback_search_mode(search_mode::in, 
 	analyser_state(T)::in, analyser_state(T)::out) is det.
 
 :- pred analyser_state_replace_io_map(io_action_map::in,
@@ -184,6 +183,10 @@
 			%
 		divide_and_query.
 
+divide_and_query_search_mode = divide_and_query.
+
+top_down_search_mode = top_down.
+
 	% Each search algorithm should respond with either a question
 	% or a request for an explicit subtree to be generated for a suspect 
 	% which is the root of an implicit subtree.
@@ -215,10 +218,9 @@
 			search_mode		:: search_mode,
 				
 				% The search mode to use by default. 
-				% This uses a different type since only
-				% non-parametized search modes can sensibly be
-				% used as the default search mode.
-			default_search_mode	:: default_search_mode,
+				% Only non-parametrized search modes should
+				% be used as the fallback search mode.
+			fallback_search_mode	:: search_mode,
 
 				% Everytime a search finds a suspect to
 				% ask the oracle about it is put in this field
@@ -254,20 +256,13 @@
 		top_down, no, IoActionMap, no).
 
 reset_analyser(!Analyser) :-
-	Default = !.Analyser ^ default_search_mode,
-	search_mode_from_default(Default) = SearchMode,
-	!:Analyser = analyser(empty_search_space, no, SearchMode, 
-		Default, no, !.Analyser ^ io_action_map, no).
-
-set_default_search_mode(DefaultSearchMode, !Analyser) :-
-	!:Analyser = !.Analyser ^ default_search_mode := DefaultSearchMode,
-	!:Analyser = !.Analyser ^ search_mode := 
-		search_mode_from_default(DefaultSearchMode).
-
-:- func search_mode_from_default(default_search_mode) = search_mode.
-
-search_mode_from_default(top_down) = top_down.
-search_mode_from_default(divide_and_query) = divide_and_query.
+	FallBack = !.Analyser ^ fallback_search_mode,
+	!:Analyser = analyser(empty_search_space, no, FallBack, 
+		FallBack, no, !.Analyser ^ io_action_map, no).
+
+set_fallback_search_mode(FallBackSearchMode, !Analyser) :-
+	!:Analyser = !.Analyser ^ fallback_search_mode := FallBackSearchMode,
+	!:Analyser = !.Analyser ^ search_mode := FallBackSearchMode.
 
 analyser_state_replace_io_map(IoActionMap, !Analyser) :-
 	!:Analyser = !.Analyser ^ io_action_map := IoActionMap.
@@ -385,8 +380,8 @@
 		revise_root(Store, SearchSpace, SearchSpace1),
 		!:Analyser = !.Analyser ^ search_space := SearchSpace1,
 		!:Analyser = !.Analyser ^ last_search_question := yes(RootId),
-		set_default_search_mode(!.Analyser ^ default_search_mode,
-			!Analyser)
+		!:Analyser = !.Analyser ^ search_mode := 
+			!.Analyser ^ fallback_search_mode
 	;
 		% There must be a root, since a bug was found (and is now
 		% being revised).
@@ -398,7 +393,9 @@
 	is det <= mercury_edt(S, T).
 
 decide_analyser_response(Store, Response, !Analyser) :-
-	% Check an invarients that should hold for the search space.
+	% Do a sanity check before the search.  So we can determine afterwards
+	% if the search corrupted the search space at all.
+	% XXX this should be removed at some stage as it's relatively slow.
 	check_search_space_consistency(Store, !.Analyser ^ search_space,
 		"Start of decide_analyser_response"),
 	some [!SearchSpace] (
@@ -418,7 +415,7 @@
 			are_unknown_suspects(!.SearchSpace)
 		->
 			search(Store, !SearchSpace, !.Analyser ^ search_mode,
-				!.Analyser ^ default_search_mode, NewMode, 
+				!.Analyser ^ fallback_search_mode, NewMode, 
 				SearchResponse),
 			!:Analyser = !.Analyser ^ search_space :=
 				!.SearchSpace,
@@ -458,7 +455,9 @@
 			)
 		)
 	),
-	% Check an invarients that should hold for the search space.
+	% Do a sanity check after the search to determine if the search 
+	% corrupted the search space at all. 
+	% XXX this should be removed at some stage as it's relatively slow.
 	check_search_space_consistency(Store, !.Analyser ^ search_space,
 		"End of decide_analyser_response").
 
@@ -547,26 +546,26 @@
 	% next time round.
 	% 
 :- pred search(S::in, search_space(T)::in, search_space(T)::out, 
-	search_mode::in, default_search_mode::in, 
+	search_mode::in, search_mode::in, 
 	search_mode::out, search_response::out) is det <= mercury_edt(S, T).
 
-search(Store, !SearchSpace, top_down, DefaultSearchMode, NewMode, Response) :-
+search(Store, !SearchSpace, top_down, FallBackSearchMode, NewMode, Response) :-
 	top_down_search(Store, !SearchSpace, Response),
-	% We always go back to the default search mode after a top-down
-	% search, because some default searches (such as divide and query)
-	% use top-down as a fail safe and we want the default search to 
+	% We always go back to the fallback search mode after a top-down
+	% search, because some fallback searches (such as divide and query)
+	% use top-down as a fail safe and we want the fallback search to 
 	% resume after the top-down search.
-	NewMode = search_mode_from_default(DefaultSearchMode).
+	NewMode = FallBackSearchMode.
 
 search(Store, !SearchSpace, follow_subterm_end(SuspectId, ArgPos, TermPath,	
-		LastUnknown), DefaultSearchMode, NewMode, Response) :-
+		LastUnknown), FallBackSearchMode, NewMode, Response) :-
 	follow_subterm_end_search(Store, !SearchSpace, LastUnknown, SuspectId, 
-		ArgPos, TermPath, DefaultSearchMode, NewMode, Response).
+		ArgPos, TermPath, FallBackSearchMode, NewMode, Response).
 
 search(Store, !SearchSpace, binary(PathArray, Top - Bottom, LastTested),
-		DefaultSearchMode, NewMode, Response) :-
+		FallBackSearchMode, NewMode, Response) :-
 	binary_search(Store, PathArray, Top, Bottom, LastTested, !SearchSpace, 
-		DefaultSearchMode, NewMode, Response).
+		FallBackSearchMode, NewMode, Response).
 
 search(Store, !SearchSpace, divide_and_query, _, NewMode, Response) :-
 	divide_and_query_search(Store, !SearchSpace, Response, NewMode).
@@ -634,11 +633,11 @@
 
 :- pred follow_subterm_end_search(S::in, search_space(T)::in,
 	search_space(T)::out, maybe(suspect_id)::in, suspect_id::in,
-	arg_pos::in, term_path::in, default_search_mode::in, search_mode::out,
+	arg_pos::in, term_path::in, search_mode::in, search_mode::out,
 	search_response::out) is det <= mercury_edt(S, T).
 
 follow_subterm_end_search(Store, !SearchSpace, LastUnknown, SuspectId, ArgPos, 
-		TermPath, DefaultSearchMode, NewMode, SearchResponse) :-
+		TermPath, FallBackSearchMode, NewMode, SearchResponse) :-
 	find_subterm_origin(Store, SuspectId, ArgPos, TermPath, !SearchSpace,
 		FindOriginResponse),
 	(
@@ -662,9 +661,9 @@
 					Unknown, NewMode)
 			;
 				LastUnknown = no,
-				start_default_search(DefaultSearchMode, 
-					Store, !SearchSpace, 
-					SearchResponse, NewMode)
+				search(Store, !SearchSpace, FallBackSearchMode, 
+					FallBackSearchMode, NewMode, 
+					SearchResponse)
 			)
 		)
 	;
@@ -676,9 +675,8 @@
 				Unknown, NewMode)
 		;
 			LastUnknown = no,
-			start_default_search(DefaultSearchMode, 
-				Store, !SearchSpace, 
-				SearchResponse, NewMode)
+			search(Store, !SearchSpace, FallBackSearchMode, 
+				FallBackSearchMode, NewMode, SearchResponse)
 		)
 	;
 		FindOriginResponse = require_explicit_subtree,
@@ -722,9 +720,9 @@
 					Unknown, NewMode)
 			;
 				LastUnknown = no,
-				start_default_search(DefaultSearchMode, 
-					Store, !SearchSpace, 
-					SearchResponse, NewMode)
+				search(Store, !SearchSpace, FallBackSearchMode, 
+					FallBackSearchMode, NewMode, 
+					SearchResponse)
 			)
 		;
 			%
@@ -737,7 +735,7 @@
 			%
 			follow_subterm_end_search(Store, !SearchSpace, 
 				NewLastUnknown, OriginId, OriginArgPos,
-				OriginTermPath, DefaultSearchMode, NewMode, 
+				OriginTermPath, FallBackSearchMode, NewMode, 
 				SearchResponse)
 		)
 	).
@@ -773,11 +771,11 @@
 	).
 
 :- pred binary_search(S::in, array(suspect_id)::in, int::in, int::in, int::in,
-	search_space(T)::in, search_space(T)::out, default_search_mode::in,
+	search_space(T)::in, search_space(T)::out, search_mode::in,
 	search_mode::out, search_response::out) is det <= mercury_edt(S, T).
 
 binary_search(Store, PathArray, Top, Bottom, LastTested, !SearchSpace, 
-		DefaultSearchMode, NewMode, Response) :-
+		FallBackSearchMode, NewMode, Response) :-
 	SuspectId = PathArray ^ elem(LastTested),
 	%
 	% Check what the result of the query about LastTested was and adjust
@@ -803,9 +801,10 @@
 	(
 		NewTop > NewBottom
 	->
-		% Revert to the default search mode when binary search is over.
-		start_default_search(DefaultSearchMode, 
-			Store, !SearchSpace, Response, NewMode)
+		% Revert to the fallback search mode when binary search is 
+		% over.
+		search(Store, !SearchSpace, FallBackSearchMode,
+			FallBackSearchMode, NewMode, Response)
 	;
 		(
 			find_unknown_closest_to_middle(!.SearchSpace, 
@@ -818,9 +817,9 @@
 				UnknownClosestToMiddle))
 		;
 			% No unknown suspects on the path, so revert to
-			% the default search strategy.
-			start_default_search(DefaultSearchMode, 
-				Store, !SearchSpace, Response, NewMode)
+			% the fallback search mode.
+			search(Store, !SearchSpace, FallBackSearchMode, 
+				FallBackSearchMode, NewMode, Response)
 		)
 	).
 
@@ -898,13 +897,33 @@
 		NewMode = divide_and_query
 	).
 
+	% Call find_middle_weight/7 if we are able to find the children of the
+	% given suspect id, otherwise return a require_explicit_subtree
+	% search response in the last argument.
+	%
+:- pred find_middle_weight_if_children(S::in, suspect_id::in,
+	maybe(suspect_id)::in, search_space(T)::in, search_space(T)::out,
+	search_response::out) is det <= mercury_edt(S, T).
+
+find_middle_weight_if_children(Store, SuspectId, MaybeLastUnknown,
+		!SearchSpace, Response) :-
+	(
+		children(Store, SuspectId, !SearchSpace, Children)
+	->
+		find_middle_weight(Store, Children, SuspectId,
+			MaybeLastUnknown, !SearchSpace, Response)
+	;
+		Response = require_explicit_subtree(SuspectId)
+	).
+
 	% find_middle_weight(Store, SuspectIds, TopId, MaybeLastUnknown,
 	%	!SearchSpace, Response).
-	% Find the suspect that splits the portion of the search space rooted
-	% at TopId into roughly equal portions by weight.  SuspectIds is 
-	% a list of suspects who's descendents should be searched.  
-	% MaybeLastUnknown is the last node that was unknown in the search (
-	% if any).
+	% Find the first unknown suspect in the descendents of SuspectIds whose
+	% weight is less than or equal to half the weight of TopId.  This is 
+	% done by considering the heaviest suspect in SuspectIds and then the
+	% heaviest child of the heaviest suspect in SuspectId and so on.
+	% MaybeLastUnknown is the last node that was unknown in the search (if
+	% any).  
 	%
 :- pred find_middle_weight(S::in, list(suspect_id)::in, suspect_id::in,
 	maybe(suspect_id)::in, search_space(T)::in, 
@@ -935,21 +954,15 @@
 		MaxWeight > Target
 	->
 		(
-			children(Store, Heaviest, !SearchSpace, Children)
-		->
-			(
 				suspect_unknown(!.SearchSpace, Heaviest)
 			->
 				NewMaybeLastUnknown = yes(Heaviest)
 			;
 				NewMaybeLastUnknown = MaybeLastUnknown
 			),
-			find_middle_weight(Store, Children, TopId,
+		find_middle_weight_if_children(Store, Heaviest, 
 				NewMaybeLastUnknown, !SearchSpace, Response)
 		;
-			Response = require_explicit_subtree(Heaviest)
-		)
-	;
 		(
 			suspect_unknown(!.SearchSpace, Heaviest)
 		->
@@ -961,16 +974,8 @@
 			;
 				MaybeLastUnknown = no,
 				% Look deeper until we find an unknown:
-				(
-					children(Store, Heaviest, !SearchSpace, 						Children)
-				->
-					find_middle_weight(Store, Children, 
-						TopId, no, !SearchSpace,
-						Response)
-				;
-					Response = require_explicit_subtree(
-						Heaviest)
-				)
+				find_middle_weight_if_children(Store, Heaviest,
+					no, !SearchSpace, Response)
 			)
 		)		
 	).
@@ -991,23 +996,3 @@
 		NewMax = PrevMax,
 		NewSuspectId = PrevSuspectId
 	).
-
-	% Start doing a default search of the search space.
-	%
-:- pred start_default_search(default_search_mode::in, S::in, 
-	search_space(T)::in, search_space(T)::out,
-	search_response::out, search_mode::out) is det <= mercury_edt(S, T).
-
-start_default_search(DefaultSearchMode, Store, !SearchSpace, SearchResponse, 
-		NewMode) :-
-	(
-		DefaultSearchMode = top_down,
-		top_down_search(Store, !SearchSpace, 
-			SearchResponse),
-		NewMode = top_down
-	;
-		DefaultSearchMode = divide_and_query,
-		divide_and_query_search(Store, 
-			!SearchSpace, SearchResponse,
-			NewMode)
-	).
--- /home/jupiter/maclarty/ws50_1/browser/declarative_debugger.m	2004-12-31 16:47:00.000000000 +1100
+++ declarative_debugger.m	2004-12-31 15:33:42.000000000 +1100
@@ -522,35 +522,37 @@
 diagnoser_state_init_store(InStr, OutStr, Browser, Diagnoser) :-
 	diagnoser_state_init(map__init, InStr, OutStr, Browser, Diagnoser).
 
-:- pred set_default_search_mode(
-	mdb.declarative_analyser.default_search_mode::in,
+:- pred set_fallback_search_mode(
+	mdb.declarative_analyser.search_mode::in,
 	diagnoser_state(trace_node_id)::in, 
 	diagnoser_state(trace_node_id)::out) is det.
 
-:- pragma export(mdb.declarative_debugger.set_default_search_mode(in, in, out), 
-	"MR_DD_decl_set_default_search_mode").
+:- pragma export(
+	mdb.declarative_debugger.set_fallback_search_mode(in, in, out), 
+	"MR_DD_decl_set_fallback_search_mode").
 
-set_default_search_mode(SearchMode, !Diagnoser) :-
+set_fallback_search_mode(SearchMode, !Diagnoser) :-
 	Analyser0 = !.Diagnoser ^ analyser_state,
-	mdb.declarative_analyser.set_default_search_mode(SearchMode,
+	mdb.declarative_analyser.set_fallback_search_mode(SearchMode,
 		Analyser0, Analyser),
 	!:Diagnoser = !.Diagnoser ^ analyser_state := Analyser.
 
-:- func top_down_default_search_mode = 
-	mdb.declarative_analyser.default_search_mode.
+:- func top_down_search_mode = 
+	mdb.declarative_analyser.search_mode.
 
-top_down_default_search_mode = top_down.
+top_down_search_mode = mdb.declarative_analyser.top_down_search_mode.
 
-:- pragma export(top_down_default_search_mode = out, 
-	"MR_DD_decl_top_down_default_search_mode").
+:- pragma export(mdb.declarative_debugger.top_down_search_mode = out, 
+	"MR_DD_decl_top_down_search_mode").
 
-:- func divide_and_query_default_search_mode = 
-	mdb.declarative_analyser.default_search_mode.
+:- func divide_and_query_search_mode = 
+	mdb.declarative_analyser.search_mode.
 
-divide_and_query_default_search_mode = divide_and_query.
+divide_and_query_search_mode = 
+	mdb.declarative_analyser.divide_and_query_search_mode.
 
-:- pragma export(divide_and_query_default_search_mode = out, 
-	"MR_DD_decl_divide_and_query_default_search_mode").
+:- pragma export(mdb.declarative_debugger.divide_and_query_search_mode = out, 
+	"MR_DD_decl_divide_and_query_search_mode").
 
 	% Export a monomorphic version of diagnosis/10, to make it
 	% easier to call from C code.
--- /home/jupiter/maclarty/ws50_1/browser/declarative_edt.m	2004-12-31 16:47:00.000000000 +1100
+++ declarative_edt.m	2004-12-31 12:39:09.000000000 +1100
@@ -36,6 +36,19 @@
 % far and the term "topmost" for the suspect in the search space with the
 % lowest depth.
 %
+% Each suspect in the search space can be assigned a weight to be used for
+% divide and query search.  Any heuristic can be used, as long as the combined
+% weight of all the children of a suspect does not exceed the suspect's own
+% weight.  Sometimes the weight may depend on the weights of unmaterialized
+% portions of the EDT resulting in the situation where the combined weight of
+% the children of a suspect exceeds the parent's weight.  If this happens then
+% an "excess weight" may be specified along with the normal weight which will
+% be added to all the ancestor's of the overweight suspect.  For example if the
+% number of events in descendent suspects is being used as a weight, then for a
+% FAIL node some events may be repeated in siblings of the FAIL node.  In this
+% case the duplicate events might not have been included in the ancestor's
+% weights, so should be added.
+%
 
 :- module mdb.declarative_edt.
 
@@ -129,16 +142,9 @@
 	pred edt_topmost_node(S::in, T::in) is semidet,
  
  		% edt_weight(Store, Node, Weight, ExcessWeight).
-		% True if Weight is the weight of Node.  ExcessWeight is
-		% some extra weight that should be added to the ancestors of
-		% Node because the sum of the weights of the Node and its
-		% siblings might otherwise be bigger than Node's parent's 
-		% weight.  For example if the number of events in descendent
-		% nodes is being used as a weight, then for a FAIL node
-		% some events may be repeated in siblings of the FAIL node.
-		% In this case the number of duplicate events should be
-		% returned in ExcessWeight so they can be added to the
-		% ancestors.
+		% Find the weight and excess weight for a node.  See the 
+		% comment at the top of this module for the meaning of 
+		% the weight of a node.
  		%
  	pred edt_weight(S::in, T::in, int::out, int::out) is det
 ].
@@ -756,7 +762,7 @@
 		adjust_unexplored_leaves(yes(Suspect ^ status), Status, 
 			!SearchSpace)
 	),
-	% Remove the suspect's weight from it's ancestors, since its weight is
+	% Remove the suspect's weight from its ancestors, since its weight is
 	% now zero.
 	add_weight_to_ancestors(SuspectId, - Suspect ^ weight, !SearchSpace),
 	%
@@ -1208,11 +1214,10 @@
 			++ string(SearchSpace) ++ "\n Context is:\n" ++
 			Context))
 	;
-		check_search_space_weights(Store, SearchSpace)
+		find_inconsistency_in_weights(Store, SearchSpace, Message)
 	->
-		% check_search_space_weights will never actually fail, but
-		% will throw an exception if the weights are inconsistent.
-		true
+		throw(internal_error("check_search_space_consistency",
+			Message))
 	;
 		true
 	).
@@ -1383,26 +1388,28 @@
 		), Suspects, Unexplored),
 	NumUnexplored = list.length(Unexplored).
 
-	% Check that the weights in the search space are correct and throw
-	% an exception if they aren't.
+	% Try to find an inconsistency in the weights of the suspects.  If one
+	% is found output an error message, otherwise fail.
 	%
-:- pred check_search_space_weights(S::in, search_space(T)::in) 
-	is semidet <= mercury_edt(S, T).
+:- pred find_inconsistency_in_weights(S::in, search_space(T)::in, 
+	string::out) is semidet <= mercury_edt(S, T).
 
-check_search_space_weights(Store, SearchSpace) :-
+find_inconsistency_in_weights(Store, SearchSpace, Message) :-
 	( root(SearchSpace, RootId) ->
-		check_search_space_weights(Store, RootId, SearchSpace)
+		find_inconsistency_in_weights_2(Store, SearchSpace, 
+			RootId, Message)
 	;
 		topmost_det(SearchSpace, TopMostId),
-		check_search_space_weights(Store, TopMostId, SearchSpace)
+		find_inconsistency_in_weights_2(Store, SearchSpace, 
+			TopMostId, Message)
 	).
 
 	% Check that the weights are correct from the given suspect down.
 	%
-:- pred check_search_space_weights(S::in, suspect_id::in, search_space(T)::in) 
-	is semidet <= mercury_edt(S, T).
+:- pred find_inconsistency_in_weights_2(S::in, search_space(T)::in,
+	suspect_id::in, string::out) is semidet <= mercury_edt(S, T).
 
-check_search_space_weights(Store, SuspectId, SearchSpace) :-
+find_inconsistency_in_weights_2(Store, SearchSpace, SuspectId, Message) :-
 	lookup_suspect(SearchSpace, SuspectId, Suspect),
 	calc_suspect_weight(Store, Suspect ^ edt_node, Suspect ^ children,
 		Suspect ^ status, SearchSpace, Weight, _),
@@ -1410,25 +1417,16 @@
 		Weight = Suspect ^ weight,
 		Weight >= 0
 	->
-		(
 			Suspect ^ children = yes(Children),
-			in_buggy_subtree(Suspect ^ status, yes)
-		->
-			all [Child] (
-				member(Child, Children)
-			=>
-				check_search_space_weights(Store, Child, 
-					SearchSpace)
-			)
-		;
-			true
-		)
+		in_buggy_subtree(Suspect ^ status, yes),
+		list.filter_map(find_inconsistency_in_weights_2(Store, 
+			SearchSpace), Children, Messages),
+		Messages = [Message | _]
 	;
-		throw(internal_error("check_search_space_weights",
-			"Weights not consistent for suspect id " ++
+		Message = "Weights not consistent for suspect id " ++
 			int_to_string(SuspectId) ++ ", Suspect = " ++ 
 			string(Suspect) ++ " Calculated weight = " ++
-			int_to_string(Weight)))
+			int_to_string(Weight)
 	).
 
 	% propagate_status_upwards(Status, StopStatusSet, SuspectId, Lowest, 
--- /home/jupiter/maclarty/ws50_1/browser/declarative_tree.m	2004-12-31 16:47:00.000000000 +1100
+++ declarative_tree.m	2004-12-31 12:47:50.000000000 +1100
@@ -297,6 +297,7 @@
 	% internal body events for the call.  Also return the number of events
 	% that could be duplicated in siblings of the node in the EDT if the 
 	% node is a FAIL event.
+	%
 	% 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
@@ -309,7 +310,7 @@
 	% True iff Events is the (conservative approximation of) the number of
 	% descendent events of Node and DupEvents is the number of events that
 	% could be duplicated in siblings.  PrevEvents and PrevDupEvents are
-	% accumlators which should initially be zero.  RecordDups keeps track
+	% accumulators which should initially be zero.  RecordDups keeps track
 	% 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
Diffing bytecode
Diffing compiler
Diffing compiler/notes
Diffing debian
Diffing deep_profiler
Diffing deep_profiler/notes
Diffing doc
--- /home/jupiter/maclarty/ws50_1/doc/user_guide.texi	2004-12-31 16:47:00.000000000 +1100
+++ user_guide.texi	2004-12-31 16:30:21.000000000 +1100
@@ -3257,7 +3257,7 @@
 @ref{Declarative debugging} for details.
 @sp 1
 @table @code
- at item dd [-d at var{depth} -s at var{strategy}]
+ at item dd [-d at var{depth}] [-s at var{search-mode}]
 @c @item dd [--assume-all-io-is-tabled]
 @c The --assume-all-io-is-tabled option is for developers only. Specifying it
 @c makes an assertion, and if the assertion is incorrect, the resulting
@@ -3274,17 +3274,12 @@
 declarative debugger for long running programs since it will not have to rerun
 the program as much.
 @sp 1
-The @samp{-s at var{strategy}} or @samp{--default-search-mode
- at var{strategy}} option tells the declarative debugger which 
-search strategy to use by default.  Either @samp{top-down} or 
- at samp{divide-and-query} may be specified.  @samp{top-down} search is more
-predicable and will ask you about the children of the last atom you
-asserted was erroneous (i.e. gave a `no' answer for), however this may
-mean that lots of questions will need to be answered before a bug is located.  
- at samp{divide-and-query} search tries to ask questions that will halve the
-search space with each answer resulting in quicker localization of the bug,
-however the questions asked may appear unrelated to each other.  
- at samp{top-down} is the default when this option is not given.
+The @samp{-s at var{search-mode}} or @samp{--search-mode
+ at var{search-mode}} option tells the declarative debugger which 
+search mode to use.  Either @samp{top-down} or @samp{divide-and-query}
+may be specified.  See @ref{Search Modes} for a more detailed description of
+the available search modes.  @samp{top-down} is the default when this option is
+not given.
 @sp 1
 @item trust @var{module-name}|@var{proc-spec}
 @kindex trust (mdb command)
@@ -3517,8 +3512,8 @@
 Tells the debugger to hide events that are normally hidden.
 @sp 1
 @item dd_dd
- at c @item dd_dd [filename]
- at c @item dd_dd [--assume-all-io-is-tabled] [filename]
+ at c @item dd_dd [-d at var{depth}] [-s at var{search-mode}] [filename]
+ at c @item dd_dd [--assume-all-io-is-tabled] 
 @c The --assume-all-io-is-tabled option is for developers only. Specifying it
 @c makes an assertion, and if the assertion is incorrect, the resulting
 @c behaviour would be hard for non-developers to understand. The option is
@@ -3636,7 +3631,7 @@
 * Oracle questions::
 * Declarative debugging commands::
 * Diagnoses::
-* Search Strategies::
+* Search Modes::
 * Improving the search::
 @end menu
 
@@ -3897,30 +3892,33 @@
 If the user aborts the diagnosis,
 they are returned to the event at which the @samp{dd} command was given.
 
- at node Search Strategies
- at subsection Search Strategies
+ at node Search Modes
+ at subsection Search Modes
 
-Currently the declarative debugger can employ one of two strategies when
-searching for a bug.  The initial strategy to use can be specified
-as an option to the @samp{dd} command.  See 
- at ref{Declarative debugging mdb commands} for information on how to do this.
+Currently the declarative debugger can operate in one of two modes when
+searching for a bug.  The mode to use can be specified as an option to the
+ at samp{dd} command.  See @ref{Declarative debugging mdb commands} for
+information on how to do this.  The specified search mode will always be used
+unless a sub-term is marked or the user hasn't answered `no' to any questions
+yet (In which case top-down search is used until `no' is answered to at least
+one question).
 
 @subsubsection Top-down Search
 
-Using this strategy the declarative debugger will ask about the children
-of the last atom who's assertion was false.  This makes the search more
-predictable from the user's point of view as the questions will more
-or less follow the program execution.  The drawback of top-down search is that
-it may require a lot of questions to be answered before a bug is found, 
-especially with deeply recursive program runs.  
+Using this mode the declarative debugger will ask about the children of the
+last atom whose assertion was false.  This makes the search more predictable
+from the user's point of view as the questions will more or less follow the
+program execution.  The drawback of top-down search is that it may require a
+lot of questions to be answered before a bug is found, especially with deeply
+recursive program runs.
 
-This search strategy is used by default when no other strategy is specified.
+This search mode is used by default when no other mode is specified.
 
 @subsubsection Divide and Query Search
 
-With this strategy the declarative debugger will attempt to halve the size of
-the search space with each question.  In most cases this will result in the 
-bug being found after log(N) questions where N is the number of events
+With this search mode the declarative debugger will attempt to halve the size of
+the search space with each question.  In many cases this will result in the 
+bug being found after O(log(N)) questions where N is the number of events
 between the event where the @samp{dd} command was given and the corresponding
 @samp{CALL} event.  This makes the search feasible for deeply recursive runs
 where top-down search would require an unreasonably large number of questions
Diffing extras
Diffing extras/aditi
Diffing extras/cgi
Diffing extras/complex_numbers
Diffing extras/complex_numbers/samples
Diffing extras/complex_numbers/tests
Diffing extras/concurrency
Diffing extras/curs
Diffing extras/curs/samples
Diffing extras/curses
Diffing extras/curses/sample
Diffing extras/dynamic_linking
Diffing extras/error
...
Diffing samples/tests/diff
Diffing samples/tests/muz
Diffing samples/tests/rot13
Diffing samples/tests/solutions
Diffing samples/tests/toplevel
Diffing scripts
Diffing tools
Diffing trace
--- /home/jupiter/maclarty/ws50_1/trace/mercury_trace_declarative.c	2004-12-31 16:47:08.000000000 +1100
+++ mercury_trace_declarative.c	2004-12-31 15:44:04.000000000 +1100
@@ -1176,12 +1176,11 @@
 }
 
 void
-MR_trace_decl_set_default_search_mode(
-	MR_Decl_Default_Search_Mode default_search_mode)
+MR_trace_decl_set_fallback_search_mode(MR_Decl_Search_Mode search_mode)
 {
 	MR_trace_decl_ensure_init();
 	MR_TRACE_CALL_MERCURY(
-		MR_DD_decl_set_default_search_mode(default_search_mode,
+		MR_DD_decl_set_fallback_search_mode(search_mode,
 			MR_trace_front_end_state,
 			&MR_trace_front_end_state);
 	);		
@@ -1189,21 +1188,27 @@
 
 MR_bool
 MR_trace_is_valid_search_mode_string(const char *search_mode_string,
-	MR_Decl_Default_Search_Mode *default_search_mode)
+	MR_Decl_Search_Mode *search_mode)
 {
 	if (MR_streq(search_mode_string, "top_down")) {
-		*default_search_mode =
-			MR_DD_decl_top_down_default_search_mode();
+		*search_mode =
+			MR_DD_decl_top_down_search_mode();
 		return MR_TRUE;
 	} else if (MR_streq(search_mode_string, "divide_and_query")) {
-		*default_search_mode =
-			MR_DD_decl_divide_and_query_default_search_mode();
+		*search_mode =
+			MR_DD_decl_divide_and_query_search_mode();
 		return MR_TRUE;
 	} else {
 		return MR_FALSE;
 	}
 }
 
+MR_Decl_Search_Mode
+MR_trace_get_default_search_mode()
+{
+	return MR_DD_decl_top_down_search_mode();
+}
+
 void
 MR_decl_add_trusted_module(const char *module_name)
 {
--- /home/jupiter/maclarty/ws50_1/trace/mercury_trace_declarative.h	2004-12-31 16:47:08.000000000 +1100
+++ mercury_trace_declarative.h	2004-12-31 15:48:19.000000000 +1100
@@ -66,22 +66,29 @@
 ** the analyser.
 */
 
-typedef MR_Word MR_Decl_Default_Search_Mode;
+typedef MR_Word MR_Decl_Search_Mode;
 
-extern	void	MR_trace_decl_set_default_search_mode(
-			MR_Decl_Default_Search_Mode default_search_mode);
+extern	void	MR_trace_decl_set_fallback_search_mode(
+			MR_Decl_Search_Mode search_mode);
 
 /*
 ** This function checks to see if the supplied string is a valid
-** default search mode.  If it is then it returns MR_TRUE and sets
-** the value at default_search_mode to the corresponding default search mode.
+** search mode.  If it is then it returns MR_TRUE and sets
+** the value at search_mode to the corresponding search mode.
 ** If it isn't then it returns MR_FALSE and leaves the value at
-** default_search_mode unchanged.
+** search_mode unchanged.
 */
 
 extern	MR_bool	MR_trace_is_valid_search_mode_string(
 			const char *search_mode_string,
-			MR_Decl_Default_Search_Mode *default_search_mode);
+			MR_Decl_Search_Mode *search_mode);
+
+/*
+** Return the default search mode to use when then --search-mode option for the
+** `dd' command is not given.
+*/
+
+extern MR_Decl_Search_Mode MR_trace_get_default_search_mode(void);
 
 /*
 ** Prints a list of the trusted objects.  If mdb_command_format is true it
--- /home/jupiter/maclarty/ws50_1/trace/mercury_trace_internal.c	2004-12-31 16:47:08.000000000 +1100
+++ mercury_trace_internal.c	2004-12-31 15:51:12.000000000 +1100
@@ -541,7 +541,7 @@
 			int *word_count, const char *cat, const char*item);
 static	MR_bool	MR_trace_options_dd(MR_bool *assume_all_io_is_tabled,
 			MR_Integer *depth_step_size, 
-			MR_Decl_Default_Search_Mode *default_search_mode, 
+			MR_Decl_Search_Mode *search_mode, 
 			char ***words, int *word_count, const char *cat, 
 			const char *item);
 static	MR_bool	MR_trace_options_type_ctor(MR_bool *print_rep,
@@ -5512,18 +5512,14 @@
 	MR_Event_Info *event_info, MR_Event_Details *event_details,
 	MR_Code **jumpaddr)
 {
-	MR_Decl_Default_Search_Mode	default_search_mode;
+	MR_Decl_Search_Mode	search_mode;
 
 	MR_trace_decl_assume_all_io_is_tabled = MR_FALSE;
 	MR_edt_depth_step_size = MR_TRACE_DECL_INITIAL_DEPTH;
-	if (! MR_trace_is_valid_search_mode_string("top_down", 
-			&default_search_mode))
-	{
-		MR_fatal_error("MR_trace_cmd_dd: top_down invalid");
-	}
+	search_mode = MR_trace_get_default_search_mode();
 		
 	if (! MR_trace_options_dd(&MR_trace_decl_assume_all_io_is_tabled,
-		&MR_edt_depth_step_size, &default_search_mode,
+		&MR_edt_depth_step_size, &search_mode,
 		&words, &word_count, "dd", "dd"))
 	{
 		; /* the usage message has already been printed */
@@ -5536,7 +5532,7 @@
 			return KEEP_INTERACTING;
 		}
 
-		MR_trace_decl_set_default_search_mode(default_search_mode);
+		MR_trace_decl_set_fallback_search_mode(search_mode);
 
 		if (MR_trace_start_decl_debug(MR_TRACE_DECL_DEBUG,
 			NULL, cmd, event_info, event_details, jumpaddr))
@@ -5557,18 +5553,14 @@
 {
 	MR_Trace_Mode	trace_mode;
 	const char	*filename;
-	MR_Decl_Default_Search_Mode	default_search_mode;
+	MR_Decl_Search_Mode	search_mode;
 
 	MR_trace_decl_assume_all_io_is_tabled = MR_FALSE;
 	MR_edt_depth_step_size = MR_TRACE_DECL_INITIAL_DEPTH;
-	if (! MR_trace_is_valid_search_mode_string("top_down",
-			&default_search_mode))
-	{
-		MR_fatal_error("MR_trace_cmd_dd_dd: top_down invalid");
-	}
+	search_mode = MR_trace_get_default_search_mode();
 	
 	if (! MR_trace_options_dd(&MR_trace_decl_assume_all_io_is_tabled,
-		&MR_edt_depth_step_size, &default_search_mode,
+		&MR_edt_depth_step_size, &search_mode,
 		&words, &word_count, "dd", "dd_dd"))
 	{
 		; /* the usage message has already been printed */
@@ -5581,7 +5573,7 @@
 			filename = (const char *) NULL;
 		} 
 
-		MR_trace_decl_set_default_search_mode(default_search_mode);
+		MR_trace_decl_set_fallback_search_mode(search_mode);
 
 		if (MR_trace_start_decl_debug(trace_mode, filename,
 			cmd, event_info, event_details, jumpaddr))
@@ -6577,16 +6569,14 @@
 {
 	{ "assume-all-io-is-tabled",	MR_no_argument,		NULL,	'a' },
 	{ "depth-step-size",		MR_required_argument, 	NULL, 	'd' },
-	{ "default-search-mode",	MR_required_argument,	NULL,	's' },
+	{ "search-mode",		MR_required_argument,	NULL,	's' },
 	{ NULL,				MR_no_argument,		NULL,	0 }
 };
 
 static MR_bool
 MR_trace_options_dd(MR_bool *assume_all_io_is_tabled, 
-	MR_Integer *depth_step_size, 
-	MR_Decl_Default_Search_Mode *default_search_mode, 
-	char ***words, int *word_count, const char
-	*cat, const char *item)
+	MR_Integer *depth_step_size, MR_Decl_Search_Mode *search_mode, 
+	char ***words, int *word_count, const char *cat, const char *item)
 {
 	int	c;
 
@@ -6608,8 +6598,7 @@
 				break;
 			case 's':
 				if (! MR_trace_is_valid_search_mode_string(
-						MR_optarg, 
-						default_search_mode)) {
+						MR_optarg, search_mode)) {
 					MR_trace_usage(cat, item);
 					return MR_FALSE;
 				}
@@ -7479,7 +7468,7 @@
 	{ "all", "interface", "entry", NULL };
 
 static const char *const	MR_trace_dd_cmd_args[] =
-	{ "-s", "-a", "-d", "--default-search-mode", 
+	{ "-s", "-a", "-d", "--search-mode", 
 	"--assume-all-io-is-tabled", "--depth-step-size", 
 	"top_down", "divide_and_query", NULL };
 
Diffing util
Diffing vim
Diffing vim/after
Diffing vim/ftplugin
Diffing vim/syntax

Phew!
--------------------------------------------------------------------------
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