[m-rev.] for review: browser parameters

Zoltan Somogyi zs at cs.mu.OZ.AU
Mon Oct 6 16:49:15 AEST 2003


For review by anyone.

Zoltan.

Make browsing in the debugger more flexible by adding options to the "ls",
"print" and "set" commands of the browser. Make browsing in the debugger less
confusing by making the "set" command by default set the parameters used
not just by the "ls" command but also by the "print" command, both inside and
outside the browser. This is done by making "ls" and "print" synonyms inside
the term browser.

browser/parse.m:
	Replace the commands ls/0, ls/1 and print/1 with a single command,
	print/2. The arguments of print/2 specify
	
	- the presence or absence of options controlling which formatter to
	  use, and
	- the path to the subterm to look at (which the "ls" command had,
	  but not the "print" command).

	Change the set/1 command into the set/2 command, adding a field
	specifying the presence or absence of options controlling which
	caller type and/or which formatter parameters to set. The set/2
	command within the browser prompt now functions the same as the "set"
	command from the mdb prompt, because they now call the same code
	to update the parameter sets.

	Change the parsing infrastructure to allow the use of getopt to
	process the options, by keeping around the word structure even after
	tokenization.

	Comment out code that isn't called, but may be needed later
	for debugging.

	Update the block comment documenting the command syntax.

browser/browse.m:
	Conform to the change in the type of commands.

	Change the implementation of the "set" command. Instead of the default
	being to change only the parameter set used by the "ls" command, make
	the default the application of the change to all the parameter sets.
	If users want to restrict the change to apply only to the "ls" command,
	they can specify the -B option.

	Change the implementation of the set/0 command to report not just one
	set of parameters, but all of them, since they can now all be changed
	by the set/2 command.

	Update the help message, to show the new options and to group related
	commands together.

browser/browser_info.m:
	Provide variants of the predicates for changing settings that are
	specialized for the requirements of mdb and of the term browser.

	Change the default format for the browser to "flat", to match the
	default for the mdb "print" command. This was the default for the
	browser's print command as well. This changes the default behavior
	of the browser's "ls" command. Since "print" and "ls" had different
	defaults but are now synonyms, we had to break backward compatibility
	for one or the other. (Preserving different defaults for these two
	browser commands would create an unnecessarily complicated user
	interface with respect to the meaning of their options.)

browser/declarative_user.m:
	Make it possible to switch the parameter set used to by the declarative
	debugger to print atoms quickly yet consistently.

trace/mercury_trace_browse.c:
	Call the C versions of the parameter setting predicates. (The versions
	for use from within the term browser specify the parameters a different
	way).

tests/debugger/browser_test.exp:
tests/debugger/exception_value.exp:
tests/debugger/polymorphic_output.exp:
tests/debugger/declarative/browse_arg.exp:
	Update the expected outputs to comply with the changes above.

cvs diff: Diffing .
cvs diff: Diffing analysis
cvs diff: Diffing bindist
cvs diff: Diffing boehm_gc
cvs diff: Diffing boehm_gc/Mac_files
cvs diff: Diffing boehm_gc/cord
cvs diff: Diffing boehm_gc/cord/private
cvs diff: Diffing boehm_gc/doc
cvs diff: Diffing boehm_gc/include
cvs diff: Diffing boehm_gc/include/private
cvs diff: Diffing boehm_gc/tests
cvs diff: Diffing browser
Index: browser/browse.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/browser/browse.m,v
retrieving revision 1.38
diff -u -b -r1.38 browse.m
--- browser/browse.m	14 Sep 2003 22:24:27 -0000	1.38
+++ browser/browse.m	6 Oct 2003 06:25:50 -0000
@@ -115,11 +115,12 @@
 	int::in, int::out) is cc_multi.
 
 %---------------------------------------------------------------------------%
+
 :- implementation.
 
 :- import_module mdb__parse, mdb__util, mdb__frame, mdb__sized_pretty.
-:- import_module string, int, char, std_util.
-:- import_module parser, require, pprint, deconstruct.
+:- import_module string, int, char, map, std_util, getopt.
+:- import_module parser, require, pprint, getopt, deconstruct.
 
 %---------------------------------------------------------------------------%
 %
@@ -154,7 +155,6 @@
 % In the latter case we need to output terms; their type is 
 % term_browser_response.
 
-
 :- type term_browser_response 
 	--->	browser_str(string)
 	;	browser_int(int)
@@ -328,132 +328,207 @@
 
 prompt("browser> ").
 
-:- pred run_command(debugger::in, command::in, bool::out, browser_info::in,
-	browser_info::out, io__state::di, io__state::uo) is cc_multi.
+:- pred run_command(debugger::in, command::in, bool::out,
+	browser_info::in, browser_info::out, io__state::di, io__state::uo)
+	is cc_multi.
 
-run_command(Debugger, Command, Quit, Info0, Info) -->
+run_command(Debugger, Command, Quit, !Info, !IO) :-
 	% XXX The commands `set', `ls' and `print' should allow the format
 	% to be specified by an option.  In each case we instead pass `no' to
 	% the respective handler.
-	( { Command = empty },
-		{ Quit = no },
-		{ Info = Info0 }
-	; { Command = unknown },
+	(
+		Command = empty,
+		Quit = no
+	;
+		Command = unknown,
 		write_string_debugger(Debugger, 
-			"Error: unknown command or syntax error.\n"),
-		write_string_debugger(Debugger, "Type \"help\" for help.\n"),
-		{ Quit = no },
-		{ Info = Info0 }
-	; { Command = help },
-		help(Debugger),
-		{ Quit = no },
-		{ Info = Info0 }
-	; { Command = set },
-		show_settings(Debugger, Info0, no),
-		{ Quit = no },
-		{ Info = Info0 }
-	; { Command = set(Setting) },
-		{ set_browse_param(Info0 ^ caller_type, Setting,
-			Info0, Info) },
-		{ Quit = no }
-	; { Command = ls },
-		portray(Debugger, browse, no, Info0),
-		{ Quit = no },
-		{ Info = Info0 }
-	; { Command = ls(Path) },
-		portray_path(Debugger, browse, no, Info0, Path),
-		{ Quit = no },
-		{ Info = Info0 }
-	; { Command = cd },
-		{ set_path(root_rel([]), Info0, Info) },
-		{ Quit = no }
-	; { Command = cd(Path) },
-		{ change_dir(Info0 ^ dirs, Path, NewPwd) },
-		( { deref_subterm(Info0 ^ term, NewPwd, _SubUniv) } ->
-			{ Info = Info0 ^ dirs := NewPwd }
+			"Error: unknown command or syntax error.\n", !IO),
+		write_string_debugger(Debugger,
+			"Type \"help\" for help.\n", !IO),
+		Quit = no
+	;
+		Command = help,
+		help(Debugger, !IO),
+		Quit = no
+	;
+		Command = set,
+		show_settings(Debugger, !.Info, !IO),
+		Quit = no
+	;
+		Command = set(MaybeOptionTable, Setting),
+		(
+			MaybeOptionTable = ok(OptionTable),
+			set_browse_param(OptionTable, Setting, !Info)
+		;
+			MaybeOptionTable = error(Msg),
+			write_string_debugger(Debugger, Msg, !IO)
+		),
+		Quit = no
+	;
+		Command = cd,
+		set_path(root_rel([]), !Info),
+		Quit = no
+	;
+		Command = cd(Path),
+		change_dir(!.Info ^ dirs, Path, NewPwd),
+		( deref_subterm(!.Info ^ term, NewPwd, _SubUniv) ->
+			!:Info = !.Info ^ dirs := NewPwd
 		;
 			write_string_debugger(Debugger, 
-				"error: cannot change to subterm\n"),
-			{ Info = Info0 }
+				"error: cannot change to subterm\n", !IO)
 		),
-		{ Quit = no }
-	; { Command = print },
-		portray(Debugger, print, no, Info0),
-		{ Quit = no },
-		{ Info = Info0 }
-	; { Command = pwd },
-		write_path(Debugger, Info0 ^ dirs),
-		nl_debugger(Debugger),
-		{ Quit = no },
-		{ Info = Info0 }
-	; { Command = mark },
-		{ Quit = yes },
-		{ Info = Info0 ^ maybe_mark := yes(Info0 ^ dirs) }
-	; { Command = mark(Path) },
-		{ change_dir(Info0 ^ dirs, Path, NewPwd) },
-		( { deref_subterm(Info0 ^ term, NewPwd, _SubUniv) } ->
-			{ Quit = yes },
-			{ Info = Info0 ^ maybe_mark := yes(NewPwd) }
+		Quit = no
+	;
+		Command = print(PrintOption, MaybePath),
+		do_portray(Debugger, browse, PrintOption, !.Info,
+			MaybePath, !IO),
+		Quit = no
+	;
+		Command = pwd,
+		write_path(Debugger, !.Info ^ dirs, !IO),
+		nl_debugger(Debugger, !IO),
+		Quit = no
+	;
+		Command = mark,
+		!:Info = !.Info ^ maybe_mark := yes(!.Info ^ dirs),
+		Quit = yes
+	;
+		Command = mark(Path),
+		change_dir(!.Info ^ dirs, Path, NewPwd),
+		( deref_subterm(!.Info ^ term, NewPwd, _SubUniv) ->
+			!:Info = !.Info ^ maybe_mark := yes(NewPwd),
+			Quit = yes
 		;
 			write_string_debugger(Debugger, 
-				"error: cannot mark subterm\n"),
-			{ Quit = no },
-			{ Info = Info0 }
+				"error: cannot mark subterm\n", !IO),
+			Quit = no
 		)
-	; { Command = quit },
-		{ Quit = yes },
-		{ Info = Info0 }
-	; { Command = display },
+	;
+		Command = quit,
+		Quit = yes
+	;
+		Command = display,
 		write_string_debugger(Debugger,
-				"command not yet implemented\n"),
-		{ Quit = no },
-		{ Info = Info0 }
-	; { Command = write },
+			"command not yet implemented\n", !IO),
+		Quit = no
+	;
+		Command = write,
 		write_string_debugger(Debugger,
-				"command not yet implemented\n"),
-		{ Quit = no },
-		{ Info = Info0 }
+			"command not yet implemented\n", !IO),
+		Quit = no
 	),
-	( { Debugger = external } ->
-		send_term_to_socket(browser_end_command)
+	( Debugger = external ->
+		send_term_to_socket(browser_end_command, !IO)
 	;
-		{ true }
+		true
 	).
 
-:- pred set_browse_param(browse_caller_type::in, setting::in,
+:- pred do_portray(debugger::in, browse_caller_type::in,
+	maybe(maybe_option_table(format_option))::in, browser_info::in,
+	maybe(path)::in, io__state::di, io__state::uo) is cc_multi.
+
+do_portray(Debugger, CallerType, MaybeMaybeOptionTable, Info,
+		MaybePath, !IO) :-
+	(
+		MaybeMaybeOptionTable = no,
+		portray_maybe_path(Debugger, CallerType, no, Info,
+			MaybePath, !IO)
+	;
+		MaybeMaybeOptionTable = yes(MaybeOptionTable),
+		(
+			MaybeOptionTable = ok(OptionTable),
+			interpret_format_options(OptionTable, FormatResult),
+			(
+				FormatResult = ok(MaybeFormat),
+				portray_maybe_path(Debugger, CallerType,
+					MaybeFormat, Info, MaybePath, !IO)
+			;
+				FormatResult = error(Msg),
+				write_string_debugger(Debugger, Msg, !IO)
+			)
+		;
+			MaybeOptionTable = error(Msg),
+			write_string_debugger(Debugger, Msg, !IO)
+		)
+	).
+
+:- pred interpret_format_options(option_table(format_option)::in,
+	maybe_error(maybe(portray_format))::out) is det.
+
+interpret_format_options(OptionTable, MaybeMaybeFormat) :-
+	map__to_assoc_list(OptionTable, OptionAssocList),
+	list__filter_map(bool_format_option_is_true, OptionAssocList,
+		TrueFormatOptions),
+	(
+		TrueFormatOptions = [],
+		MaybeMaybeFormat = ok(no)
+	;
+		TrueFormatOptions = [FormatOption],
+		(
+			FormatOption = flat,
+			Format = flat
+		;
+			FormatOption = raw_pretty,
+			Format = raw_pretty
+		;
+			FormatOption = pretty,
+			Format = pretty
+		;
+			FormatOption = verbose,
+			Format = verbose
+		),
+		MaybeMaybeFormat = ok(yes(Format))
+	;
+		TrueFormatOptions = [_, _ | _],
+		MaybeMaybeFormat = error("error: inconsistent format options")
+	).
+
+:- pred bool_format_option_is_true(pair(format_option, option_data)::in,
+	format_option::out) is semidet.
+
+bool_format_option_is_true(Format - bool(yes), Format).
+
+:- pred set_browse_param(option_table(setting_option)::in, setting::in,
 	browser_info::in, browser_info::out) is det.
 
-set_browse_param(CallerType, Setting, Info0, Info) :-
-	%
-	% XXX We can't yet give options to the `set' command.
-	%
-	No = bool__no,
-	browser_info__set_param(yes(CallerType), No, No, No, No, Setting, 
-			Info0 ^ state, NewState),
+set_browse_param(OptionTable, Setting, Info0, Info) :-
+	browser_info__set_param(yes,
+		lookup_bool_option(OptionTable, print) `with_type` bool,
+		lookup_bool_option(OptionTable, browse) `with_type` bool,
+		lookup_bool_option(OptionTable, print_all) `with_type` bool,
+		lookup_bool_option(OptionTable, flat) `with_type` bool,
+		lookup_bool_option(OptionTable, raw_pretty) `with_type` bool,
+		lookup_bool_option(OptionTable, verbose) `with_type` bool,
+		lookup_bool_option(OptionTable, pretty) `with_type` bool,
+		Setting, Info0 ^ state, NewState),
 	Info = Info0 ^ state := NewState.
 
 :- pred help(debugger::in, io__state::di, io__state::uo) is det.
+
 help(Debugger) -->
 	{ string__append_list([
 "Commands are:\n",
-"\tls [path]      -- list subterm (expanded)\n",
-"\tcd [path]      -- cd current subterm (default is root)\n",
-"\thelp           -- show this help message\n",
-"\tset var value  -- set a setting\n",
-"\tset            -- show settings\n",
-"\tprint          -- show single line representation of current term\n",
-"\tquit           -- quit browser\n",
+"\t[print|p|ls] [format_options] [path]\n",
+"\t               -- print the specified subterm using the `browse' params\n",
+"\tcd [path]      -- cd to the specified subterm (default is root)\n",
+"\tpwd            -- print the path to the current subterm\n",
+"\tset [setting_options] var value\n",
+"\t               -- set a parameter value\n",
+"\tset            -- show parameter values\n",
 "\tmark [path]    -- mark the given subterm (default is current) and quit\n",
+"\tquit           -- quit browser\n",
+"\thelp           -- show this help message\n",
 "SICStus Prolog style commands are:\n",
 "\tp              -- print\n",
 "\t< n            -- set depth\n",
-"\t^ [path]       -- cd [path] (default is root)\n",
+"\t^ [path]       -- cd to the specified subterm (default is root)\n",
 "\t?              -- help\n",
 "\th              -- help\n",
 "\n",
-"-- settings:\n",
+"-- Parameter variables with integer values:\n",
 "--    size <n>; depth <n>; path <n>; width <n>; lines <n>; num_io_actions <n>;\n",
-"--    format <flat,raw_pretty,verbose,pretty>; ",
+"-- Parameter variables with non-integer values:\n",
+"--  format <flat,raw_pretty,verbose,pretty>;\n",
 "--    Paths can be Unix-style or SICStus-style: /2/3/1 or ^2^3^1\n",
 "\n"],
 		HelpMessage) },
@@ -464,6 +539,19 @@
 % Various pretty-print routines
 %
 
+:- pred portray_maybe_path(debugger::in, browse_caller_type::in,
+	maybe(portray_format)::in, browser_info::in,
+	maybe(path)::in, io__state::di, io__state::uo) is cc_multi.
+
+portray_maybe_path(Debugger, Caller, MaybeFormat, Info, MaybePath, !IO) :-
+	(
+		MaybePath = no,
+		portray(Debugger, Caller, MaybeFormat, Info, !IO)
+	;
+		MaybePath = yes(Path),
+		portray_path(Debugger, Caller, MaybeFormat, Info, Path, !IO)
+	).
+
 :- pred portray(debugger::in, browse_caller_type::in,
 	maybe(portray_format)::in, browser_info::in,
 	io__state::di, io__state::uo) is cc_multi.
@@ -591,16 +679,13 @@
 max_print_size = 60.
 
 term_size_left_from_max(Univ, MaxSize, RemainingSize) :-
-	(
-		MaxSize < 0
-	->
+	( MaxSize < 0 ->
 		RemainingSize = MaxSize
 	;
-		std_util__limited_deconstruct_cc(univ_value(Univ), MaxSize,
+		deconstruct__limited_deconstruct_cc(univ_value(Univ), MaxSize,
 				MaybeFunctorArityArgs),
 		(
-			MaybeFunctorArityArgs = yes({Functor, Arity, Args})
-		->
+			MaybeFunctorArityArgs = yes({Functor, Arity, Args}),
 			string__length(Functor, FunctorSize),
 			% "()", plus Arity-1 times ", "
 			PrincipalSize = FunctorSize + Arity * 2,
@@ -608,6 +693,7 @@
 			list__foldl(term_size_left_from_max,
 				Args, MaxArgsSize, RemainingSize)
 		;
+			MaybeFunctorArityArgs = no,
 			RemainingSize = -1
 		)
 	;
@@ -985,7 +1071,6 @@
 write_path(Debugger, [Dir, Dir2 | Dirs]) -->
 	write_path_2(Debugger, [Dir, Dir2 | Dirs]).
 
-
 :- pred write_path_2(debugger, list(dir), io__state, io__state).
 :- mode write_path_2(in, in, di, uo) is det.
 write_path_2(Debugger, []) -->
@@ -1141,49 +1226,104 @@
 % Display predicates.
 %
 
-:- pred show_settings(debugger, browser_info, maybe(portray_format),
-		io__state, io__state).
-:- mode show_settings(in, in, in, di, uo) is det.
-
-show_settings(Debugger, Info, MaybeFormat) -->
-	{ browser_info__get_format(Info, browse, MaybeFormat, Format) },
-	{ browser_info__get_format_params(Info, browse, Format, Params) },
-	write_string_debugger(Debugger, "Max depth is: "), 
-		write_int_debugger(Debugger, Params ^ depth), 
-		nl_debugger(Debugger),
-	write_string_debugger(Debugger, "Max size is: "), 
-		write_int_debugger(Debugger, Params ^ size), 
-		nl_debugger(Debugger),
-	write_string_debugger(Debugger, "X clip is: "), 
-		write_int_debugger(Debugger, Params ^ width), 
-		nl_debugger(Debugger),
-	write_string_debugger(Debugger, "Y clip is: "), 
-		write_int_debugger(Debugger, Params ^ lines),
-		nl_debugger(Debugger),
-	write_string_debugger(Debugger, "Current path is: "),
-		write_path(Debugger, Info ^ dirs),
-		nl_debugger(Debugger),
-	{ browser_info__get_format(Info, browse, no, LsFormat) },
-	write_string_debugger(Debugger, "Ls format is "),
-		print_format_debugger(Debugger, LsFormat),
-		nl_debugger(Debugger),
-	{ browser_info__get_format(Info, print, no, PrintFormat) },
-	write_string_debugger(Debugger, "Print format is "),
-		print_format_debugger(Debugger, PrintFormat),
-		nl_debugger(Debugger),
-	write_string_debugger(Debugger, "Number of I/O actions printed is: "),
+:- pred show_settings(debugger::in, browser_info::in,
+	io__state::di, io__state::uo) is det.
+
+show_settings(Debugger, Info, !IO) :-
+	show_settings_caller(Debugger, Info, browse, "Browser", !IO),
+	show_settings_caller(Debugger, Info, print, "Print", !IO),
+	show_settings_caller(Debugger, Info, print_all, "Printall", !IO),
+
+	write_string_debugger(Debugger, "Current path is: ", !IO),
+	write_path(Debugger, Info ^ dirs, !IO),
+	nl_debugger(Debugger, !IO),
+
+	write_string_debugger(Debugger,
+		"Number of I/O actions printed is: ", !IO),
 		write_int_debugger(Debugger,
-			get_num_printed_io_actions(Info ^ state)),
-		nl_debugger(Debugger).
+		get_num_printed_io_actions(Info ^ state), !IO),
+	nl_debugger(Debugger, !IO).
+
+:- pred show_settings_caller(debugger::in, browser_info::in,
+	browse_caller_type::in, string::in,
+	io__state::di, io__state::uo) is det.
+
+show_settings_caller(Debugger, Info, Caller, CallerName, !IO) :-
+	browser_info__get_format(Info, Caller, no, Format),
+	write_string_debugger(Debugger,
+		CallerName ++ " default format: ", !IO),
+	print_format_debugger(Debugger, Format, !IO),
+	nl_debugger(Debugger, !IO),
+
+	write_string_debugger(Debugger,
+		pad_right("", ' ', row_name_len), !IO),
+	write_string_debugger(Debugger,
+		pad_right("depth", ' ', depth_len), !IO),
+	write_string_debugger(Debugger,
+		pad_right("size", ' ', size_len), !IO),
+	write_string_debugger(Debugger,
+		pad_right("x clip", ' ', x_len), !IO),
+	write_string_debugger(Debugger,
+		pad_right("y clip", ' ', y_len), !IO),
+	nl_debugger(Debugger, !IO),
+
+	show_settings_caller_format(Debugger, Info, Caller, CallerName,
+		flat, "flat", !IO),
+	show_settings_caller_format(Debugger, Info, Caller, CallerName,
+		verbose, "verbose", !IO),
+	show_settings_caller_format(Debugger, Info, Caller, CallerName,
+		pretty, "pretty", !IO),
+	show_settings_caller_format(Debugger, Info, Caller, CallerName,
+		raw_pretty, "raw_pretty", !IO),
+	nl_debugger(Debugger, !IO).
+
+:- pred show_settings_caller_format(debugger::in, browser_info::in,
+	browse_caller_type::in, string::in, portray_format::in, string::in,
+	io__state::di, io__state::uo) is det.
+
+show_settings_caller_format(Debugger, Info, Caller, CallerName,
+		Format, FormatName, !IO) :-
+	browser_info__get_format_params(Info, Caller, Format, Params),
+	write_string_debugger(Debugger,
+		pad_right(CallerName ++ " " ++ FormatName ++ ":",
+			' ', row_name_len),
+		!IO),
+	write_string_debugger(Debugger,
+		pad_right(" ", ' ', centering_len), !IO),
+	write_string_debugger(Debugger,
+		pad_right(int_to_string(Params ^ depth), ' ', depth_len), !IO),
+	write_string_debugger(Debugger,
+		pad_right(int_to_string(Params ^ size), ' ', size_len), !IO),
+	write_string_debugger(Debugger,
+		pad_right(int_to_string(Params ^ width), ' ', x_len), !IO),
+	write_string_debugger(Debugger,
+		pad_right(int_to_string(Params ^ lines), ' ', y_len), !IO),
+	nl_debugger(Debugger, !IO).
+
+:- func row_name_len = int.
+:- func centering_len = int.
+:- func depth_len = int.
+:- func size_len = int.
+:- func x_len = int.
+:- func y_len = int.
+
+row_name_len  = 30.
+centering_len =  3.
+depth_len     = 10.
+size_len      = 10.
+x_len         = 10.
+y_len         = 10.
 
 :- pred string_to_path(string, path).
 :- mode string_to_path(in, out) is semidet.
+
 string_to_path(Str, Path) :-
 	string__to_char_list(Str, Cs),
 	chars_to_path(Cs, Path).
 
 :- pred chars_to_path(list(char), path).
 :- mode chars_to_path(in, out) is semidet.
+
 chars_to_path([C | Cs], Path) :-
 	( C = ('/') ->
 		Path = root_rel(Dirs),
@@ -1195,12 +1335,14 @@
 
 :- pred chars_to_dirs(list(char), list(dir)).
 :- mode chars_to_dirs(in, out) is semidet.
+
 chars_to_dirs(Cs, Dirs) :-
 	split_dirs(Cs, Names),
 	names_to_dirs(Names, Dirs).
 
 :- pred names_to_dirs(list(string), list(dir)).
 :- mode names_to_dirs(in, out) is semidet.
+
 names_to_dirs([], []).
 names_to_dirs([Name | Names], Dirs) :-
 	( Name = ".." ->
@@ -1216,9 +1358,9 @@
 		names_to_dirs(Names, RestDirs)
 	).
 
-
 :- pred split_dirs(list(char), list(string)).
 :- mode split_dirs(in, out) is det.
+
 split_dirs(Cs, Names) :-
 	takewhile(not_slash, Cs, NameCs, Rest),
 	string__from_char_list(NameCs, Name),
@@ -1233,9 +1375,9 @@
 		error("split_dirs: software error")
 	).
 		
-		
 :- pred not_slash(char).
 :- mode not_slash(in) is semidet.
+
 not_slash(C) :-
 	C \= ('/').
 
@@ -1245,6 +1387,7 @@
 	% to a limit.
 :- pred simplify_dirs(list(dir), list(dir)).
 :- mode simplify_dirs(in, out) is det.
+
 simplify_dirs(Dirs, SimpleDirs) :-
 	util__limit(simplify, Dirs, SimpleDirs).
 
@@ -1256,6 +1399,7 @@
 	%
 :- pred simplify(list(dir), list(dir)).
 :- mode simplify(in, out) is det.
+
 simplify([], []).
 simplify([First | Rest], Simplified) :-
 	( First = parent ->
@@ -1273,6 +1417,7 @@
 
 :- pred write_string_debugger(debugger, string, io__state, io__state).
 :- mode write_string_debugger(in, in, di, uo) is det.
+
 write_string_debugger(internal, String) -->
 	io__write_string(String).
 write_string_debugger(external, String) -->
@@ -1280,6 +1425,7 @@
 
 :- pred nl_debugger(debugger, io__state, io__state).
 :- mode nl_debugger(in, di, uo) is det.
+
 nl_debugger(internal) -->
 	io__nl.
 nl_debugger(external) -->
@@ -1287,14 +1433,15 @@
 
 :- pred write_int_debugger(debugger, int, io__state, io__state).
 :- mode write_int_debugger(in, in, di, uo) is det.
+
 write_int_debugger(internal, Int) -->
 	io__write_int(Int).
 write_int_debugger(external, Int) -->
 	send_term_to_socket(browser_int(Int)).
 
-
 :- pred print_format_debugger(debugger, portray_format, io__state, io__state).
 :- mode print_format_debugger(in, in, di, uo) is det.
+
 print_format_debugger(internal, X) -->
 	io__print(X).
 print_format_debugger(external, X) -->
@@ -1314,6 +1461,7 @@
 
 :- pred send_term_to_socket(term_browser_response, io__state, io__state).
 :- mode send_term_to_socket(in, di, uo) is det.
+
 send_term_to_socket(Term) -->
 	write(Term),
 	print(".\n"),
Index: browser/browser_info.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/browser/browser_info.m,v
retrieving revision 1.12
diff -u -b -r1.12 browser_info.m
--- browser/browser_info.m	14 Sep 2003 22:24:27 -0000	1.12
+++ browser/browser_info.m	14 Sep 2003 22:28:35 -0000
@@ -135,21 +135,23 @@
 :- pred browser_info__init_persistent_state(browser_persistent_state).
 :- mode browser_info__init_persistent_state(out) is det.
 
-	% Update a setting in the browser state.  The first seven arguments
-	% indicate the presence of the `set' options -P, -B, -A, -f, -r, -v
-	% and -p, in that order.
+	% Update a setting in the browser state.  The first argument should be
+	% true iff the set command is invoked from within the browser. The next
+	% seven arguments indicate the presence of the `set' options
+	% -P, -B, -A, -f, -r, -v and -p, in that order.
 	%
 :- pred browser_info__set_param(bool::in, bool::in, bool::in, bool::in,
-	bool::in, bool::in, bool::in, setting::in, 
+	bool::in, bool::in, bool::in, bool::in, setting::in, 
 	browser_persistent_state::in, browser_persistent_state::out) is det.
 
-	% Update a setting in the browser state.  The first argument
-	% indicates the presence of at most one of the options -P, -B, -A,
-	% while the next four indicate the presence of -f, -r, -v and -p,
-	% in that order.
+	% Update a setting in the browser state.  The first argument should be
+	% true iff the set command is invoked from within the browser. The next
+	% argument indicates the presence of at most one of the options
+	% -P, -B, -A, while the next four indicate the presence of -f, -r, -v
+	% and -p, in that order.
 	%
-:- pred browser_info__set_param(maybe(browse_caller_type)::in, bool::in,
-	bool::in, bool::in, bool::in, setting::in, 
+:- pred browser_info__set_param(bool::in, maybe(browse_caller_type)::in,
+	bool::in, bool::in, bool::in, bool::in, setting::in, 
 	browser_persistent_state::in, browser_persistent_state::out) is det.
 
 %---------------------------------------------------------------------------%
@@ -193,53 +195,53 @@
 	% call browser_info__set_param from C code.
 	%
 
-:- pred set_param_depth(bool::in, bool::in, bool::in, bool::in, bool::in,
-		bool::in, bool::in, int::in, browser_persistent_state::in,
+:- pred set_param_depth_from_mdb(bool::in, bool::in, bool::in, bool::in,
+	bool::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, in, out),
-		"ML_BROWSE_set_param_depth").
+:- pragma export(set_param_depth_from_mdb(in, in, in, in, in, in, in, in,
+	in, out), "ML_BROWSE_set_param_depth_from_mdb").
 
-set_param_depth(P, B, A, F, Pr, V, NPr, Depth) -->
-	browser_info__set_param(P, B, A, F, Pr, V, NPr,  depth(Depth)).
+set_param_depth_from_mdb(P, B, A, F, Pr, V, NPr, Depth) -->
+	browser_info__set_param(no, 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, bool::in, int::in, browser_persistent_state::in,
+:- pred set_param_size_from_mdb(bool::in, bool::in, bool::in, bool::in,
+	bool::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, in, out),
-		"ML_BROWSE_set_param_size").
+:- pragma export(set_param_size_from_mdb(in, in, in, in, in, in, in, in,
+	in, out), "ML_BROWSE_set_param_size_from_mdb").
 
-set_param_size(P, B, A, F, Pr, NPr, V, Size) -->
-	browser_info__set_param(P, B, A, F, Pr, V, NPr, size(Size)).
+set_param_size_from_mdb(P, B, A, F, Pr, NPr, V, Size) -->
+	browser_info__set_param(no, 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, bool::in, int::in, browser_persistent_state::in,
+:- pred set_param_width_from_mdb(bool::in, bool::in, bool::in, bool::in,
+	bool::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, in, out),
-		"ML_BROWSE_set_param_width").
+:- pragma export(set_param_width_from_mdb(in, in, in, in, in, in, in, in,
+	in, out), "ML_BROWSE_set_param_width_from_mdb").
 
-set_param_width(P, B, A, F, Pr, V, NPr, Width) -->
-	browser_info__set_param(P, B, A, F, Pr, V, NPr, width(Width)).
+set_param_width_from_mdb(P, B, A, F, Pr, V, NPr, Width) -->
+	browser_info__set_param(no, 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, 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, in, out),
-		"ML_BROWSE_set_param_lines").
+:- pred set_param_lines_from_mdb(bool::in, bool::in, bool::in, bool::in,
+	bool::in, bool::in, bool::in, int::in,
+	browser_persistent_state::in, browser_persistent_state::out) is det.
+:- pragma export(set_param_lines_from_mdb(in, in, in, in, in, in, in, in,
+	in, out), "ML_BROWSE_set_param_lines_from_mdb").
 
-set_param_lines(P, B, A, F, Pr, V, NPr, Lines) -->
-	browser_info__set_param(P, B, A, F, Pr, V, NPr, lines(Lines)).
+set_param_lines_from_mdb(P, B, A, F, Pr, V, NPr, Lines) -->
+	browser_info__set_param(no, 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)
-		is det.
-:- pragma export(set_param_format(in, in, in, in, in, out),
-		"ML_BROWSE_set_param_format").
+:- pred set_param_format_from_mdb(bool::in, bool::in, bool::in,
+	portray_format::in, browser_persistent_state::in,
+	browser_persistent_state::out) is det.
+:- pragma export(set_param_format_from_mdb(in, in, in, in, in, out),
+	"ML_BROWSE_set_param_format_from_mdb").
 
-set_param_format(P, B, A, Format) -->
+set_param_format_from_mdb(P, B, A, Format) -->
 	%
 	% Any format flags are ignored for this parameter.
 	%
-	browser_info__set_param(P, B, A, no, no, no, no, format(Format)).
+	browser_info__set_param(no, P, B, A, no, no, no, no, format(Format)).
 
 	%
 	% The following exported functions allow C code to create
@@ -248,10 +250,12 @@
 
 :- func mercury_bool_yes = bool.
 :- pragma export(mercury_bool_yes = out, "ML_BROWSE_mercury_bool_yes").
+
 mercury_bool_yes = yes.
 
 :- func mercury_bool_no = bool.
 :- pragma export(mercury_bool_no = out, "ML_BROWSE_mercury_bool_no").
+
 mercury_bool_no = no.
 
 %---------------------------------------------------------------------------%
@@ -337,7 +341,7 @@
 :- mode caller_type_browse_defaults(out) is det.
 
 caller_type_browse_defaults(Params) :-
-	DefaultFormat = verbose,
+	DefaultFormat = flat,
 	Flat	  = format_params(10, 30, 80, 25),
 	RawPretty = format_params(10, 30, 80, 25),
 	Verbose	  = format_params(10, 30, 80, 25),
@@ -362,18 +366,34 @@
 % context.
 num_printed_io_actions_default = 20.
 
-browser_info__set_param(MaybeCallerType, F0, Pr0, V0, NPr0, Setting, State0,
-		State) :-
-	affected_caller_types(MaybeCallerType, P, B, A),
-	browser_info__set_param(P, B, A, F0, Pr0, V0, NPr0, Setting, State0,
-		State).
+browser_info__set_param(FromBrowser, MaybeCallerType, F0, Pr0, V0, NPr0,
+		Setting, State0, State) :-
+	affected_caller_types(FromBrowser, MaybeCallerType, P, B, A),
+	browser_info__set_param(FromBrowser, P, B, A, F0, Pr0, V0, NPr0,
+		Setting, State0, State).
 
-browser_info__set_param(P0, B0, A0, F0, Pr0, V0, NPr0, Setting, State0,
-		State) :-
+browser_info__set_param(FromBrowser, P0, B0, A0, F0, Pr0, V0, NPr0,
+		Setting, State0, State) :-
 	( Setting = num_io_actions(NumIoActions) ->
 		State = State0 ^ num_printed_io_actions := NumIoActions
 	;
-		default_all_yes(P0, B0, A0, P, B, A),
+		(
+			FromBrowser = no,
+			default_all_yes(P0, B0, A0, P, B, A)
+		;
+			FromBrowser = yes,
+			(
+				P0 = no,
+				B0 = no,
+				A0 = no
+			->
+				affected_caller_types(FromBrowser, no, P, B, A)
+			;
+				P = P0,
+				B = B0,
+				A = A0
+			)
+		),
 		default_all_yes(F0, Pr0, V0, NPr0, F, Pr, V, NPr),
 		PParams0 = State0 ^ print_params,
 		BParams0 = State0 ^ browse_params,
@@ -385,17 +405,19 @@
 			State0 ^ num_printed_io_actions)
 	).
 
-:- pred affected_caller_types(maybe(browse_caller_type)::in,
+:- pred affected_caller_types(bool::in, maybe(browse_caller_type)::in,
 	bool::out, bool::out, bool::out) is det.
 
 	%
-	% If no caller type is specified, the command by default
-	% applies to _all_ caller types.
-	%
-affected_caller_types(no,             yes, yes, yes).
-affected_caller_types(yes(print),     yes, no, no).
-affected_caller_types(yes(browse),    no, yes, no).
-affected_caller_types(yes(print_all), no, no, yes).
+	% If no caller type is specified, the set command by default
+	% applies to _all_ caller types if invoked from the mdb prompt,
+	% and to the browser only if invoked from the browser prompt.
+	%
+affected_caller_types(no, no,            yes, yes, yes).
+affected_caller_types(yes, no,           no, yes, no).
+affected_caller_types(_, yes(print),     yes, no, no).
+affected_caller_types(_, yes(browse),    no, yes, no).
+affected_caller_types(_, yes(print_all), no, no, yes).
 
 :- pred default_all_yes(bool, bool, bool, bool, bool, bool).
 :- mode default_all_yes(in, in, in, out, out, out) is det.
@@ -479,16 +501,15 @@
 maybe_set_param_2(yes, num_io_actions(_), _, _) :-
 	error("maybe_set_param_2: num_io_actions").
 
-:- pred get_caller_params(browser_persistent_state, browse_caller_type,
-		caller_params).
-:- mode get_caller_params(in, in, out) is det.
+:- pred get_caller_params(browser_persistent_state::in, browse_caller_type::in,
+	caller_params::out) is det.
 
 get_caller_params(State, print, State ^ print_params).
 get_caller_params(State, browse, State ^ browse_params).
 get_caller_params(State, print_all, State ^ print_all_params).
 
-:- pred get_caller_format_params(caller_params, portray_format, format_params).
-:- mode get_caller_format_params(in, in, out) is det.
+:- pred get_caller_format_params(caller_params::in, portray_format::in,
+	format_params::out) is det.
 
 get_caller_format_params(Params, flat, Params ^ flat_params).
 get_caller_format_params(Params, raw_pretty, Params ^ raw_pretty_params).
Index: browser/declarative_user.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/browser/declarative_user.m,v
retrieving revision 1.24
diff -u -b -r1.24 declarative_user.m
--- browser/declarative_user.m	3 Feb 2003 05:19:25 -0000	1.24
+++ browser/declarative_user.m	5 Aug 2003 04:16:37 -0000
@@ -367,7 +367,8 @@
 		{ ArgInfo = arg_info(_, _, MaybeArg) },
 		{ MaybeArg = yes(Arg) }
 	->
-		print(univ_value(Arg), User0 ^ outstr, print, User0 ^ browser),
+		print(univ_value(Arg), User0 ^ outstr, decl_caller_type,
+			User0 ^ browser),
 		{ OK = yes }
 	;
 		io__write_string(User0 ^ outstr, "Invalid argument number\n"),
@@ -590,6 +591,12 @@
 
 %-----------------------------------------------------------------------------%
 
+	% Returns the caller type we want to use throughout the
+	% declarative debugger.
+:- func decl_caller_type = browse_caller_type.
+
+decl_caller_type = print.
+
 	% Display the node in user readable form on the current
 	% output stream.
 	%
@@ -597,10 +604,10 @@
 	io__state::di, io__state::uo) is cc_multi.
 
 write_decl_question(wrong_answer(_, Atom), User) -->
-	write_decl_final_atom(User, "", print, Atom).
+	write_decl_final_atom(User, "", decl_caller_type, Atom).
 	
 write_decl_question(missing_answer(_, Call, Solns), User) -->
-	write_decl_init_atom(User, "Call ", print, Call),
+	write_decl_init_atom(User, "Call ", decl_caller_type, Call),
 	(
 		{ Solns = [] }
 	->
@@ -611,7 +618,7 @@
 	).
 
 write_decl_question(unexpected_exception(_, Call, Exception), User) -->
-	write_decl_init_atom(User, "Call ", print, Call),
+	write_decl_init_atom(User, "Call ", decl_caller_type, Call),
 	io__write_string(User ^ outstr, "Throws "),
 	io__write(User ^ outstr, include_details_cc, univ_value(Exception)),
 	io__nl(User ^ outstr).
@@ -623,16 +630,16 @@
 	(
 		{ EBug = incorrect_contour(Atom, _, _) },
 		io__write_string(User ^ outstr, "Found incorrect contour:\n"),
-		write_decl_final_atom(User, "", print, Atom)
+		write_decl_final_atom(User, "", decl_caller_type, Atom)
 	;
 		{ EBug = partially_uncovered_atom(Atom, _) },
 		io__write_string(User ^ outstr,
 				"Found partially uncovered atom:\n"),
-		write_decl_init_atom(User, "", print, Atom)
+		write_decl_init_atom(User, "", decl_caller_type, Atom)
 	;
 		{ EBug = unhandled_exception(Atom, Exception, _) },
 		io__write_string(User ^ outstr, "Found unhandled exception:\n"),
-		write_decl_init_atom(User, "", print, Atom),
+		write_decl_init_atom(User, "", decl_caller_type, Atom),
 		io__write(User ^ outstr, include_details_cc,
 				univ_value(Exception)),
 		io__nl(User ^ outstr)
@@ -641,8 +648,8 @@
 write_decl_bug(i_bug(IBug), User) -->
 	{ IBug = inadmissible_call(Parent, _, Call, _) },
 	io__write_string(User ^ outstr, "Found inadmissible call:\n"),
-	write_decl_atom(User, "Parent ", print, init(Parent)),
-	write_decl_atom(User, "Call ", print, init(Call)).
+	write_decl_atom(User, "Parent ", decl_caller_type, init(Parent)),
+	write_decl_atom(User, "Call ", decl_caller_type, init(Call)).
 
 :- pred write_decl_init_atom(user_state::in, string::in, browse_caller_type::in,
 	init_decl_atom::in, io__state::di, io__state::uo) is cc_multi.
Index: browser/parse.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/browser/parse.m,v
retrieving revision 1.16
diff -u -b -r1.16 parse.m
--- browser/parse.m	26 May 2003 08:59:44 -0000	1.16
+++ browser/parse.m	5 Aug 2003 04:17:37 -0000
@@ -20,19 +20,57 @@
 %
 %	commandline:
 %		"?"			// SICStus help
-%		"^" [numlist]		// SICStus cd
+%		"^" [path]			// SICStus cd
 %		"d"			// SICStus display
 %		"w"			// SICStus write
+%		"<"				// SICStus set depth
 %		"help"
+%		"h"				// short for help
 %		"cd" [path]
 %		"pwd"
-%		"ls"
+%		"ls" [formatoptions] [path]
+%		"print" [formatoptions] [path]
+%		"p" [formatoptions] [path]	// short for print
 %		"display"
 %		"write"
-%		"set" [varvalue]
+%		"set" [[setoptions] varvalue]
 %		"mark" [path]
 %		"quit"
 %
+%	formatoptions:
+%		/* empty */
+%		formatoption formatoptions
+%
+%	formatoption:
+%		-f
+%		-r
+%		-v
+%		-p
+%		--flat
+%		--raw-pretty
+%		--verbose
+%		--pretty
+%
+%	setoptions:
+%		/* empty */
+%		setoption setoptions
+%
+%	setoption:
+%		-P
+%		-B
+%		-A
+%		-f
+%		-r
+%		-v
+%		-p
+%		--print
+%		--browse
+%		--print-all
+%		--flat
+%		--raw-pretty
+%		--verbose
+%		--pretty
+%
 %	varvalue:
 %		"depth" num
 %		"size" num
@@ -66,22 +104,23 @@
 
 :- interface.
 
-:- import_module io, string, list.
 :- import_module mdb__browser_info.
+:- import_module io, string, list, std_util, getopt.
 
 :- type command
-	--->	ls(path)
-	;	ls
+	--->	print(
+			maybe(maybe_option_table(format_option)),
+			maybe(path)
+		)
 	;	cd(path)
 	;	cd
 	;	mark(path)
 	;	mark
 	;	pwd
 	;	help
-	;	set(setting)
+	;	set(maybe_option_table(setting_option), setting)
 	;	set
 	;	quit
-	;	print
 	;	display
 	;	write
 	;	empty
@@ -91,6 +130,21 @@
 	--->	root_rel(list(dir))
 	;	dot_rel(list(dir)).
 
+:- type format_option
+	--->	flat
+	;	raw_pretty
+	;	verbose
+	;	pretty.
+
+:- type setting_option
+	--->	print
+	;	browse
+	;	print_all
+	;	flat
+	;	raw_pretty
+	;	verbose
+	;	pretty.
+
 % If the term browser is called from the external debugger, the term browser
 % commands are send through the socket via terms of type external_request.
 :- type external_request 
@@ -103,11 +157,11 @@
 :- mode parse__read_command_external(out, di, uo) is det.
 
 %---------------------------------------------------------------------------%
+
 :- implementation.
 
-:- import_module list, char, int, std_util.
 :- import_module mdb__util.
-
+:- import_module bool, list, char, int.
 
 :- type token
 	--->	(.)
@@ -123,9 +177,8 @@
 
 parse__read_command(Prompt, Command) -->
 	util__trace_get_command(Prompt, Line),
-	{ string__to_char_list(Line, Cs) },
-	{ lexer(Cs, Tokens) },
-	( { parse(Tokens, Command2) } ->
+	{ string__words(char__is_whitespace, Line) = Words },
+	( { parse(Words, Command2) } ->
 		{ Command = Command2 }
 	;
 		{ Command = unknown }
@@ -134,9 +187,8 @@
 parse__read_command_external(Command) -->
 	io__read(Result),
 	( { Result = ok(external_request(StringToParse)) } ->
-		{ string__to_char_list(StringToParse, Cs) },
-		{ lexer(Cs, Tokens) },
-		( { parse(Tokens, Command2) } ->
+		{ string__words(char__is_whitespace, StringToParse) = Words },
+		( { parse(Words, Command2) } ->
 			{ Command = Command2 }
 		;
 			{ Command = unknown }
@@ -147,52 +199,71 @@
 		{ Command = unknown }
 	).
 
-:- pred lexer(list(char), list(token)).
-:- mode lexer(in, out) is det.
-lexer([], []).
-lexer([C | Cs], Toks) :-
+:- pred lexer_words(list(string), list(token)).
+:- mode lexer_words(in, out) is det.
+
+lexer_words([], []).
+lexer_words([Word | Words], Tokens) :-
+	lexer_word(Word, WordTokens),
+	lexer_words(Words, WordsTokens),
+	list__append(WordTokens, WordsTokens, Tokens).
+
+:- pred lexer_word(string, list(token)).
+:- mode lexer_word(in, out) is det.
+
+lexer_word(Word, Tokens) :-
+	string__to_char_list(Word, Chars),
+	lexer_word_chars(Chars, Tokens).
+
+:- pred lexer_word_chars(list(char), list(token)).
+:- mode lexer_word_chars(in, out) is det.
+
+lexer_word_chars([], []).
+lexer_word_chars([C | Cs], Toks) :-
 	( C = ('.') ->
 		lexer_dots(Cs, Toks)
 	; C = ('/') ->
 		Toks = [(/) | Toks2],
-		lexer(Cs, Toks2)
+		lexer_word_chars(Cs, Toks2)
 	; C = ('?') ->
 		Toks = [(?) | Toks2],
-		lexer(Cs, Toks2)
+		lexer_word_chars(Cs, Toks2)
 	; C = ('^') ->
 		Toks = [(^) | Toks2],
-		lexer(Cs, Toks2)
+		lexer_word_chars(Cs, Toks2)
 	; C = ('<') ->
 		Toks = [(<) | Toks2],
-		lexer(Cs, Toks2)
+		lexer_word_chars(Cs, Toks2)
 	; char__is_digit(C) ->
 		dig_to_int(C, N),
 		lexer_num(N, Cs, Toks)
 	; char__is_alpha_or_underscore(C) ->
 		lexer_name(C, Cs, Toks)
 	; char__is_whitespace(C) ->
-		lexer(Cs, Toks)
+		lexer_word_chars(Cs, Toks)
 	;
 		Toks = [unknown(C) | Toks2],
-		lexer(Cs, Toks2)
+		lexer_word_chars(Cs, Toks2)
 	).
 
 :- pred lexer_dots(list(char), list(token)).
 :- mode lexer_dots(in, out) is det.
+
 lexer_dots([], []).
 lexer_dots([C | Cs], Toks) :-
 	( C = ('.') ->
 		Tok = (..),
-		lexer(Cs, Toks2),
+		lexer_word_chars(Cs, Toks2),
 		Toks = [Tok | Toks2]
 	;
 		Tok = (.),
-		lexer([C | Cs], Toks2),
+		lexer_word_chars([C | Cs], Toks2),
 		Toks = [Tok | Toks2]
 	).
 
 :- pred dig_to_int(char, int).
 :- mode dig_to_int(in, out) is det.
+
 dig_to_int(C, N) :-
 	char__to_int('0', Zero),
 	char__to_int(C, CN),
@@ -200,155 +271,240 @@
 
 :- pred lexer_num(int, list(char), list(token)).
 :- mode lexer_num(in, in, out) is det.
+
 lexer_num(N, Cs, Toks) :-
 	list__takewhile(char__is_digit, Cs, Digits, Rest),
 	digits_to_int_acc(N, Digits, Num),
 	Toks = [num(Num) | Toks2],
-	lexer(Rest, Toks2).
-	
+	lexer_word_chars(Rest, Toks2).
 			
 :- pred digits_to_int_acc(int, list(char), int).
 :- mode digits_to_int_acc(in, in, out) is det.
+
 digits_to_int_acc(Acc, [], Acc).
 digits_to_int_acc(Acc, [C | Cs], Num) :-
 	dig_to_int(C, D),
 	Acc2 = 10 * Acc + D,
 	digits_to_int_acc(Acc2, Cs, Num).
 	
-
 :- pred lexer_name(char, list(char), list(token)).
 :- mode lexer_name(in, in, out) is det.
+
 lexer_name(C, Cs, Toks) :-
 	list__takewhile(char__is_alnum_or_underscore, Cs, Letters, Rest),
 	string__from_char_list([C | Letters], Name),
-	lexer(Rest, Toks2),
+	lexer_word_chars(Rest, Toks2),
 	Toks = [name(Name) | Toks2].
 	
+%---------------------------------------------------------------------------%
 
-:- pred parse(list(token), command).
+:- pred parse(list(string), command).
 :- mode parse(in, out) is semidet.
-parse(Toks, Command) :-
-	( Toks = [] ->
+
+parse(Words, Command) :-
+	(
+		Words = [],
+		Command = empty
+	;
+		Words = [CmdWord | ArgWords],
+		lexer_word(CmdWord, CmdTokens),
+		lexer_words(ArgWords, ArgTokens),
+		( CmdTokens = [_] ->
+			% If the initial word is one token, then it can make
+			% sense to parse the command line as words.
+			MaybeArgWords = yes(ArgWords)
+		;
+			% If the initial word is more than one token, then
+			% it doesn't make sense to parse the command line
+			% as words.
+			MaybeArgWords = no
+		),
+		list__append(CmdTokens, ArgTokens, AllTokens),
+		(
+			AllTokens = [],
 		Command = empty
 	;
-		start(Toks, Command)
+			AllTokens = [FirstToken | LaterTokens],
+			parse_cmd(FirstToken, LaterTokens, MaybeArgWords,
+				Command)
+		)
 	).
 
-:- pred start(list(token), command).
-:- mode start(in, out) is semidet.
-start([Tok | Toks], Command) :-
-	( (Tok = name("help") ; Tok = (?) ; Tok = name("h")) ->
-		Toks = [],
+:- pred parse_cmd(token::in, list(token)::in, maybe(list(string))::in,
+	command::out) is semidet.
+
+parse_cmd(CmdToken, ArgTokens, MaybeArgWords, Command) :-
+	(
+		( CmdToken = name("help")
+		; CmdToken = (?)
+		; CmdToken = name("h")
+		)
+	->
+		ArgTokens = [],
 		Command = help
-	; (Tok = name("cd") ; Tok = (^)) ->
-		( Toks = [] ->
+	;
+		( CmdToken = name("cd")
+		; CmdToken = (^)
+		)
+	->
+		( ArgTokens = [] ->
 			Command = cd
 		;
-			parse_path(Toks, Path),
+			parse_path(ArgTokens, Path),
 			Command = cd(Path)
 		)
-	; Tok = name("pwd") ->
-		Toks = [],
+	;
+		CmdToken = name("pwd")
+	->
+		ArgTokens = [],
 		Command = pwd
-	; Tok = name("ls") ->
-		( Toks = [] ->
-			Command = ls
 		;
-			parse_path(Toks, Path),
-			Command = ls(Path)
-		)
-	; Tok = name("mark") ->
-		( Toks = [] ->
+		CmdToken = name("mark")
+	->
+		( ArgTokens = [] ->
 			Command = mark
 		;
-			parse_path(Toks, Path),
+			parse_path(ArgTokens, Path),
 			Command = mark(Path)
 		)
-	; Tok = name("set") ->
-		( Toks = [] ->
+	;
+		CmdToken = name("set")
+	->
+		( ArgTokens = [] ->
 			Command = set
 		;
-			parse_setting(Toks, Setting),
-			Command = set(Setting)
+			MaybeArgWords = yes(ArgWords),
+			OptionOps = option_ops(short_setting_option,
+				long_setting_option,
+				setting_option_defaults_nondet),
+			getopt__process_options(OptionOps, ArgWords,
+				RemainingWords, MaybeOptionTable),
+			lexer_words(RemainingWords, RemainingTokens),
+			parse_setting(RemainingTokens, Setting),
+			Command = set(MaybeOptionTable, Setting)
 		)
-	; Tok = name("quit") ->
-		Toks = [],
+	;
+		CmdToken = name("quit")
+	->
+		ArgTokens = [],
 		Command = quit
-	; (Tok = name("display") ; Tok = name("d")) ->
-		Toks = [],
+	;
+		( CmdToken = name("display")
+		; CmdToken = name("d")
+		)
+	->
+		ArgTokens = [],
 		Command = display
-	; (Tok = name("write") ; Tok = name("w")) ->
-		Toks = [],
+	;
+		( CmdToken = name("write")
+		; CmdToken = name("w")
+		)
+	->
+		ArgTokens = [],
 		Command = write
-	; (Tok = name("print") ; Tok = name("p")) ->
-		Toks = [],
-		Command = print
-	;
-		Tok = (<),
-		Toks = [num(Depth)],
-		Command = set(depth(Depth))
+	;
+		( CmdToken = name("print")
+		; CmdToken = name("p")
+		; CmdToken = name("ls")
+		)
+	->
+		(
+			MaybeArgWords = no,
+			MaybeMaybeOptionTable = no,
+			RemainingTokens = ArgTokens
+		;
+			MaybeArgWords = yes(ArgWords),
+			OptionOps = option_ops(short_format_option,
+				long_format_option,
+				format_option_defaults_nondet),
+			getopt__process_options(OptionOps, ArgWords,
+				RemainingWords, MaybeOptionTable),
+			MaybeMaybeOptionTable = yes(MaybeOptionTable),
+			lexer_words(RemainingWords, RemainingTokens)
+		),
+		( RemainingTokens = [] ->
+			MaybePath = no
+		;
+			parse_path(RemainingTokens, Path),
+			MaybePath = yes(Path)
+		),
+		Command = print(MaybeMaybeOptionTable, MaybePath)
+	;
+		CmdToken = (<)
+	->
+		ArgTokens = [num(Depth)],
+		% compute the default MaybeOptionTable
+		OptionOps = option_ops(short_setting_option,
+			long_setting_option, setting_option_defaults_nondet),
+		getopt__process_options(OptionOps, [], _, MaybeOptionTable),
+		Command = set(MaybeOptionTable, depth(Depth))
+	;
+		fail
 	).
 
 :- pred parse_path(list(token), path).
 :- mode parse_path(in, out) is semidet.
+
 	% SICStus is forgiving in the syntax of paths, hence so are we.
 	% XXX: Be less forgiving?
-parse_path([Tok | Toks], Path) :-
-	( Tok = (/) ->
+parse_path([Token | Tokens], Path) :-
+	( Token = (/) ->
 		Path = root_rel(Dirs),
-		parse_dirs(Toks, Dirs)
+		parse_dirs(Tokens, Dirs)
 	;
 		Path = dot_rel(Dirs),
-		parse_dirs([Tok | Toks], Dirs)
+		parse_dirs([Token | Tokens], Dirs)
 	).
 
 :- pred parse_dirs(list(token), list(dir)).
 :- mode parse_dirs(in, out) is semidet.
+
 parse_dirs([], []).
-parse_dirs([Tok | Toks], Dirs) :-
+parse_dirs([Token | Tokens], Dirs) :-
 	(
-		Tok = num(Subdir),
+		Token = num(Subdir),
 		Dirs = [child_num(Subdir) | RestDirs],
-		parse_dirs(Toks, RestDirs)
+		parse_dirs(Tokens, RestDirs)
 	;
-		Tok = name(NamedSubdir),
+		Token = name(NamedSubdir),
 		Dirs = [child_name(NamedSubdir) | RestDirs],
-		parse_dirs(Toks, RestDirs)
+		parse_dirs(Tokens, RestDirs)
 	;
-		Tok = (..),
+		Token = (..),
 		Dirs = [parent | RestDirs],
-		parse_dirs(Toks, RestDirs)
+		parse_dirs(Tokens, RestDirs)
 	;
 		% We can effectively ignore slashes (for Unix-style
 		% pathnames) and carets (for SICStus-style pathnames),
 		% but anything else is not allowed.
-		Tok = (/),
-		parse_dirs(Toks, Dirs)
+		Token = (/),
+		parse_dirs(Tokens, Dirs)
 	;
-		Tok = (^),
-		parse_dirs(Toks, Dirs)
+		Token = (^),
+		parse_dirs(Tokens, Dirs)
 	).
 
 :- pred parse_setting(list(token), setting).
 :- mode parse_setting(in, out) is semidet.
-parse_setting([Tok | Toks], Setting) :-
-	( Tok = name("depth") ->
-		Toks = [num(Depth)],
+
+parse_setting([Token | Tokens], Setting) :-
+	( Token = name("depth") ->
+		Tokens = [num(Depth)],
 		Setting = depth(Depth)
-	; Tok = name("size") ->
-		Toks = [num(Size)],
+	; Token = name("size") ->
+		Tokens = [num(Size)],
 		Setting = size(Size)
-	; Tok = name("width") ->
-		Toks = [num(X)],
+	; Token = name("width") ->
+		Tokens = [num(X)],
 		Setting = width(X)
-	; Tok = name("lines") ->
-		Toks = [num(Y)],
+	; Token = name("lines") ->
+		Tokens = [num(Y)],
 		Setting = lines(Y)
-	; Tok = name("num_io_actions") ->
-		Toks = [num(Y)],
+	; Token = name("num_io_actions") ->
+		Tokens = [num(Y)],
 		Setting = num_io_actions(Y)
-	; Tok = name("format") ->
-		Toks = [Fmt],
+	; Token = name("format") ->
+		Tokens = [Fmt],
 		( Fmt = name("flat") ->
 			Setting = format(flat)
 		; Fmt = name("raw_pretty") ->
@@ -363,117 +519,194 @@
 		fail
 	).
 	
+%---------------------------------------------------------------------------%
+
+:- pred short_format_option(char::in, format_option::out) is semidet.
+
+short_format_option('f', flat).
+short_format_option('r', raw_pretty).
+short_format_option('v', verbose).
+short_format_option('p', pretty).
+
+:- pred long_format_option(string::in, format_option::out) is semidet.
+
+long_format_option("flat", flat).
+long_format_option("raw-pretty", raw_pretty).
+long_format_option("verbose", verbose).
+long_format_option("pretty", pretty).
+
+:- pred format_option_defaults_nondet(format_option::out, option_data::out)
+	is nondet.
+
+format_option_defaults_nondet(Option, Value) :-
+	( semidet_succeed ->
+		format_option_defaults(Option, Value)
+	;
+		fail
+	).
+
+:- pred format_option_defaults(format_option::out, option_data::out) is multi.
+
+format_option_defaults(flat,		bool(no)).
+format_option_defaults(raw_pretty,	bool(no)).
+format_option_defaults(verbose,		bool(no)).
+format_option_defaults(pretty,		bool(no)).
+
+%---------------------------------------------------------------------------%
+
+:- pred short_setting_option(char::in, setting_option::out) is semidet.
+
+short_setting_option('P', print).
+short_setting_option('B', browse).
+short_setting_option('A', print_all).
+short_setting_option('f', flat).
+short_setting_option('r', raw_pretty).
+short_setting_option('v', verbose).
+short_setting_option('p', pretty).
+
+:- pred long_setting_option(string::in, setting_option::out) is semidet.
+
+long_setting_option("print", print).
+long_setting_option("browse", browse).
+long_setting_option("print-all", print_all).
+long_setting_option("flat", flat).
+long_setting_option("raw-pretty", raw_pretty).
+long_setting_option("verbose", verbose).
+long_setting_option("pretty", pretty).
+
+:- pred setting_option_defaults_nondet(setting_option::out, option_data::out)
+	is nondet.
+
+setting_option_defaults_nondet(Option, Value) :-
+	( semidet_succeed ->
+		setting_option_defaults(Option, Value)
+	;
+		fail
+	).
+
+:- pred setting_option_defaults(setting_option::out, option_data::out)
+	is multi.
+
+setting_option_defaults(print,		bool(no)).
+setting_option_defaults(browse,		bool(no)).
+setting_option_defaults(print_all,	bool(no)).
+setting_option_defaults(flat,		bool(no)).
+setting_option_defaults(raw_pretty,	bool(no)).
+setting_option_defaults(verbose,	bool(no)).
+setting_option_defaults(pretty,		bool(no)).
 
 %---------------------------------------------------------------------------%
 
-:- pred show_command(command, io__state, io__state).
-:- mode show_command(in, di, uo) is det.
+% The commented out code is not currently used.
 
-show_command(ls(Path)) -->
-	io__write_string("ls "),
-	show_path(Path),
-	io__nl.
-show_command(ls) -->
-	io__write_string("ls\n").
-show_command(cd(Path)) -->
-	io__write_string("cd "),
-	show_path(Path),
-	io__nl.
-show_command(cd) -->
-	io__write_string("cd\n").
-show_command(mark(Path)) -->
-	io__write_string("mark "),
-	show_path(Path),
-	io__nl.
-show_command(mark) -->
-	io__write_string("mark\n").
-show_command(pwd) -->
-	io__write_string("pwd\n").
-show_command(help) -->
-	io__write_string("help\n").
-show_command(set(Setting)) -->
-	io__write_string("set "),
-	show_setting(Setting),
-	io__nl.
-show_command(set) -->
-	io__write_string("set\n").
-show_command(quit) -->
-	io__write_string("quit\n").
-show_command(print) -->
-	io__write_string("print\n").
-show_command(display) -->
-	io__write_string("display\n").
-show_command(write) -->
-	io__write_string("write\n").
-show_command(empty) -->
-	io__write_string("empty\n").
-show_command(unknown) -->
-	io__write_string("unknown\n").
-
-:- pred show_path(path, io__state, io__state).
-:- mode show_path(in, di, uo) is det.
-
-show_path(root_rel(Dirs)) -->
-	io__write_string("/"),
-	show_dirs(Dirs).
-show_path(dot_rel(Dirs)) -->
-	show_dirs(Dirs).
-
-:- pred show_dirs(list(dir), io__state, io__state).
-:- mode show_dirs(in, di, uo) is det.
-
-show_dirs([]) -->
-	io__nl.
-show_dirs([child_num(Num) | Dirs]) -->
-	io__write_int(Num),
-	io__write_string("/"),
-	show_dirs(Dirs).
-show_dirs([child_name(Name) | Dirs]) -->
-	io__write_string(Name),
-	io__write_string("/"),
-	show_dirs(Dirs).
-show_dirs([parent | Dirs]) -->
-	io__write_string("../"),
-	show_dirs(Dirs).
-
-:- pred show_setting(setting, io__state, io__state).
-:- mode show_setting(in, di, uo) is det.
-
-show_setting(depth(Depth)) -->
-	io__write_string("depth "),
-	io__write_int(Depth),
-	io__nl.
-show_setting(size(Size)) -->
-	io__write_string("size "),
-	io__write_int(Size),
-	io__nl.
-show_setting(width(X)) -->
-	io__write_string("width "),
-	io__write_int(X),
-	io__nl.
-show_setting(lines(Y)) -->
-	io__write_string("lines "),
-	io__write_int(Y),
-	io__nl.
-show_setting(format(Fmt)) -->
-	io__write_string("format "),
-	show_format(Fmt),
-	io__nl.
-show_setting(num_io_actions(N)) -->
-	io__write_string("num_io_actions "),
-	io__write_int(N),
-	io__nl.
-
-:- pred show_format(portray_format, io__state, io__state).
-:- mode show_format(in, di, uo) is det.
-
-show_format(flat) -->
-	io__write_string("flat").
-show_format(raw_pretty) -->
-	io__write_string("raw_pretty").
-show_format(verbose) -->
-	io__write_string("verbose").
-show_format(pretty) -->
-	io__write_string("pretty").
+% :- pred show_command(command, io__state, io__state).
+% :- mode show_command(in, di, uo) is det.
+% 
+% show_command(ls(Path)) -->
+% 	io__write_string("ls "),
+% 	show_path(Path),
+% 	io__nl.
+% show_command(ls) -->
+% 	io__write_string("ls\n").
+% show_command(cd(Path)) -->
+% 	io__write_string("cd "),
+% 	show_path(Path),
+% 	io__nl.
+% show_command(cd) -->
+% 	io__write_string("cd\n").
+% show_command(mark(Path)) -->
+% 	io__write_string("mark "),
+% 	show_path(Path),
+% 	io__nl.
+% show_command(mark) -->
+% 	io__write_string("mark\n").
+% show_command(pwd) -->
+% 	io__write_string("pwd\n").
+% show_command(help) -->
+% 	io__write_string("help\n").
+% show_command(set(Setting)) -->
+% 	io__write_string("set "),
+% 	show_setting(Setting),
+% 	io__nl.
+% show_command(set) -->
+% 	io__write_string("set\n").
+% show_command(quit) -->
+% 	io__write_string("quit\n").
+% show_command(print) -->
+% 	io__write_string("print\n").
+% show_command(display) -->
+% 	io__write_string("display\n").
+% show_command(write) -->
+% 	io__write_string("write\n").
+% show_command(empty) -->
+% 	io__write_string("empty\n").
+% show_command(unknown) -->
+% 	io__write_string("unknown\n").
+% 
+% :- pred show_path(path, io__state, io__state).
+% :- mode show_path(in, di, uo) is det.
+% 
+% show_path(root_rel(Dirs)) -->
+% 	io__write_string("/"),
+% 	show_dirs(Dirs).
+% show_path(dot_rel(Dirs)) -->
+% 	show_dirs(Dirs).
+% 
+% :- pred show_dirs(list(dir), io__state, io__state).
+% :- mode show_dirs(in, di, uo) is det.
+% 
+% show_dirs([]) -->
+% 	io__nl.
+% show_dirs([child_num(Num) | Dirs]) -->
+% 	io__write_int(Num),
+% 	io__write_string("/"),
+% 	show_dirs(Dirs).
+% show_dirs([child_name(Name) | Dirs]) -->
+% 	io__write_string(Name),
+% 	io__write_string("/"),
+% 	show_dirs(Dirs).
+% show_dirs([parent | Dirs]) -->
+% 	io__write_string("../"),
+% 	show_dirs(Dirs).
+% 
+% :- pred show_setting(setting, io__state, io__state).
+% :- mode show_setting(in, di, uo) is det.
+% 
+% show_setting(depth(Depth)) -->
+% 	io__write_string("depth "),
+% 	io__write_int(Depth),
+% 	io__nl.
+% show_setting(size(Size)) -->
+% 	io__write_string("size "),
+% 	io__write_int(Size),
+% 	io__nl.
+% show_setting(width(X)) -->
+% 	io__write_string("width "),
+% 	io__write_int(X),
+% 	io__nl.
+% show_setting(lines(Y)) -->
+% 	io__write_string("lines "),
+% 	io__write_int(Y),
+% 	io__nl.
+% show_setting(format(Fmt)) -->
+% 	io__write_string("format "),
+% 	show_format(Fmt),
+% 	io__nl.
+% show_setting(num_io_actions(N)) -->
+% 	io__write_string("num_io_actions "),
+% 	io__write_int(N),
+% 	io__nl.
+% 
+% :- pred show_format(portray_format, io__state, io__state).
+% :- mode show_format(in, di, uo) is det.
+% 
+% show_format(flat) -->
+% 	io__write_string("flat").
+% show_format(raw_pretty) -->
+% 	io__write_string("raw_pretty").
+% show_format(verbose) -->
+% 	io__write_string("verbose").
+% show_format(pretty) -->
+% 	io__write_string("pretty").
 
 %---------------------------------------------------------------------------%
cvs diff: Diffing bytecode
cvs diff: Diffing compiler
cvs diff: [06:44:38] waiting for uid20308's lock in /home/mercury/mercury1/repository/mercury/compiler
cvs diff: [06:45:08] waiting for uid20308's lock in /home/mercury/mercury1/repository/mercury/compiler
cvs diff: [06:45:38] obtained lock in /home/mercury/mercury1/repository/mercury/compiler
cvs diff: Diffing compiler/notes
cvs diff: Diffing debian
cvs diff: Diffing deep_profiler
cvs diff: Diffing deep_profiler/notes
cvs diff: Diffing doc
cvs diff: Diffing extras
cvs diff: Diffing extras/aditi
cvs diff: Diffing extras/cgi
cvs diff: Diffing extras/complex_numbers
cvs diff: Diffing extras/complex_numbers/samples
cvs diff: Diffing extras/complex_numbers/tests
cvs diff: Diffing extras/concurrency
cvs diff: Diffing extras/curs
cvs diff: Diffing extras/curs/samples
cvs diff: Diffing extras/curses
cvs diff: Diffing extras/curses/sample
cvs diff: Diffing extras/dynamic_linking
cvs diff: Diffing extras/error
cvs diff: Diffing extras/graphics
cvs diff: Diffing extras/graphics/mercury_opengl
cvs diff: Diffing extras/graphics/mercury_tcltk
cvs diff: Diffing extras/graphics/samples
cvs diff: Diffing extras/graphics/samples/calc
cvs diff: Diffing extras/graphics/samples/maze
cvs diff: Diffing extras/graphics/samples/pent
cvs diff: Diffing extras/lazy_evaluation
cvs diff: Diffing extras/lex
cvs diff: Diffing extras/lex/samples
cvs diff: Diffing extras/lex/tests
cvs diff: Diffing extras/logged_output
cvs diff: Diffing extras/moose
cvs diff: Diffing extras/moose/samples
cvs diff: Diffing extras/morphine
cvs diff: Diffing extras/morphine/non-regression-tests
cvs diff: Diffing extras/morphine/scripts
cvs diff: Diffing extras/morphine/source
cvs diff: Diffing extras/odbc
cvs diff: Diffing extras/posix
cvs diff: Diffing extras/quickcheck
cvs diff: Diffing extras/quickcheck/tutes
cvs diff: Diffing extras/references
cvs diff: Diffing extras/references/samples
cvs diff: Diffing extras/references/tests
cvs diff: Diffing extras/stream
cvs diff: Diffing extras/trailed_update
cvs diff: Diffing extras/trailed_update/samples
cvs diff: Diffing extras/trailed_update/tests
cvs diff: Diffing extras/xml
cvs diff: Diffing extras/xml/samples
cvs diff: Diffing java
cvs diff: Diffing java/library
cvs diff: Diffing java/runtime
cvs diff: Diffing library
cvs diff: Diffing profiler
cvs diff: Diffing robdd
cvs diff: Diffing runtime
cvs diff: Diffing runtime/GETOPT
cvs diff: Diffing runtime/machdeps
cvs diff: Diffing samples
cvs diff: Diffing samples/c_interface
cvs diff: Diffing samples/c_interface/c_calls_mercury
cvs diff: Diffing samples/c_interface/cplusplus_calls_mercury
cvs diff: Diffing samples/c_interface/mercury_calls_c
cvs diff: Diffing samples/c_interface/mercury_calls_cplusplus
cvs diff: Diffing samples/c_interface/mercury_calls_fortran
cvs diff: Diffing samples/c_interface/simpler_c_calls_mercury
cvs diff: Diffing samples/c_interface/simpler_cplusplus_calls_mercury
cvs diff: Diffing samples/diff
cvs diff: Diffing samples/muz
cvs diff: Diffing samples/rot13
cvs diff: Diffing samples/solutions
cvs diff: Diffing samples/tests
cvs diff: Diffing samples/tests/c_interface
cvs diff: Diffing samples/tests/c_interface/c_calls_mercury
cvs diff: Diffing samples/tests/c_interface/cplusplus_calls_mercury
cvs diff: Diffing samples/tests/c_interface/mercury_calls_c
cvs diff: Diffing samples/tests/c_interface/mercury_calls_cplusplus
cvs diff: Diffing samples/tests/c_interface/mercury_calls_fortran
cvs diff: Diffing samples/tests/c_interface/simpler_c_calls_mercury
cvs diff: Diffing samples/tests/c_interface/simpler_cplusplus_calls_mercury
cvs diff: Diffing samples/tests/diff
cvs diff: Diffing samples/tests/muz
cvs diff: Diffing samples/tests/rot13
cvs diff: Diffing samples/tests/solutions
cvs diff: Diffing samples/tests/toplevel
cvs diff: Diffing scripts
cvs diff: Diffing tests
cvs diff: Diffing tests/benchmarks
cvs diff: Diffing tests/debugger
Index: tests/debugger/browser_test.exp
===================================================================
RCS file: /home/mercury/mercury1/repository/tests/debugger/browser_test.exp,v
retrieving revision 1.15
diff -u -b -r1.15 browser_test.exp
--- tests/debugger/browser_test.exp	30 Jan 2003 05:59:26 -0000	1.15
+++ tests/debugger/browser_test.exp	1 Oct 2003 17:05:32 -0000
@@ -56,7 +56,10 @@
 print: unrecognized option `--xyzzy'
 mdb: print: usage error -- type `help print' for help.
 mdb> browse 1; print; quit
-big(big(big(small, 1, small), 2, small), 3, big(big(small, 4, big/3), 6, small))
+big(
+  big(big(small, 1, small), 2, small), 
+  3, 
+  big(big(small, 4, big(small, 5, small)), 6, small))
 mdb> browse -f 1; ls; quit
 big(big(big(small, 1, small), 2, small), 3, big(big(small, 4, big(small, 5, small)), 6, small))
 mdb> browse Data
Index: tests/debugger/exception_value.exp
===================================================================
RCS file: /home/mercury/mercury1/repository/tests/debugger/exception_value.exp,v
retrieving revision 1.7
diff -u -b -r1.7 exception_value.exp
--- tests/debugger/exception_value.exp	17 Jan 2003 05:56:52 -0000	1.7
+++ tests/debugger/exception_value.exp	1 Oct 2003 17:04:29 -0000
@@ -24,16 +24,7 @@
 browser> set depth 9
 browser> set size 99
 browser> ls
--
-1-"q oops"
-2-[|]
-  1-1
-  2-[|]
-    1-2
-    2-[|]
-      1-3
-      2-[]
-
+"q oops" - [1, 2, 3]
 browser> quit
 mdb> continue
 mdb: warning: reached unknown label
Index: tests/debugger/polymorphic_output.exp
===================================================================
RCS file: /home/mercury/mercury1/repository/tests/debugger/polymorphic_output.exp,v
retrieving revision 1.10
diff -u -b -r1.10 polymorphic_output.exp
--- tests/debugger/polymorphic_output.exp	17 Jan 2003 05:56:55 -0000	1.10
+++ tests/debugger/polymorphic_output.exp	1 Oct 2003 17:04:59 -0000
@@ -38,15 +38,15 @@
 mdb> browse goal
 browser> ^1
 browser> p
-two("three", 3, three("four", 4, "one", 1, empty, empty, empty), two/4)
+two("three", 3, three("four", 4, "one", 1, empty, empty, empty), two("two", 2, empty, empty))
 browser> ^..^2
 error: cannot change to subterm
 browser> p
-two("three", 3, three("four", 4, "one", 1, empty, empty, empty), two/4)
+two("three", 3, three("four", 4, "one", 1, empty, empty, empty), two("two", 2, empty, empty))
 browser> ^..^3
 error: cannot change to subterm
 browser> p
-two("three", 3, three("four", 4, "one", 1, empty, empty, empty), two/4)
+two("three", 3, three("four", 4, "one", 1, empty, empty, empty), two("two", 2, empty, empty))
 browser> ^..^r
 browser> p
 '_'
cvs diff: Diffing tests/debugger/declarative
Index: tests/debugger/declarative/browse_arg.exp
===================================================================
RCS file: /home/mercury/mercury1/repository/tests/debugger/declarative/browse_arg.exp,v
retrieving revision 1.2
diff -u -b -r1.2 browse_arg.exp
--- tests/debugger/declarative/browse_arg.exp	17 Jan 2003 05:57:00 -0000	1.2
+++ tests/debugger/declarative/browse_arg.exp	1 Oct 2003 17:06:06 -0000
@@ -12,10 +12,7 @@
 p(1, baz(1, bar))
 Valid? browse 2
 browser> ls
-baz
-1-1
-2-bar
-
+baz(1, bar)
 browser> quit
 p(1, baz(1, bar))
 Valid? no
cvs diff: Diffing tests/dppd
cvs diff: Diffing tests/general
cvs diff: Diffing tests/general/accumulator
cvs diff: Diffing tests/general/string_format
cvs diff: Diffing tests/general/structure_reuse
cvs diff: Diffing tests/grade_subdirs
cvs diff: Diffing tests/hard_coded
cvs diff: Diffing tests/hard_coded/exceptions
cvs diff: Diffing tests/hard_coded/purity
cvs diff: Diffing tests/hard_coded/sub-modules
cvs diff: Diffing tests/hard_coded/typeclasses
cvs diff: Diffing tests/invalid
cvs diff: Diffing tests/invalid/purity
cvs diff: Diffing tests/misc_tests
cvs diff: Diffing tests/mmc_make
cvs diff: Diffing tests/mmc_make/lib
cvs diff: Diffing tests/recompilation
cvs diff: Diffing tests/tabling
cvs diff: Diffing tests/term
cvs diff: Diffing tests/valid
cvs diff: Diffing tests/warnings
cvs diff: Diffing tools
cvs diff: Diffing trace
Index: trace/mercury_trace_browse.c
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/trace/mercury_trace_browse.c,v
retrieving revision 1.27
diff -u -b -r1.27 mercury_trace_browse.c
--- trace/mercury_trace_browse.c	15 Nov 2002 04:50:47 -0000	1.27
+++ trace/mercury_trace_browse.c	5 Aug 2003 04:07:06 -0000
@@ -209,43 +209,52 @@
 			MR_trace_is_portray_format(value, &new_format))
 	{
 		MR_TRACE_CALL_MERCURY(
-			ML_BROWSE_set_param_format(print, browse, print_all,
-				new_format, MR_trace_browser_persistent_state,
+			ML_BROWSE_set_param_format_from_mdb(print, browse,
+				print_all, new_format,
+				MR_trace_browser_persistent_state,
 				&MR_trace_browser_persistent_state);
 		);
 	}
-	else if (MR_streq(param, "depth") && MR_trace_is_natural_number(value, &depth))
+	else if (MR_streq(param, "depth") &&
+		MR_trace_is_natural_number(value, &depth))
 	{
 		MR_TRACE_CALL_MERCURY(
-			ML_BROWSE_set_param_depth(print, browse, print_all,
-				flat, raw_pretty, verbose, pretty, depth,
+			ML_BROWSE_set_param_depth_from_mdb(print, browse,
+				print_all, flat, raw_pretty, verbose, pretty,
+				depth,
 				MR_trace_browser_persistent_state,
 				&MR_trace_browser_persistent_state);
 		);
 	}
-	else if (MR_streq(param, "size") && MR_trace_is_natural_number(value, &size))
+	else if (MR_streq(param, "size") &&
+		MR_trace_is_natural_number(value, &size))
 	{
 		MR_TRACE_CALL_MERCURY(
-			ML_BROWSE_set_param_size(print, browse, print_all,
-				flat, raw_pretty, verbose, pretty, size,
+			ML_BROWSE_set_param_size_from_mdb(print, browse,
+				print_all, flat, raw_pretty, verbose, pretty,
+				size,
 				MR_trace_browser_persistent_state,
 				&MR_trace_browser_persistent_state);
 		);
 	}
-	else if (MR_streq(param, "width") && MR_trace_is_natural_number(value, &width))
+	else if (MR_streq(param, "width") &&
+		MR_trace_is_natural_number(value, &width))
 	{
 		MR_TRACE_CALL_MERCURY(
-			ML_BROWSE_set_param_width(print, browse, print_all,
-				flat, raw_pretty, verbose, pretty, width,
+			ML_BROWSE_set_param_width_from_mdb(print, browse,
+				print_all, flat, raw_pretty, verbose, pretty,
+				width,
 				MR_trace_browser_persistent_state,
 				&MR_trace_browser_persistent_state);
 		);
 	}
-	else if (MR_streq(param, "lines") && MR_trace_is_natural_number(value, &lines))
+	else if (MR_streq(param, "lines") &&
+		MR_trace_is_natural_number(value, &lines))
 	{
 		MR_TRACE_CALL_MERCURY(
-			ML_BROWSE_set_param_lines(print, browse, print_all,
-				flat, raw_pretty, verbose, pretty, lines,
+			ML_BROWSE_set_param_lines_from_mdb(print, browse,
+				print_all, flat, raw_pretty, verbose, pretty,
+				lines,
 				MR_trace_browser_persistent_state,
 				&MR_trace_browser_persistent_state);
 		);
cvs diff: Diffing util
cvs diff: Diffing vim
cvs diff: Diffing vim/after
cvs diff: Diffing vim/ftplugin
cvs diff: Diffing vim/syntax
--------------------------------------------------------------------------
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