[m-dev.] for review: Added a new format "newpretty" to the browser.

Sarvamanan THURAIRATNAM sthur at students.cs.mu.oz.au
Thu Jan 11 18:48:34 AEDT 2001


For Mark Brown to review (Zoltan's Recommendation)

This new format helps put a limit on the size of the term printed during
debugging. This limit is specified by setting the number of lines you want
the term to be printed on and the width of these lines. Refer to
sizepretty.m for Examples.

browser/sizepretty.m:
	New file that does what's described above.
browser/browse.m:
	Modified to accommodate the new format.
browser/browser_info.m:
	Modified to accommodate the new format.
browser/parse.m:
        Modified to accommodate the new format.
trace/mercury_trace_browse.c:
        Modified to accommodate the new format.
trace/mercury_trace_browse.h:
        Modified to accommodate the new format.
trace/mercury_trace_internal.c:
        Modified to accommodate the new format.

? make_all.log
? make_install.log
? scripts/canonical_grade
Index: browser/browse.m
===================================================================
RCS file: /home/mercury1/repository/mercury/browser/browse.m,v
retrieving revision 1.17
diff -u -r1.17 browse.m
--- browser/browse.m	2001/01/09 23:30:13	1.17
+++ browser/browse.m	2001/01/11 07:17:29
@@ -84,7 +84,7 @@
 
 :- import_module mdb__parse, mdb__util, mdb__frame.
 :- import_module string, list, parser, require, std_util, int, char, pprint.
-:- import_module bool.
+:- import_module bool, sizepretty.
 
 %---------------------------------------------------------------------------%
 %
@@ -294,8 +294,8 @@
 	% XXX We can't yet give options to the `set' command.
 	%
 	No = bool__no,
-	browser_info__set_param(No, No, No, No, No, No, Setting, Info0 ^ state,
-			NewState),
+	browser_info__set_param(No, No, No, No, No, No, No, Setting, 
+			Info0 ^ state, NewState),
 	Info = Info0 ^ state := NewState.
 
 :- pred help(debugger::in, io__state::di, io__state::uo) is det.
@@ -347,6 +347,9 @@
 		;
 			{ Format = verbose },
 			portray_verbose(Debugger, SubUniv, Params)
+		;
+			{ Format = newpretty },
+			portray_newpretty(Debugger, SubUniv, Params)
 		)
 	;
 		write_string_debugger(Debugger, "error: no such subterm")
@@ -401,6 +404,13 @@
 	write_string_debugger(Debugger, Str).
 
 
+:- pred portray_newpretty(debugger, univ, format_params, io__state, io__state).
+:- mode portray_newpretty(in, in, in, di, uo) is det.
+
+portray_newpretty(Debugger, Univ, Params) -->
+	{ term_to_string_newpretty(Univ, Params ^ lines, Params ^ width, Str) },
+	write_string_debugger(Debugger, Str).
+
 	% The maximum estimated size for which we use `io__write'.
 :- pred max_print_size(int::out) is det.
 max_print_size(60).
@@ -519,6 +529,21 @@
 
 %---------------------------------------------------------------------------%
 %
+% Print using the sizepretty.m module.
+%
+
+:- pred term_to_string_newpretty(univ, int, int, string).
+:- mode term_to_string_newpretty(in, in, in, out) is det.
+
+term_to_string_newpretty(Univ, Lines, Width, Str) :-
+	sizepretty__annotate_with_size(Univ, measure_params(Width),
+		size_count(Lines, 0), AnnotTerm),
+	Doc = sizepretty__my_to_doc(AnnotTerm),
+		% The plus 3 is to account for ", \n"
+	Str = pprint__to_string((Width+3), Doc).
+
+%---------------------------------------------------------------------------%
+%
 % Verbose printing. Tree layout with numbered branches.
 % Numbering makes it easier to change to subterms.
 %
@@ -871,6 +896,9 @@
 	;
 		{ X = verbose },
 		send_term_to_socket(browser_str("verbose"))
+	;
+		{ X = newpretty },
+		send_term_to_socket(browser_str("newpretty"))
 	).
 
 :- pred send_term_to_socket(term_browser_response, io__state, io__state).
Index: browser/browser_info.m
===================================================================
RCS file: /home/mercury1/repository/mercury/browser/browser_info.m,v
retrieving revision 1.1
diff -u -r1.1 browser_info.m
--- browser/browser_info.m	2000/10/27 08:38:49	1.1
+++ browser/browser_info.m	2001/01/11 07:17:29
@@ -52,10 +52,12 @@
 
 	% The various ways of representing terms by the browser.
 	%
+	% Added the Format newpretty
 :- type portray_format
 	--->	flat
 	;	pretty
-	;	verbose.
+	;	verbose
+	;	newpretty.
 
 :- type format_params
 	--->	format_params(
@@ -110,8 +112,9 @@
 	% and -v, in that order.
 	%
 :- pred browser_info__set_param(bool::in, bool::in, bool::in, bool::in,
-		bool::in, bool::in, setting::in, browser_persistent_state::in,
-		browser_persistent_state::out) is det.
+		bool::in, bool::in, bool::in, setting::in, 
+		browser_persistent_state::in, browser_persistent_state::out) 
+		is det.
 
 %---------------------------------------------------------------------------%
 
@@ -127,40 +130,40 @@
 	%
 
 :- pred set_param_depth(bool::in, bool::in, bool::in, bool::in, bool::in,
-		bool::in, int::in, browser_persistent_state::in,
+		bool::in, bool::in, int::in, browser_persistent_state::in,
 		browser_persistent_state::out) is det.
-:- pragma export(set_param_depth(in, in, in, in, in, in, in, in, out),
+:- pragma export(set_param_depth(in, in, in, in, in, in, in, in, in, out),
 		"ML_BROWSE_set_param_depth").
 
-set_param_depth(P, B, A, F, Pr, V, Depth) -->
-	browser_info__set_param(P, B, A, F, Pr, V, depth(Depth)).
+set_param_depth(P, B, A, F, Pr, V, NPr, Depth) -->
+	browser_info__set_param(P, B, A, F, Pr, V, NPr,  depth(Depth)).
 
 :- pred set_param_size(bool::in, bool::in, bool::in, bool::in, bool::in,
-		bool::in, int::in, browser_persistent_state::in,
+		bool::in, bool::in, int::in, browser_persistent_state::in,
 		browser_persistent_state::out) is det.
-:- pragma export(set_param_size(in, in, in, in, in, in, in, in, out),
+:- pragma export(set_param_size(in, in, in, in, in, in, in, in, in, out),
 		"ML_BROWSE_set_param_size").
 
-set_param_size(P, B, A, F, Pr, V, Size) -->
-	browser_info__set_param(P, B, A, F, Pr, V, size(Size)).
+set_param_size(P, B, A, F, Pr, NPr, V, Size) -->
+	browser_info__set_param(P, B, A, F, Pr, V, NPr, size(Size)).
 
 :- pred set_param_width(bool::in, bool::in, bool::in, bool::in, bool::in,
-		bool::in, int::in, browser_persistent_state::in,
+		bool::in, bool::in, int::in, browser_persistent_state::in,
 		browser_persistent_state::out) is det.
-:- pragma export(set_param_width(in, in, in, in, in, in, in, in, out),
+:- pragma export(set_param_width(in, in, in, in, in, in, in, in, in, out),
 		"ML_BROWSE_set_param_width").
 
-set_param_width(P, B, A, F, Pr, V, Width) -->
-	browser_info__set_param(P, B, A, F, Pr, V, width(Width)).
+set_param_width(P, B, A, F, Pr, V, NPr, Width) -->
+	browser_info__set_param(P, B, A, F, Pr, V, NPr, width(Width)).
 
 :- pred set_param_lines(bool::in, bool::in, bool::in, bool::in, bool::in,
-		bool::in, int::in, browser_persistent_state::in,
+		bool::in, bool::in, int::in, browser_persistent_state::in,
 		browser_persistent_state::out) is det.
-:- pragma export(set_param_lines(in, in, in, in, in, in, in, in, out),
+:- pragma export(set_param_lines(in, in, in, in, in, in, in, in, in, out),
 		"ML_BROWSE_set_param_lines").
 
-set_param_lines(P, B, A, F, Pr, V, Lines) -->
-	browser_info__set_param(P, B, A, F, Pr, V, lines(Lines)).
+set_param_lines(P, B, A, F, Pr, V, NPr, Lines) -->
+	browser_info__set_param(P, B, A, F, Pr, V, NPr, lines(Lines)).
 
 :- pred set_param_format(bool::in, bool::in, bool::in, portray_format::in,
 		browser_persistent_state::in, browser_persistent_state::out)
@@ -172,7 +175,7 @@
 	%
 	% Any format flags are ignored for this parameter.
 	%
-	browser_info__set_param(P, B, A, no, no, no, format(Format)).
+	browser_info__set_param(P, B, A, no, no, no, no, format(Format)).
 
 %---------------------------------------------------------------------------%
 
@@ -212,7 +215,8 @@
 			default_format		:: portray_format,
 			flat_params		:: format_params,
 			pretty_params		:: format_params,
-			verbose_params		:: format_params
+			verbose_params		:: format_params,
+			newpretty_params	:: format_params
 		).
 
 	% Initialise the persistent settings with default values.  The
@@ -244,10 +248,11 @@
 
 caller_type_print_defaults(Params) :-
 	DefaultFormat = flat,
-	Flat	= format_params(3, 10, 80, 25),
-	Pretty	= format_params(3, 10, 80, 25),
-	Verbose	= format_params(3, 10, 80, 25),
-	Params	= caller_params(DefaultFormat, Flat, Pretty, Verbose).
+	Flat	  = format_params(3, 10, 80, 25),
+	Pretty	  = format_params(3, 10, 80, 25),
+	Verbose	  = format_params(3, 10, 80, 25),
+	Newpretty = format_params(3, 10, 80, 25),
+	Params = caller_params(DefaultFormat, Flat, Pretty, Verbose, Newpretty).
 
 :- pred caller_type_browse_defaults(caller_params).
 :- mode caller_type_browse_defaults(out) is det.
@@ -257,7 +262,8 @@
 	Flat	= format_params(10, 30, 80, 25),
 	Pretty	= format_params(10, 30, 80, 25),
 	Verbose	= format_params(10, 30, 80, 25),
-	Params	= caller_params(DefaultFormat, Flat, Pretty, Verbose).
+	Newpretty = format_params(3, 10, 80, 25),
+	Params = caller_params(DefaultFormat, Flat, Pretty, Verbose, Newpretty).
 
 :- pred caller_type_print_all_defaults(caller_params).
 :- mode caller_type_print_all_defaults(out) is det.
@@ -267,14 +273,20 @@
 	Flat	= format_params(3, 10, 80, 2),
 	Pretty	= format_params(3, 10, 80, 2),
 	Verbose	= format_params(3, 10, 80, 5),
-	Params	= caller_params(DefaultFormat, Flat, Pretty, Verbose).
+	Newpretty = format_params(3, 10, 80, 2),
+	Params = caller_params(DefaultFormat, Flat, Pretty, Verbose, Newpretty).
 
-browser_info__set_param(P0, B0, A0, F0, Pr0, V0, Setting, State0, State) :-
+browser_info__set_param(P0, B0, A0, F0, Pr0, V0, _, Setting, State0, State):-
 	default_all_yes(P0, B0, A0, P, B, A),
 	default_all_yes(F0, Pr0, V0, F, Pr, V),
-	maybe_set_param(P, F, Pr, V, Setting, State0 ^ print_params, PParams),
-	maybe_set_param(B, F, Pr, V, Setting, State0 ^ browse_params, BParams),
-	maybe_set_param(A, F, Pr, V, Setting, State0 ^ print_all_params,
+	% XXX for now NPr = Pr but when "pretty format" is replaced with
+	% "newpretty format" this statement is not required.
+	NPr = Pr,
+	maybe_set_param(P, F, Pr, V, NPr, Setting, State0 ^ print_params, 
+			PParams),
+	maybe_set_param(B, F, Pr, V, NPr, Setting, State0 ^ browse_params, 
+			BParams),
+	maybe_set_param(A, F, Pr, V, NPr, Setting, State0 ^ print_all_params,
 			AParams),
 	State = browser_persistent_state(PParams, BParams, AParams).
 
@@ -300,12 +312,12 @@
 		C = C0
 	).
 
-:- pred maybe_set_param(bool, bool, bool, bool, setting, caller_params,
+:- pred maybe_set_param(bool, bool, bool, bool, bool, setting, caller_params,
 		caller_params).
-:- mode maybe_set_param(in, in, in, in, in, in, out) is det.
+:- mode maybe_set_param(in, in, in, in, in, in, in, out) is det.
 
-maybe_set_param(no, _, _, _, _, Params, Params).
-maybe_set_param(yes, F, Pr, V, Setting, Params0, Params) :-
+maybe_set_param(no, _, _, _, _, _, Params, Params).
+maybe_set_param(yes, F, Pr, V, NPr, Setting, Params0, Params) :-
 	(
 		Setting = format(NewFormat)
 	->
@@ -316,8 +328,10 @@
 				PrParams),
 		maybe_set_param_2(V, Setting, Params0 ^ verbose_params,
 				VParams),
+		maybe_set_param_2(NPr, Setting, Params0 ^ newpretty_params,
+				NPrParams),
 		Params = caller_params(Params0 ^ default_format, FParams,
-				PrParams, VParams)
+				PrParams, VParams, NPrParams)
 	).
 
 :- pred maybe_set_param_2(bool, setting, format_params, format_params).
@@ -345,6 +359,7 @@
 get_caller_format_params(Params, flat, Params ^ flat_params).
 get_caller_format_params(Params, pretty, Params ^ pretty_params).
 get_caller_format_params(Params, verbose, Params ^ verbose_params).
+get_caller_format_params(Params, newpretty, Params ^ newpretty_params).
 
 %---------------------------------------------------------------------------%
 
Index: browser/parse.m
===================================================================
RCS file: /home/mercury1/repository/mercury/browser/parse.m,v
retrieving revision 1.9
diff -u -r1.9 parse.m
--- browser/parse.m	2000/10/27 08:38:50	1.9
+++ browser/parse.m	2001/01/11 07:17:29
@@ -333,9 +333,11 @@
 			Setting = format(flat)
 		; Fmt = name("pretty") ->
 			Setting = format(pretty)
-		;
-			Fmt = name("verbose"),
+		; Fmt = name("verbose") ->
 			Setting = format(verbose)
+		; 
+			Fmt = name("newpretty"),
+			Setting = format(newpretty)
 		)
 	;
 		fail
@@ -430,5 +432,7 @@
 	io__write_string("pretty").
 show_format(verbose) -->
 	io__write_string("verbose").
+show_format(newpretty) -->
+	io__write_string("newpretty").
 
 %---------------------------------------------------------------------------%
Index: browser/sizepretty.m
===================================================================
RCS file: sizepretty.m
diff -N sizepretty.m
--- /dev/null	Wed Nov 15 09:24:47 2000
+++ sizepretty.m	Thu Jan 11 18:17:29 2001
@@ -0,0 +1,809 @@
+% How to use sizepretty.m
+% 1. Pass a term(in univ type), a linewidth(by measure_params(LineWidth)), 
+%    a Limit(size_count(NO.of.Lines, NO.of.Chars)) to annotate_with_size
+%    and you will recieve a size_annotated term.
+%
+% 2. Pass this Size annotated term to my_to_doc, which returns a 'doc' type
+%    value.
+%
+% 3. Pass this 'doc' type value to pprint__to_string along with the LineWidth
+%    to receive a string which can be printed.
+%
+% EXAMPLES
+% --------
+%
+% Term Used in these examples:
+%
+%	Term = big(
+%                 big(
+%                    big(
+%                       small,
+%			"Level 3",
+%                       small
+%                       ),
+%		     "Level 2",
+%                    small
+%                    ),
+%		  "Level 1",
+%                 big(
+%                    big(
+%                       small,
+%		        "Level 3",
+%			small
+%                       ),
+%		     "Level 2",
+%		     small
+%                    )).
+/*
+%------------------------------------------------------------------------------%
+Width = 16, Limit = size_count(16, 0)
+
+big(
+  big(
+    big(
+      small, 
+      "Level 3", 
+      small), 
+    "Level 2", 
+    small), 
+  "Level 1", 
+  big(
+    big(
+      small, 
+      "Level 3", 
+      small), 
+    "Level 2", 
+    small))
+
+%------------------------------------------------------------------------------%
+Width = 14, Limit = size_count(16, 0)
+
+big(
+  big(
+    big/3, 
+    "Level 2", 
+    small), 
+  "Level 1", 
+  big(
+    big/3, 
+    "Level 2", 
+    small))
+
+%------------------------------------------------------------------------------%
+Width = 50, Limit = size_count(4, 0)
+
+big(
+  big(big/3, "Level 2", small), 
+  "Level 1", 
+  big(big/3, "Level 2", small))
+
+%------------------------------------------------------------------------------%
+Width = 54, Limit = size_count(4, 0)
+
+big(
+  big(big(small, "Level 3", small), "Level 2", small), 
+  "Level 1", 
+  big(big(small, "Level 3", small), "Level 2", small))
+
+%------------------------------------------------------------------------------%
+Width = 29, Limit = size_count(5, 0)
+
+big(big/3, "Level 1", big/3)
+
+%------------------------------------------------------------------------------%
+Width = 31, Limit = size_count(5, 0)
+
+big(
+  big(big/3, "Level 2", small), 
+  "Level 1", 
+  big(big/3, "Level 2", small))
+
+%------------------------------------------------------------------------------%
+Width = 74, Limit = size_count(2, 0)
+
+big(big(big/3, "Level 2", small), "Level 1", big(big/3, "Level 2", small))
+
+%------------------------------------------------------------------------------%
+Width = 20, Limit = size_count(10, 0)
+
+big(
+  big(
+    big/3, 
+    "Level 2", 
+    small), 
+  "Level 1", 
+  big(
+    big/3, 
+    "Level 2", 
+    small))
+
+%------------------------------------------------------------------------------%
+Width = 40, Limit = size_count(10, 0)
+
+big(
+  big(
+    big(small, "Level 3", small), 
+    "Level 2", 
+    small), 
+  "Level 1", 
+  big(
+    big(small, "Level 3", small), 
+    "Level 2", 
+    small))
+
+%------------------------------------------------------------------------------%
+Width = 28, Limit = size_count(1, 0)
+
+big(big/3, "Level 1", big/3)
+
+%------------------------------------------------------------------------------%
+Width = 20, Limit = size_count(1, 0)
+
+big/3
+
+%------------------------------------------------------------------------------%
+*/
+
+:- module sizepretty.
+
+:- interface.
+
+:- import_module std_util, list, pprint, bool, int, string.
+
+:- type measure_params
+	--->	measure_params
+	;	measure_params(int).
+
+:- type maybe_deconstructed(T)
+	--->	not_deconstructed
+	;	deconstructed(
+			string,
+			int,
+			list(maybe(pair(T, size_annotated_term(T))))  	
+		).
+
+:- type size_annotated_term(T)
+	--->	exact(
+			univ,
+			T,
+			string,
+			int,
+			list(maybe(pair(T, size_annotated_term(T))))
+		)
+	;	at_least(
+			univ,
+			T,
+			maybe_deconstructed(T)
+		).
+
+:- type functor_count
+	--->	functor_count(int).
+
+:- type char_count
+	--->	char_count(int).
+
+:- type size_count
+	--->	size_count(int, int).	
+
+:- typeclass measure(T) where [
+	func add_measures(T, T, measure_params) = T is det,
+	func subtract_measures(T, T, measure_params) = T is det,
+	func compare_measures(T, T) = comparison_result is det,
+	func max_measure(T, T) = T is det,
+	func zero_measure = T is det,
+	pred measured_split(univ::in, measure_params::in, T::in, int::in,
+	     bool::in, T::out, maybe(T)::out, T::out,measure_params::out) is det
+		
+].
+
+:- instance measure(functor_count).
+:- instance measure(char_count).
+:- instance measure(size_count).
+	
+	% This may throw an exception or cause a runtime abort if the term
+	% in question has user-defined equality.
+:- pred annotate_with_size(univ::in, measure_params::in, T::in,
+	size_annotated_term(T)::out) is det <= measure(T).
+
+	% A function to convert a size annotated term to a 'doc' type,
+	% a type defined in pprint.m.
+:- func my_to_doc(size_annotated_term(T)) = doc <= measure(T).
+
+:- implementation.
+
+:- import_module require, assoc_list.
+
+%------------------------------------------------------------------------------%
+	% first_pass gives an idea of how much space each term takes
+	% (In this pass the space is unevenly distributed. First come first
+	% served. In The Second pass the space is evenly distriduted between
+	% the terms.
+annotate_with_size(Univ, Params, Limit, Size2) :-
+	first_pass(Univ, Params, Limit, Size1),
+	second_pass(Size1, Params, Limit, Size2).
+
+%------------------------------------------------------------------------------%
+	
+:- pred first_pass(univ::in, measure_params::in, T::in,
+	size_annotated_term(T)::out) is det <= measure(T).
+
+first_pass(Univ, Params, Limit, Size) :-
+	deconstruct(univ_value(Univ), Functor, Arity, Args),	
+	measured_split(Univ, Params, Limit, Arity, yes, FunctorSize, 
+					Flag, NewLimit, NewParams),
+	flag_with(Args, Flag, FlaggedUnivArgs),
+	( (Arity \= 0, Flag = no) ->
+		Exact0 = no
+	;
+		Exact0 = yes
+	),
+        annotate_args_with_size(FlaggedUnivArgs, NewParams, NewLimit, 
+		FunctorSize, SoFar, Exact0, Exact, MaybeArgSizes),
+	(
+		Exact = no,
+	        Size = at_least(Univ, SoFar,
+	                        deconstructed(Functor, Arity, MaybeArgSizes))
+	;
+	        Exact = yes,
+	        Size = exact(Univ, SoFar, Functor, Arity, MaybeArgSizes)
+	).
+
+%------------------------------------------------------------------------------%
+	% annotating the arguments.
+:- pred annotate_args_with_size(assoc_list(maybe(T), univ)::in,
+	measure_params::in, T::in, T::in, T::out, bool::in, bool::out,
+	list(maybe(pair(T, size_annotated_term(T))))::out)
+	is det <= measure(T).
+
+annotate_args_with_size([], _, _, SoFar, SoFar, Exact, Exact, []).
+annotate_args_with_size([Flag - Arg | FlaggedArgs], Params, Limit,
+		SoFar0, SoFar, Exact0, Exact,
+		[MaybeFlaggedSize | MaybeFlaggedSizes]) :-
+	(
+		Flag = yes(ArgLimit),
+		AppliedArgLimit = max_measure(ArgLimit,
+			subtract_measures(Limit, SoFar0, Params)),
+		first_pass(Arg, Params, AppliedArgLimit, Size),
+		MaybeFlaggedSize = yes(ArgLimit - Size),
+		extract_size_from_annotation(Size) = ArgSize,
+		SoFar1 = add_measures(SoFar0, ArgSize, Params),
+		(
+			Size = exact(_, _, _, _, _),
+			Exact1 = Exact0
+		;
+			Size = at_least(_, _, _),
+			Exact1 = no
+		)
+	;
+		Flag = no,
+		MaybeFlaggedSize = no,
+		SoFar1 = SoFar0,
+		Exact1 = Exact0
+	),
+	( compare_measures(SoFar1, Limit) = (>) ->
+		SoFar = SoFar1,
+		Exact = no,
+		annotate_args_with_zero_size(FlaggedArgs, zero_measure,
+			MaybeFlaggedSizes)
+	;
+		annotate_args_with_size(FlaggedArgs, Params, Limit,
+			SoFar1, SoFar, Exact1, Exact, MaybeFlaggedSizes)
+	).
+
+%------------------------------------------------------------------------------%
+
+:- pred annotate_args_with_zero_size(assoc_list(maybe(T), univ)::in, T::in,
+	list(maybe(pair(T, size_annotated_term(T))))::out) is det <= measure(T).
+
+annotate_args_with_zero_size([], _, []).
+annotate_args_with_zero_size([Flag - Univ | FlaggedArgs], ZeroMeasure,
+		[FlaggedSize | FlaggedSizes]) :-
+	(
+		Flag = yes(ArgLimit),
+		FlaggedSize = yes(ArgLimit -
+			at_least(Univ, ZeroMeasure, not_deconstructed))
+	;
+		Flag = no,
+		FlaggedSize = no
+	),
+	annotate_args_with_zero_size(FlaggedArgs, ZeroMeasure, FlaggedSizes).
+
+%------------------------------------------------------------------------------%
+
+:- func extract_size_from_annotation(size_annotated_term(T)) = T.
+
+extract_size_from_annotation(exact(_, Size, _, _, _)) = Size.
+extract_size_from_annotation(at_least(_, Size, _)) = Size.
+
+%------------------------------------------------------------------------------%
+
+:- func extract_univ_from_annotation(size_annotated_term(T)) = univ.
+
+extract_univ_from_annotation(exact(Univ, _, _, _, _)) = Univ.
+extract_univ_from_annotation(at_least(Univ, _, _)) = Univ.
+
+%------------------------------------------------------------------------------%
+	% This predicate basically ensures that the arguments that
+	% take up smaller "Space" than their fair share is fully
+	% printed and the rest the Space is shared equally between
+	% the other terms which could take up more than their share.
+	% If a term can be fully printed within the given space,
+	% ("exact" type) then the Term is not altered.
+:- pred second_pass(size_annotated_term(T)::in, measure_params::in, T::in,
+	size_annotated_term(T)::out) is det <= measure(T).
+
+second_pass(OldSizeTerm, Params, Limit, NewSizeTerm) :-
+    if OldSizeTerm = exact(_Univ, _Size, _, _Arity, _MaybeArgs) then
+	NewSizeTerm = OldSizeTerm
+    else if OldSizeTerm = at_least(_Univ, _Size, not_deconstructed) then
+	NewSizeTerm = OldSizeTerm
+    else if OldSizeTerm = at_least(Univ, _Size, deconstructed(Functor, Arity,
+	MaybeArgs)) then
+	measured_split(Univ, Params, Limit, Arity, yes, FSize, Flag, NewLimit, 
+		NewParams),
+	( if Flag = yes(X) then
+	    ArgLimit = X,
+	    check_args(NewParams, MaybeArgs, ArgLimit, 0, Passed, 
+	   	zero_measure, Used),
+	    measured_split(Univ, Params, subtract_measures(NewLimit, Used, 
+	    	Params), Arity-Passed, no, _, Flag2, _, _),
+	    ( if Flag2 = yes(Y) then
+	        SplitLimit = Y,
+	        process_args(NewParams, MaybeArgs, ArgLimit, SplitLimit, 
+			NewArgs, NewSize0),
+		NewSize = add_measures(FSize, NewSize0, NewParams),
+		Result0 = list__map(check_if_exact, NewArgs),
+    		list__remove_adjacent_dups(Result0, Result),
+		( Result = [yes] ->
+			NewSizeTerm = exact(Univ, NewSize, Functor, 
+				Arity, NewArgs) 	
+	        ;
+			NewSizeTerm = at_least(Univ, NewSize, 
+				deconstructed(Functor, Arity, NewArgs))
+		)
+	    else
+	        NewSizeTerm = at_least(Univ, FSize, not_deconstructed)
+	    )
+	else
+	    NewSizeTerm = at_least(Univ, FSize, not_deconstructed)
+	)
+    else
+    	error("Incorrect type of Size Annotated Term").
+	
+%------------------------------------------------------------------------------%
+	% Given a list of size annotated terms(ie arguments) and a
+	% Limit, this predicate returns the values "Passed" and 
+	% "Used". Where "Passed" represents the number of terms that
+	% obey the Limit and are fully represented("exact") and "Used"
+	% represents the space that these terms take up.
+:- pred check_args(measure_params::in, list(maybe(pair(T, size_annotated_term(T)
+	)))::in, T::in, int::in, int::out, T::in, T::out) is det <= measure(T).
+
+check_args(_, [], _, Passed0, Passed0, Used0, Used0).
+check_args(Params, [HeadArg | Rest], ArgLimit, Passed0, Passed, Used0, Used) :-
+    if HeadArg = yes(X) then
+	X = _-STerm,
+	Size = extract_size_from_annotation(STerm), 
+	( if STerm = exact(_, _, _, _, _) then
+	    ( if compare_measures(ArgLimit, Size) = (<) then
+	    	check_args(Params, Rest, ArgLimit, Passed0, Passed, Used0, Used)
+	    else
+	    	check_args(Params, Rest, ArgLimit, Passed0+1, Passed, 
+				add_measures(Used0, Size, Params), Used)
+	    )
+	else
+	    check_args(Params, Rest, ArgLimit, Passed0, Passed, Used0, Used)
+	)
+    else
+	check_args(Params, Rest, ArgLimit, Passed0, Passed, Used0, Used).
+
+%------------------------------------------------------------------------------%
+	% This predicate accepts a list of size annotated terms(paired
+	% with a flag) and returns a list of the same type. This new
+	% list would consist of the same number of terms as the other
+	% but the terms which do not obey the limit or not fully 
+	% represented would be annoted again with a new limit
+	% (SplitLimit). The rest of the terms are left alone.
+:- pred process_args(measure_params::in, 
+	list(maybe(pair(T, size_annotated_term(T))))::in, T::in, T::in, 
+	list(maybe(pair(T, size_annotated_term(T))))::out, T::out)
+	is det <= measure(T).
+
+process_args(_, [], _, _, [], zero_measure).
+process_args(Params, [HeadArg | Rest], ArgLimit, SplitLimit, 
+		[NewHeadArg | NewRest], SizeOut) :-
+    ( if HeadArg = yes(X) then
+	X = _-STerm,
+	Size = extract_size_from_annotation(STerm), 
+        Univ = extract_univ_from_annotation(STerm), 
+	( if STerm = exact(_, _, _, _, _) then
+	    ( if compare_measures(ArgLimit, Size) = (<) then
+		NewHeadArg = yes(pair(SplitLimit, NewSTerm)),
+		annotate_with_size(Univ, Params, SplitLimit, NewSTerm)
+	    else
+		NewHeadArg = HeadArg
+	    )
+	else
+	    NewHeadArg = yes(pair(SplitLimit, NewSTerm)),
+	    annotate_with_size(Univ, Params, SplitLimit, NewSTerm)
+	)
+    else
+	NewHeadArg = no
+    ),
+    ( NewHeadArg = yes(_-Term) ->
+	NewSize = extract_size_from_annotation(Term),
+	SizeOut = add_measures(NewSize, RestSize, Params)
+    ;
+	SizeOut = RestSize
+    ),
+    process_args(Params, Rest, ArgLimit, SplitLimit, NewRest, RestSize).
+
+%------------------------------------------------------------------------------%
+	% checking if an size-annotated arg is an exact type (fully represented)
+:- func check_if_exact(maybe(pair(T, size_annotated_term(T)))) = bool.
+
+check_if_exact(no) = no.
+check_if_exact(yes(_-Term)) = Result:-
+	( Term = exact(_, _, _, _, _) ->
+		Result = yes
+	;
+		Result = no
+	).	
+
+%------------------------------------------------------------------------------%
+	% Converting size-annotated terms to 'doc' type
+my_to_doc(at_least(Univ, _, not_deconstructed)) = Doc :-
+	deconstruct(univ_value(Univ), Functor, Arity, _Args),
+	Doc = text(Functor) `<>` text("/") `<>` poly(i(Arity)).
+
+my_to_doc(at_least(_, _, deconstructed(Functor, Arity, MaybeArgs))) = Doc :-
+	Doc = my_to_doc2(Functor, Arity, MaybeArgs).
+
+my_to_doc(exact(_, _, Functor, Arity, MaybeArgs)) = Doc :-
+	Doc = my_to_doc2(Functor, Arity, MaybeArgs).
+
+%------------------------------------------------------------------------------%
+	% Assumes that every argument must be on a different line
+	% or all of them should be on the same line.
+:- func my_to_doc2(string, int, list(maybe(pair(T, size_annotated_term(T))))) 
+	= doc <= measure(T).
+
+my_to_doc2(Functor, _Arity, []) = text(Functor).
+
+my_to_doc2(Functor, Arity, [HeadArg|Tail]) = Doc :-
+    Args = list__map(handleArg, [HeadArg|Tail]),
+    list__remove_adjacent_dups(Args, NewArgs),
+    ( NewArgs \= [text("*")] -> 
+        (Doc = text(Functor) `<>`
+	      parentheses(
+	                 group(
+	                      nest(2,
+	                          line `<>` separated(id,comma_space_line, Args)
+	                          )
+	                      )
+	                 )
+	)
+    ;
+        Doc = text(Functor) `<>` text("/") `<>` poly(i(Arity))
+    ).
+	
+%------------------------------------------------------------------------------%
+
+:- func handleArg(maybe(pair(T,size_annotated_term(T)))) = doc <= measure(T).
+
+handleArg(yes(_ - Arg_Term)) = my_to_doc(Arg_Term). 
+handleArg(no) = text("*").
+
+%------------------------------------------------------------------------------%
+	% A predicate that creates an associated list of Univ and their
+	% individual Limit
+:- pred flag_with(list(univ)::in, maybe(T)::in,
+	assoc_list(maybe(T), univ)::out) is det.
+flag_with([], _, []).
+flag_with([Arg | Args], Flag, [Flag - Arg | FlaggedArgs]) :-
+	flag_with(Args, Flag, FlaggedArgs).
+
+%------------------------------------------------------------------------------%
+	% functor_count is a representation where the size of a term
+	% is measured by the number of function symbols.
+
+:- func add_functor_count(functor_count, functor_count, 
+	measure_params) = functor_count.
+
+add_functor_count(functor_count(A), functor_count(B), _) = functor_count(A + B).
+
+:- func subtract_functor_count(functor_count, functor_count, 
+	measure_params) = functor_count.
+
+subtract_functor_count(functor_count(A), functor_count(B), _) =
+	functor_count(A - B).
+
+:- func compare_functor_count(functor_count, functor_count) = comparison_result.
+
+compare_functor_count(functor_count(A), functor_count(B)) = R :-
+	compare(R, A, B).
+
+:- func max_functor_count(functor_count, functor_count) = functor_count.
+
+max_functor_count(functor_count(A), functor_count(B)) = functor_count(Max) :-
+	int__max(A, B, Max).
+
+:- func zero_functor_count = functor_count.
+
+zero_functor_count = functor_count(0).
+	
+	% Refer to size_count_split for comments.
+:- pred functor_count_split(univ::in, measure_params::in, functor_count::in,
+	int::in, bool::in, functor_count::out, maybe(functor_count)::out,
+	functor_count::out, measure_params::out) is det.
+
+functor_count_split(_, X, functor_count(Limit), Arity, _, functor_count(1),
+		Flag, functor_count(Limit), X) :-
+	( Arity = 0 ->
+		Flag = no
+	;
+		( Limit =< (Arity + 1) ->			
+			Flag = no
+		;
+			RoundUp = (Limit + Arity - 1) // Arity,
+			Flag = yes(functor_count(RoundUp))
+		)
+	).
+
+:- instance measure(functor_count) where [
+	func(add_measures/3) is add_functor_count,
+	func(subtract_measures/3) is subtract_functor_count,
+	func(compare_measures/2) is compare_functor_count,
+	func(max_measure/2) is max_functor_count,
+	func(zero_measure/0) is zero_functor_count,
+	pred(measured_split/9) is functor_count_split
+].
+
+%------------------------------------------------------------------------------%
+	% char_count is a representation where the size of a term is
+	% measured by the number of characters.
+
+:- func add_char_count(char_count, char_count, measure_params) = char_count.
+
+add_char_count(char_count(A), char_count(B), _) = char_count(A + B).
+
+:- func subtract_char_count(char_count, char_count, 
+	measure_params) = char_count.
+
+subtract_char_count(char_count(A), char_count(B), _) =
+	char_count(A - B).
+
+:- func compare_char_count(char_count, char_count) = comparison_result.
+
+compare_char_count(char_count(A), char_count(B)) = R :-
+	compare(R, A, B).
+
+:- func max_char_count(char_count, char_count) = char_count.
+
+max_char_count(char_count(A), char_count(B)) = char_count(Max) :-
+	int__max(A, B, Max).
+
+:- func zero_char_count = char_count.
+
+zero_char_count = char_count(0).
+
+	% Refer to size_count_split for comments.
+:- pred char_count_split(univ::in, measure_params::in, char_count::in,
+	int::in, bool::in, char_count::out, maybe(char_count)::out,
+	char_count::out, measure_params::out) is det.
+
+char_count_split(Univ, X, char_count(Limit), Arity, Check, 
+		char_count(FunctorSize), Flag, char_count(Limit), X) :-
+	deconstruct(univ_value(Univ), Functor, _, Args),
+	( Check = yes ->
+		get_arg_length(Args, TotalLength, _)
+	;
+		TotalLength = 0
+	),
+	FunctorSize = string__length(Functor) + 2*(Arity),
+	( Arity = 0 ->
+		Flag = no
+	;
+		( Limit =< (FunctorSize + TotalLength) ->
+			Flag = no
+		;
+			RoundUp = (Limit + Arity - FunctorSize) // Arity,
+			Flag = yes(char_count(RoundUp))
+		)
+	).
+
+:- instance measure(char_count) where [
+        func(add_measures/3) is add_char_count,
+        func(subtract_measures/3) is subtract_char_count,
+        func(compare_measures/2) is compare_char_count,
+        func(max_measure/2) is max_char_count,
+        func(zero_measure/0) is zero_char_count,
+        pred(measured_split/9) is char_count_split
+].
+
+%------------------------------------------------------------------------------%
+	% size_count is representation where the size of a term is
+	% measured by number of lines and number of characters.
+
+:- func add_size_count(size_count, size_count, measure_params) = size_count.
+
+add_size_count(size_count(L1, C1), size_count(L2, C2), 
+		Params) = size_count(Line, Char) :-
+	( Params = measure_params(W) ->
+		LineWidth = W
+	;
+		LineWidth = 80
+	),
+	( (L1 > 0 ; L2 > 0) ->
+		( C1 > 0 ->
+			R1 = L1 + 1
+		;
+			R1 = L1
+		),
+		( C2 > 0 ->
+			R2 = L2 +1
+		;	
+			R2 = L2
+		),
+		Line = R1 + R2,
+		Char = 0
+	;
+		( (C1 + C2) > LineWidth ->
+			Line = 1,
+			Char = 0
+		;
+			Line = 0,
+			Char = C1 + C2
+		)
+	).
+		
+	% Rounding up the Lines and subtracting works because we assume
+	% that each argument is a differnet line or they are all on 
+	% the same line. But this requires you to determine which case
+	% likely to happen before hand. For example if a term is to be
+	% on one line, you should do subtract_size_count(size_count(0, 
+	% LineLength), size_count(0, arglength)) rather than
+	% subtract_size_count(size_count(1, 0), size_count(0, arglength)).
+:- func subtract_size_count(size_count, size_count,measure_params) = size_count.
+
+subtract_size_count(size_count(L1, C1), size_count(L2, C2), _Params) 
+		= size_count(Line, Char) :-
+	( (L1 > 0 ; L2 > 0) ->
+		( C1 > 0 ->
+			R1 = L1 + 1
+		;
+			R1 = L1
+		),
+		( C2 > 0 ->
+			R2 = L2 +1
+		;	R2 = L2
+		),
+		Line0 = R1 - R2,
+		Char0 = 0
+	;
+		Line0 = 0,
+		Char0 = C1 - C2
+	),
+	( (Line0 < 0 ; Char0 < 0) ->
+		Line = 0,
+		Char = 0
+	;
+		Line = Line0,
+		Char = Char0
+	).
+
+:- func compare_size_count(size_count, size_count) = comparison_result.
+
+compare_size_count(size_count(L1, C1), size_count(L2, C2)) = R :-
+	L1 = L2 ->
+		compare(R, C1, C2)
+	;
+		compare(R, L1, L2).
+
+:- func max_size_count(size_count, size_count) = size_count.
+
+max_size_count(A, B) = Max :-
+	( compare_size_count(A, B) = (>) ->
+		Max = A
+	;
+		Max = B
+	).
+
+:- func zero_size_count = size_count.
+
+zero_size_count = size_count(0, 0).
+
+	% This code divides up the Limit into smaller Limits for
+	% the terms's arguments. We assume that all arguments have
+	% to be on separte lines, or the whole term should be printed
+	% on a single line.
+	% I have modified this code so that a term is not deconstructed
+	% unless it has enough space to print functor and the functors
+	% of it's arguments. But in some cases this check is not needed
+	% that's why the booleen is included.
+:- pred size_count_split(univ::in, measure_params::in, size_count::in,
+	int::in, bool::in, size_count::out, maybe(size_count)::out,
+	size_count::out, measure_params::out) is det.
+
+size_count_split(Univ, Params, Limit, Arity, Check, FunctorSize, 
+		Flag, NewLimit, NewParams) :-
+    ( Params = measure_params(X) ->
+        LineWidth = X	
+    ;
+	LineWidth = 80
+    ),
+    deconstruct(univ_value(Univ), Functor, ActualArity, Args),
+    FSize = string__length(Functor) + 2*(ActualArity),
+    ( Check = yes ->
+    	get_arg_length(Args, TotalLength, MaxLength)
+    ;
+    	TotalLength = 0,
+	MaxLength = 0
+    ), 
+    ( Arity = 0 ->
+	Flag = no,
+    	FunctorSize = size_count(0, FSize),
+	NewLimit = Limit,
+	NewParams = Params
+    ;
+	Limit = size_count(LineLimit, CharLimit),
+	( if (LineLimit >= (Arity + 1), (LineWidth - 2) >= MaxLength) then
+	    Line = (LineLimit - 1) // Arity,
+	    Char = 0,
+	    Flag = yes(size_count(Line, Char)),
+	    FunctorSize = size_count(1, 0),
+	    NewLimit = Limit,
+	    NewParams = measure_params(LineWidth - 2)
+	else if (LineLimit > 0, LineWidth >= (FSize + TotalLength)) then
+	    Line = 0,
+	    Char = (LineWidth - FSize + Arity - 1) // Arity ,
+	    Flag = yes(size_count(Line, Char)),
+	    FunctorSize = size_count(0, FSize),
+	    NewLimit = size_count(0, LineWidth),
+	    NewParams = Params
+   	else if (CharLimit >= (FSize + TotalLength)) then
+	   Line = 0,	
+	   Char = (CharLimit - FSize + Arity - 1)// Arity,
+	   Flag = yes(size_count(Line, Char)),
+	   FunctorSize = size_count(0, FSize),
+	   NewLimit = Limit,
+	   NewParams = Params
+	else
+	   Flag = no, 
+	   FunctorSize = size_count(0, string__length(Functor)+2),
+	   NewLimit = Limit, 
+	   NewParams = Params
+	) 	
+    ).
+
+:- instance measure(size_count) where [
+	func(add_measures/3) is add_size_count,
+	func(subtract_measures/3) is subtract_size_count,
+	func(compare_measures/2) is compare_size_count,
+	func(max_measure/2) is max_size_count,
+	func(zero_measure/0) is zero_size_count,
+	pred(measured_split/9) is size_count_split
+].
+
+%------------------------------------------------------------------------------%
+	% This predicate determines how many characters it will take
+	% to print the functors of the arguments. Also determines the
+	% length of biggest functor.
+:- pred get_arg_length(list(univ)::in, int::out, int::out) is det.
+
+get_arg_length([], 0, 0).
+get_arg_length([HeadUniv | Rest], TotalLength, MaxLength) :-
+	deconstruct(univ_value(HeadUniv), Functor, Arity, _),
+	( Arity = 0 -> 
+		Length = string__length(Functor)
+	;
+		% 2 is added because if a term has arguments then the
+		% shortest way to print it is "functor/Arity"
+		% Assuming Arity is a single digit
+		Length = string__length(Functor) + 2
+	),
+	TotalLength = Length + RestTotalLength,
+	int__max(Length, RestMaxLength, MaxLength),
+	get_arg_length(Rest, RestTotalLength, RestMaxLength).
+
+%------------------------------------------------------------------------------%
Index: trace/mercury_trace_browse.c
===================================================================
RCS file: /home/mercury1/repository/mercury/trace/mercury_trace_browse.c,v
retrieving revision 1.18
diff -u -r1.18 mercury_trace_browse.c
--- trace/mercury_trace_browse.c	2000/11/23 02:01:07	1.18
+++ trace/mercury_trace_browse.c	2001/01/11 07:17:30
@@ -142,8 +142,8 @@
 
 bool
 MR_trace_set_browser_param(MR_Bool print, MR_Bool browse, MR_Bool print_all,
-		MR_Bool flat, MR_Bool pretty, MR_Bool verbose,
-		const char *param, const char *value)
+		MR_Bool flat, MR_Bool pretty, MR_Bool verbose, 
+		MR_Bool newpretty, const char *param, const char *value)
 {
 	int			depth, size, width, lines;
 	MR_Browse_Format	new_format;
@@ -163,7 +163,7 @@
 	{
 		MR_TRACE_CALL_MERCURY(
 			ML_BROWSE_set_param_depth(print, browse, print_all,
-				flat, pretty, verbose, depth,
+				flat, pretty, verbose, newpretty, depth,
 				MR_trace_browser_persistent_state,
 				&MR_trace_browser_persistent_state);
 		);
@@ -172,7 +172,7 @@
 	{
 		MR_TRACE_CALL_MERCURY(
 			ML_BROWSE_set_param_size(print, browse, print_all,
-				flat, pretty, verbose, size,
+				flat, pretty, verbose, newpretty, size,
 				MR_trace_browser_persistent_state,
 				&MR_trace_browser_persistent_state);
 		);
@@ -181,7 +181,7 @@
 	{
 		MR_TRACE_CALL_MERCURY(
 			ML_BROWSE_set_param_width(print, browse, print_all,
-				flat, pretty, verbose, width,
+				flat, pretty, verbose, newpretty, width,
 				MR_trace_browser_persistent_state,
 				&MR_trace_browser_persistent_state);
 		);
@@ -190,7 +190,7 @@
 	{
 		MR_TRACE_CALL_MERCURY(
 			ML_BROWSE_set_param_lines(print, browse, print_all,
-				flat, pretty, verbose, lines,
+				flat, pretty, verbose, newpretty, lines,
 				MR_trace_browser_persistent_state,
 				&MR_trace_browser_persistent_state);
 		);
@@ -220,8 +220,10 @@
 	} else if (streq(str, "verbose")) {
 		*format = MR_BROWSE_FORMAT_VERBOSE;
 		return TRUE;
+	} else if (streq(str, "newpretty")) {
+		*format = MR_BROWSE_FORMAT_NEWPRETTY;
+		return TRUE;
 	}
-
 	return FALSE;
 }
 
Index: trace/mercury_trace_browse.h
===================================================================
RCS file: /home/mercury1/repository/mercury/trace/mercury_trace_browse.h,v
retrieving revision 1.9
diff -u -r1.9 mercury_trace_browse.h
--- trace/mercury_trace_browse.h	2000/10/27 08:38:56	1.9
+++ trace/mercury_trace_browse.h	2001/01/11 07:17:30
@@ -30,7 +30,8 @@
 typedef enum {
 	MR_BROWSE_FORMAT_FLAT,
 	MR_BROWSE_FORMAT_PRETTY,
-	MR_BROWSE_FORMAT_VERBOSE
+	MR_BROWSE_FORMAT_VERBOSE,
+	MR_BROWSE_FORMAT_NEWPRETTY
 } MR_Browse_Format;
 
 /*
@@ -59,7 +60,8 @@
 */
 extern	bool	MR_trace_set_browser_param(MR_Bool print, MR_Bool browse,
 			MR_Bool print_all, MR_Bool flat, MR_Bool pretty,
-			MR_Bool verbose, const char *param, const char *value);
+			MR_Bool verbose, MR_Bool newpretty, const char *param, 
+			const char *value);
 
 /*
 ** Invoke an interactive query.
Index: trace/mercury_trace_internal.c
===================================================================
RCS file: /home/mercury1/repository/mercury/trace/mercury_trace_internal.c,v
retrieving revision 1.93
diff -u -r1.93 mercury_trace_internal.c
--- trace/mercury_trace_internal.c	2001/01/09 23:30:26	1.93
+++ trace/mercury_trace_internal.c	2001/01/11 07:17:30
@@ -180,8 +180,9 @@
 static	bool	MR_trace_options_param_set(MR_Bool *print_set,
 			MR_Bool *browse_set, MR_Bool *print_all_set,
 			MR_Bool *flat_format, MR_Bool *pretty_format,
-			MR_Bool *verbose_format, char ***words,
-			int *word_count, const char *cat, const char *item);
+			MR_Bool *verbose_format, MR_Bool *newpretty_format, 
+			char ***words, int *word_count, const char *cat, 
+			const char *item);
 static	void	MR_trace_usage(const char *cat, const char *item);
 static	void	MR_trace_do_noop(void);
 
@@ -1093,19 +1094,20 @@
 		MR_Bool			flat_format;
 		MR_Bool			pretty_format;
 		MR_Bool			verbose_format;
+		MR_Bool			newpretty_format;
 
 		if (! MR_trace_options_param_set(&print_set, &browse_set,
 				&print_all_set, &flat_format, &pretty_format,
-				&verbose_format, &words, &word_count,
-				"browsing", "set"))
+				&verbose_format, &newpretty_format, &words, 
+				&word_count, "browsing", "set"))
 		{
 			; /* the usage message has already been printed */
 		}
 		else if (word_count != 3 ||
 				! MR_trace_set_browser_param(print_set,
 					browse_set, print_all_set, flat_format,
-					pretty_format, verbose_format,
-					words[1], words[2]))
+					pretty_format, verbose_format, 
+					newpretty_format, words[1], words[2]))
 		{
 			MR_trace_usage("browsing", "set");
 		}
@@ -2387,6 +2389,7 @@
 	{ "flat",	FALSE,	NULL,	'f' },
 	{ "pretty",	FALSE,	NULL,	'p' },
 	{ "verbose",	FALSE,	NULL,	'v' },
+	{ "newpretty",	FALSE,	NULL,	'x' },
 	{ NULL,		FALSE,	NULL,	0 }
 };
 
@@ -2398,7 +2401,7 @@
 
 	*format = MR_BROWSE_DEFAULT_FORMAT;
 	MR_optind = 0;
-	while ((c = MR_getopt_long(*word_count, *words, "fpv",
+	while ((c = MR_getopt_long(*word_count, *words, "fpvx",
 			MR_trace_format_opts, NULL)) != EOF)
 	{
 		switch (c) {
@@ -2415,6 +2418,10 @@
 				*format = MR_BROWSE_FORMAT_VERBOSE;
 				break;
 
+			case 'x':
+				*format = MR_BROWSE_FORMAT_NEWPRETTY;
+				break;
+
 			default:
 				MR_trace_usage(cat, item);
 				return FALSE;
@@ -2431,6 +2438,7 @@
 	{ "flat",	FALSE,	NULL,	'f' },
 	{ "pretty",	FALSE,	NULL,	'p' },
 	{ "verbose",	FALSE,	NULL,	'v' },
+	{ "newpretty",	FALSE,	NULL,	'x' },	
 	{ "print",	FALSE,	NULL,	'P' },
 	{ "browse",	FALSE,	NULL,	'B' },
 	{ "print-all",	FALSE,	NULL,	'A' },
@@ -2440,8 +2448,8 @@
 static bool
 MR_trace_options_param_set(MR_Bool *print_set, MR_Bool *browse_set,
 	MR_Bool *print_all_set, MR_Bool *flat_format, MR_Bool *pretty_format,
-	MR_Bool *verbose_format, char ***words, int *word_count,
-	const char *cat, const char *item)
+	MR_Bool *verbose_format, MR_Bool *newpretty_format, char ***words, 
+	int *word_count, const char *cat, const char *item)
 {
 	int	c;
 
@@ -2451,9 +2459,10 @@
 	*flat_format = FALSE;
 	*pretty_format = FALSE;
 	*verbose_format = FALSE;
+	*newpretty_format = FALSE;
 
 	MR_optind = 0;
-	while ((c = MR_getopt_long(*word_count, *words, "PBAfpv",
+	while ((c = MR_getopt_long(*word_count, *words, "PBAfpvx",
 			MR_trace_param_set_opts, NULL)) != EOF)
 	{
 		switch (c) {
@@ -2468,6 +2477,10 @@
 
 			case 'v':
 				*verbose_format = TRUE;
+				break;
+
+			case 'x':
+				*newpretty_format = TRUE;
 				break;
 
 			case 'P':



--------------------------------------------------------------------------
mercury-developers mailing list
Post messages to:       mercury-developers at cs.mu.oz.au
Administrative Queries: owner-mercury-developers at cs.mu.oz.au
Subscriptions:          mercury-developers-request at cs.mu.oz.au
--------------------------------------------------------------------------



More information about the developers mailing list