Change grade handling

Thomas Charles CONWAY conway at cs.mu.OZ.AU
Thu Jul 23 15:50:20 AEST 1998


Hi

Fergus, these are the changes we discussed yesterday.
If anyone else wants to review them, feel free - I'm sure Fergus won't
mind.

-- 
Thomas Conway <conway at cs.mu.oz.au>
Nail here [] for new monitor.  )O+


This change makes the parsing of GRADE/--grade strings more flexible.
The GADE string can now have its components given in any order. The
only places that depend on the order are those that use the grade as
part of a pathname: ml and install_grades. There is also a new option
to the compiler `--output-grade-string' which prints the grade string
for the set of options given to mmc/mmake.

NEWS:	mention the changes.

compiler/handle_options.m:
	Reimplement convert_grade_option to accept a grade string with
	its components in any order. The conversion is now table-driven,
	which should make it easier to add new dimensions to the grade
	and new values to existing ones.

	Reimplement compute_grade to use the same table as
	convert_grade_option.

compiler/mercury_compile.m:
	If --output-grade-string option was given, just compute the
	grade string and print it.

compiler/options.m:
	Add the --output-grade-string option.

library/list.m:
	Add an extra mode to list__foldl2 (gee, it would be nice to be
	able to make higher order predicates polymorphic in their
	determinism).

scripts/ml.in:
	Include .par in the grade string. (bugfix)

scripts/parse_grade_options.sh-subr:
	split the grade string into . separated pieces and process them
	in a loop, setting the appropriate options.

runtime/getopt.h:
	fix a prototype so that it *is* a prototype to shut up gcc.

cvs diff: Diffing .
Index: NEWS
===================================================================
RCS file: /home/staff/zs/imp/mercury/NEWS,v
retrieving revision 1.108
diff -u -r1.108 NEWS
--- NEWS	1998/07/09 07:18:04	1.108
+++ NEWS	1998/07/23 05:38:17
@@ -200,6 +200,10 @@
 
 * We have fixed a few minor bugs.
 
+* The components of the GRADE mmake variable/the argument to the --grade
+  option may now be given in any order. The compiler also has a new option
+  `--output-grade-string' which prints the cannonical grade string for
+  the set of options with which the compiler was invoked.
 
 NEWS for Mercury release 0.7.3
 ------------------------------
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/include
cvs diff: Diffing boehm_gc/include/private
cvs diff: Diffing browser
cvs diff: Diffing bytecode
cvs diff: Diffing bytecode/test
cvs diff: Diffing compiler
Index: compiler/handle_options.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/handle_options.m,v
retrieving revision 1.59
diff -u -r1.59 handle_options.m
--- handle_options.m	1998/07/20 10:00:46	1.59
+++ handle_options.m	1998/07/23 05:26:45
@@ -47,7 +47,7 @@
 :- implementation.
 
 :- import_module options, globals, prog_io_util.
-:- import_module int, string, map, getopt, library.
+:- import_module char, int, string, map, set, getopt, library.
 
 handle_options(MaybeError, Args, Link) -->
 	io__command_line_arguments(Args0),
@@ -453,313 +453,6 @@
 		[]
 	).
 
-	% IMPORTANT: any changes here may require similar changes to
-	%	runtime/mercury_grade.h
-	%	scripts/ml.in
-
-compute_grade(Globals, Grade) :-
-	globals__lookup_bool_option(Globals, asm_labels, AsmLabels),
-	globals__lookup_bool_option(Globals, gcc_non_local_gotos,
-						NonLocalGotos),
-	globals__lookup_bool_option(Globals, gcc_global_registers, GlobalRegs),
-	globals__get_gc_method(Globals, GC_Method),
-	globals__lookup_bool_option(Globals, profile_time, ProfileTime),
-	globals__lookup_bool_option(Globals, profile_calls, ProfileCalls),
-	globals__lookup_bool_option(Globals, profile_memory, ProfileMemory),
-	globals__lookup_bool_option(Globals, use_trail, UseTrail),
-/*
-% These vary from machine to machine, and (for backwards compatibility,
-% if nothing else) we want examples such as "GRADE = asm_fast.gc.prof"
-% to continue to work, so we can't include these in the grade.
-	globals__get_tags_method(Globals, TagsMethod),
-	globals__lookup_int_option(Globals, tag_bits, TagBits),
-	globals__lookup_bool_option(Globals, unboxed_float, UnboxedFloat),
-*/
-	globals__get_args_method(Globals, ArgsMethod),
-	globals__lookup_bool_option(Globals, parallel, Parallel),
-	globals__lookup_bool_option(Globals, stack_trace, StackTrace),
-	globals__lookup_bool_option(Globals, require_tracing, RequireTracing),
-/*
-	globals__lookup_bool_option(Globals, pic_reg, PIC_Reg),
-*/
-
-	( AsmLabels = yes ->
-		Part1 = "asm_"
-	;
-		Part1 = ""
-	),
-	( NonLocalGotos = yes ->
-		( GlobalRegs = yes ->
-			Part2 = "fast"
-		;
-			Part2 = "jump"
-		)
-	;
-		( GlobalRegs = yes ->
-			Part2 = "reg"
-		;
-			Part2 = "none"
-		)
-	),
-	( Parallel = yes, Part2a = ".par"
-	; Parallel = no, Part2a = ""
-	),
-	( GC_Method = conservative, Part3 = ".gc"
-	; GC_Method = accurate, Part3 = ".agc"
-	; GC_Method = none, Part3 = ""
-	),
-	( ProfileTime = yes ->
-		( ProfileCalls = yes ->
-			( ProfileMemory = yes ->
-				Part4 = ".profall"
-			;
-				Part4 = ".prof"
-			)
-		;
-			( ProfileMemory = yes ->
-				Part4 = ".profmemtime" /* not allowed */
-					/* `ml' will catch the error */
-			;
-				Part4 = ".proftime" /* currently useless */
-			)
-		)
-	;
-		( ProfileCalls = yes ->
-			( ProfileMemory = yes ->
-				Part4 = ".memprof"
-			;
-				Part4 = ".profcalls"
-			)
-		;
-			( ProfileMemory = yes ->
-				Part4 = ".profmem" /* not allowed */
-					/* `ml' will catch the error */
-			;
-				Part4 = ""
-			)
-		)
-	),
-	( UseTrail = yes ->
-		Part5 = ".tr"
-	;
-		Part5 = ""
-	),
-
-/*
-% These vary from machine to machine, and (for backwards compatibility,
-% if nothing else) we want examples such as "GRADE = asm_fast.gc.prof"
-% to continue to work, so we can't include these in the grade.
-	( HighTags = yes ->
-		string__format(".hightags%d", [i(TagBits)], Part6)
-	;
-		string__format(".tags%d", [i(TagBits)], Part6)
-	),
-	( UnboxedFloat = yes ->
-		Part7 = ".ubf"
-	;
-		Part7 = ""
-	),
-*/
-	Part6 = "",
-	Part7 = "",
-
-	( ArgsMethod = compact, Part8 = ""
-	; ArgsMethod = simple, Part8 = ".sa"
-	),
-
-	( StackTrace = yes ->
-		( RequireTracing = yes ->
-			Part9 = ".debug"
-		;
-			Part9 = ".strce"
-		)
-	;
-		( RequireTracing = yes ->
-			Part9 = ".trace"
-		;
-			Part9 = ""
-		)
-	),
-
-/*******
-	% This can't be part of the grade, due to the way
-	% we handle things on Linux.  See README.Linux.
-	( PIC_Reg = yes ->
-		Part10 = ".picreg"
-	;
-		Part10 = ""
-	),
-*******/
-	Part10 = "",
-
-	string__append_list( [Part1, Part2, Part2a, Part3, Part4, Part5,
-				Part6, Part7, Part8, Part9, Part10], Grade).
-
-	% IMPORTANT: any changes here may require similar changes to
-	%	runtime/mercury_grade.h
-	%	scripts/parse_grade_options.sh-subr
-
-convert_grade_option(Grade0) -->
-	% part10
-	( { string__remove_suffix(Grade0, ".picreg", Grade1) } ->
-		{ Grade2 = Grade1 },
-		set_bool_opt(pic_reg, yes)
-	;
-		{ Grade2 = Grade0 },
-		set_bool_opt(pic_reg, no)
-	),
-	% part9
-	( { string__remove_suffix(Grade2, ".debug", Grade3) } ->
-		{ Grade4 = Grade3 },
-		set_bool_opt(stack_trace, yes),
-		set_bool_opt(require_tracing, yes)
-	; { string__remove_suffix(Grade2, ".trace", Grade3) } ->
-		{ Grade4 = Grade3 },
-		set_bool_opt(stack_trace, no),
-		set_bool_opt(require_tracing, yes)
-	; { string__remove_suffix(Grade2, ".strce", Grade3) } ->
-		{ Grade4 = Grade3 },
-		set_bool_opt(stack_trace, yes),
-		set_bool_opt(require_tracing, no)
-	;
-		{ Grade4 = Grade2 },
-		set_bool_opt(stack_trace, no),
-		set_bool_opt(require_tracing, no)
-	),
-	% part8
-	( { string__remove_suffix(Grade4, ".sa", Grade5) } ->
-		{ Grade6 = Grade5 },
-		set_string_opt(args, "simple")
-	;
-		{ Grade6 = Grade4 },
-		set_string_opt(args, "compact")
-	),
-	% part6 & 7
-	{ Grade10 = Grade6 },
-	% part5
-	( { string__remove_suffix(Grade10, ".tr", Grade11) } ->
-		{ Grade12 = Grade11 },
-		set_bool_opt(use_trail, yes)
-	;
-		{ Grade12 = Grade10 },
-		set_bool_opt(use_trail, no)
-	),
-	% part 4
-	( { string__remove_suffix(Grade12, ".prof", Grade13) } ->
-		{ Grade14 = Grade13 },
-		set_bool_opt(profile_time, yes),
-		set_bool_opt(profile_calls, yes),
-		set_bool_opt(profile_memory, no)
-	; { string__remove_suffix(Grade12, ".proftime", Grade13) } ->
-		{ Grade14 = Grade13 },
-		set_bool_opt(profile_time, yes),
-		set_bool_opt(profile_calls, no),
-		set_bool_opt(profile_memory, no)
-	; { string__remove_suffix(Grade12, ".profcalls", Grade13) } ->
-		{ Grade14 = Grade13 },
-		set_bool_opt(profile_time, no),
-		set_bool_opt(profile_calls, yes),
-		set_bool_opt(profile_memory, no)
-	; { string__remove_suffix(Grade12, ".profall", Grade13) } ->
-		{ Grade14 = Grade13 },
-		set_bool_opt(profile_time, yes),
-		set_bool_opt(profile_calls, yes),
-		set_bool_opt(profile_memory, yes)
-	; { string__remove_suffix(Grade12, ".memprof", Grade13) } ->
-		{ Grade14 = Grade13 },
-		set_bool_opt(profile_time, no),
-		set_bool_opt(profile_calls, yes),
-		set_bool_opt(profile_memory, yes)
-	;
-		{ Grade14 = Grade12 },
-		set_bool_opt(profile_time, no),
-		set_bool_opt(profile_calls, no),
-		set_bool_opt(profile_memory, no)
-	),
-	% part 3
-	( { string__remove_suffix(Grade14, ".gc", Grade15) } ->
-		{ Grade16 = Grade15 },
-		{ GC = conservative }
-	; { string__remove_suffix(Grade14, ".agc", Grade15) } ->
-		{ Grade16 = Grade15 },
-		{ GC = accurate }
-	;
-		{ Grade16 = Grade14 },
-		{ GC = none }
-	),
-	% Set the type of gc that the grade option implies.
-	% 'accurate' is now set in the grade, so we can override it here.
-	(
-		{ GC = accurate },
-		set_string_opt(gc, "accurate")
-	;
-		{ GC = conservative },
-		set_string_opt(gc, "conservative")
-	;
-		{ GC = none },
-		set_string_opt(gc, "none")
-	),
-	( { string__remove_suffix(Grade16, ".par", Grade17) } ->
-		{ Grade = Grade17 },
-		set_bool_opt(parallel, yes)
-	;
-		{ Grade = Grade16 }
-	),
-	% parts 2 & 1
-	convert_grade_option_2(Grade).
-
-:- pred convert_grade_option_2(string::in, option_table::in, option_table::out)
-	is semidet.
-
-convert_grade_option_2("asm_fast") -->
-	set_bool_opt(c_optimize, yes),
-	set_bool_opt(gcc_non_local_gotos, yes),
-	set_bool_opt(gcc_global_registers, yes),
-	set_bool_opt(asm_labels, yes).
-convert_grade_option_2("fast") -->
-	set_bool_opt(c_optimize, yes),
-	set_bool_opt(gcc_non_local_gotos, yes),
-	set_bool_opt(gcc_global_registers, yes),
-	set_bool_opt(asm_labels, no).
-convert_grade_option_2("asm_jump") -->
-	set_bool_opt(c_optimize, yes),
-	set_bool_opt(gcc_non_local_gotos, yes),
-	set_bool_opt(gcc_global_registers, no),
-	set_bool_opt(asm_labels, yes).
-convert_grade_option_2("jump") -->
-	set_bool_opt(c_optimize, yes),
-	set_bool_opt(gcc_non_local_gotos, yes),
-	set_bool_opt(gcc_global_registers, no),
-	set_bool_opt(asm_labels, no).
-convert_grade_option_2("reg") -->
-	set_bool_opt(c_optimize, yes),
-	set_bool_opt(gcc_non_local_gotos, no),
-	set_bool_opt(gcc_global_registers, yes),
-	set_bool_opt(asm_labels, no).
-convert_grade_option_2("none") -->
-	set_bool_opt(c_optimize, yes),
-	set_bool_opt(gcc_non_local_gotos, no),
-	set_bool_opt(gcc_global_registers, no),
-	set_bool_opt(asm_labels, no).
-
-:- pred set_bool_opt(option, bool, option_table, option_table).
-:- mode set_bool_opt(in, in, in, out) is det.
-
-set_bool_opt(Option, Value, OptionTable0, OptionTable) :-
-	map__set(OptionTable0, Option, bool(Value), OptionTable).
-
-:- pred set_string_opt(option, string, option_table, option_table).
-:- mode set_string_opt(in, in, in, out) is det.
-
-set_string_opt(Option, Value, OptionTable0, OptionTable) :-
-	map__set(OptionTable0, Option, string(Value), OptionTable).
-
-:- pred get_string_opt(option, string, option_table, option_table).
-:- mode get_string_opt(in, in, in, out) is semidet.
-
-get_string_opt(Option, Value, OptionTable, OptionTable) :-
-	map__lookup(OptionTable, Option, string(Value)).
-
 usage_error(ErrorMessage) -->
 	io__progname_base("mercury_compile", ProgName),
 	io__stderr_stream(StdErr),
@@ -790,3 +483,179 @@
 	io__write_string("\t\tArguments that do not end in `.m' are assumed to be module names.\n"),
 	io__write_string("Options:\n"),
 	options_help.
+
+%-----------------------------------------------------------------------------%
+
+	% IMPORTANT: any changes here may require similar changes to
+	%	runtime/mercury_grade.h
+	%	scripts/parse_grade_options.sh-subr
+	%
+	% The grade_component type should have 1 constructor for each
+	% dimension of the grade. It is used when converting the components
+	% of the grade string to make sure the grade string doesn't contain
+	% more than one value for each dimension (eg *.gc.agc).
+	% Adding a value here will require adding clauses to the
+	% grade_component_table.
+	% The ordering of the components here is the same as the order
+	% used in scripts/ml.in, and any change here will require a
+	% corresponding change there. The only place where the ordering
+	% actually matters is for constructing the pathname for the
+	% grade of the library, etc for linking (and installation).
+:- type grade_component
+	--->	gcc
+	;	gc
+	;	prof
+	;	trail
+	;	args
+	;	trace
+	;	par
+	;	pic
+	.
+
+convert_grade_option(GradeString, Options0, Options) :-
+	split_grade_string(GradeString, Components),
+	set__init(NoComps),
+	list__foldl2(lambda([CompStr::in, Opts0::in, Opts::out,
+			CompSet0::in, CompSet::out] is semidet, (
+		grade_component_table(CompStr, Comp, CompOpts),
+			% Check that the component isn't mentioned
+			% more than once
+		\+ set__member(Comp, CompSet0),
+		set__insert(CompSet0, Comp, CompSet),
+		add_option_list(CompOpts, Opts0, Opts)
+	)), Components, Options0, Options, NoComps, _FinalComps).
+
+:- pred add_option_list(list(pair(option, option_data)), option_table,
+		option_table).
+:- mode add_option_list(in, in, out) is det.
+
+add_option_list(CompOpts, Opts0, Opts) :-
+	list__foldl(lambda([Opt::in, Opts1::in, Opts2::out] is det, (
+		Opt = Option - Data,
+		map__set(Opts1, Option, Data, Opts2)
+	)), CompOpts, Opts0, Opts).
+
+compute_grade(Globals, Grade) :-
+	globals__get_options(Globals, Options),
+	compute_grade_components(Options, Components),
+	(
+		Components = [],
+		Grade = "none"
+	;
+		Components = [_|_],
+		construct_string(Components, Grade)
+	).
+
+:- pred construct_string(list(pair(grade_component, string)), string).
+:- mode construct_string(in, out) is det.
+
+construct_string([], "").
+construct_string([_ - Bit|Bits], Grade) :-
+	(
+		Bits = [_|_],
+		construct_string(Bits, Grade0),
+		string__append_list([Bit, ".", Grade0], Grade)
+	;
+		Bits = [],
+		Grade = Bit
+	).
+
+:- pred compute_grade_components(option_table,
+		list(pair(grade_component, string))).
+:- mode compute_grade_components(in, out) is det.
+
+compute_grade_components(Options, GradeComponents) :-
+	solutions(lambda([CompData::out] is nondet, (
+		grade_component_table(Name, Comp, CompOpts),
+		\+ (
+			list__member(Opt - Value, CompOpts),
+			\+ map__search(Options, Opt, Value)
+		),
+		CompData = Comp - Name
+	)), GradeComponents).
+
+:- pred grade_component_table(string, grade_component,
+		list(pair(option, option_data))).
+:- mode grade_component_table(in, out, out) is semidet.
+:- mode grade_component_table(out, out, out) is multi.
+
+	% Args method components
+grade_component_table("sa", args, [args - string("simple")]).
+
+	% GCC-hack components
+grade_component_table("none", gcc, [asm_labels - bool(no),
+	gcc_non_local_gotos - bool(no), gcc_global_registers - bool(no)]).
+grade_component_table("reg", gcc, [asm_labels - bool(no),
+	gcc_non_local_gotos - bool(no), gcc_global_registers - bool(yes)]).
+grade_component_table("jump", gcc, [asm_labels - bool(no),
+	gcc_non_local_gotos - bool(yes), gcc_global_registers - bool(no)]).
+grade_component_table("asm_jump", gcc, [asm_labels - bool(yes),
+	gcc_non_local_gotos - bool(yes), gcc_global_registers - bool(no)]).
+grade_component_table("fast", gcc, [asm_labels - bool(no),
+	gcc_non_local_gotos - bool(yes), gcc_global_registers - bool(yes)]).
+grade_component_table("asm_fast", gcc, [asm_labels - bool(yes),
+	gcc_non_local_gotos - bool(yes), gcc_global_registers - bool(yes)]).
+
+	% GC components
+grade_component_table("nogc", gc, [gc - string("none")]).
+grade_component_table("gc", gc, [gc - string("conservative")]).
+grade_component_table("agc", gc, [gc - string("accurate")]).
+grade_component_table("par", par, [parallel - bool(yes)]).
+
+	% Pic reg components
+grade_component_table("picreg", pic, [pic_reg - bool(yes)]).
+
+	% Profiling components
+grade_component_table("prof", prof, [profile_time - bool(yes),
+	profile_calls - bool(yes), profile_memory - bool(no)]).
+grade_component_table("proftime", prof, [profile_time - bool(yes),
+	profile_calls - bool(no), profile_memory - bool(no)]).
+grade_component_table("profcalls", prof, [profile_time - bool(no),
+	profile_calls - bool(yes), profile_memory - bool(no)]).
+grade_component_table("memprof", prof, [profile_time - bool(no),
+	profile_calls - bool(no), profile_memory - bool(yes)]).
+grade_component_table("profall", prof, [profile_time - bool(yes),
+	profile_calls - bool(yes), profile_memory - bool(yes)]).
+
+	% Debugging/Tracing components
+grade_component_table("debug", trace,
+	[stack_trace - bool(yes), require_tracing - bool(yes)]).
+grade_component_table("trace", trace,
+	[stack_trace - bool(no), require_tracing - bool(yes)]).
+grade_component_table("strace", trace,
+	[stack_trace - bool(yes), require_tracing - bool(no)]).
+
+	% Trailing components
+grade_component_table("tr", trail, [use_trail - bool(yes)]).
+
+
+:- pred split_grade_string(string, list(string)).
+:- mode split_grade_string(in, out) is semidet.
+
+split_grade_string(GradeStr, Components) :-
+	string__to_char_list(GradeStr, Chars),
+	split_grade_string_2(Chars, Components).
+
+:- pred split_grade_string_2(list(char), list(string)).
+:- mode split_grade_string_2(in, out) is semidet.
+
+split_grade_string_2([], []).
+split_grade_string_2(Chars, Components) :-
+	Chars = [_|_],
+	list__takewhile(char_is_not('.'), Chars, ThisChars, RestChars0),
+	string__from_char_list(ThisChars, ThisComponent),
+	Components = [ThisComponent|RestComponents],
+	(
+		RestChars0 = [_|RestChars], % discard the `.'
+		split_grade_string_2(RestChars, RestComponents)
+	;
+		RestChars0 = [],
+		RestComponents = []
+	).
+
+:- pred char_is_not(char, char).
+:- mode char_is_not(in, in) is semidet.
+
+char_is_not(A, B) :-
+	A \= B.
+
Index: compiler/mercury_compile.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/mercury_compile.m,v
retrieving revision 1.103
diff -u -r1.103 mercury_compile.m
--- mercury_compile.m	1998/07/20 10:01:09	1.103
+++ mercury_compile.m	1998/07/23 04:53:03
@@ -63,8 +63,14 @@
 	usage_error(ErrorMessage).
 main_2(no, Args, Link) -->
 	globals__io_lookup_bool_option(help, Help),
+	globals__io_lookup_bool_option(output_grade_string, OutputGrade),
 	( { Help = yes } ->
 		long_usage
+	; { OutputGrade = yes } ->
+		globals__io_get_globals(Globals),
+		{ compute_grade(Globals, Grade) },
+		io__write_string(Grade),
+		io__write_string("\n")
 	; { Args = [] } ->
 		usage
 	;
Index: compiler/options.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/options.m,v
retrieving revision 1.236
diff -u -r1.236 options.m
--- options.m	1998/07/20 10:01:19	1.236
+++ options.m	1998/07/23 04:53:32
@@ -86,6 +86,7 @@
 		;	errorcheck_only
 		;	compile_to_c
 		;	compile_only
+		;	output_grade_string
 	% Auxiliary output options
 		;	assume_gmake
 		;	trace
@@ -364,7 +365,8 @@
 	typecheck_only		-	bool(no),
 	errorcheck_only		-	bool(no),
 	compile_to_c		-	bool(no),
-	compile_only		-	bool(no)
+	compile_only		-	bool(no),
+	output_grade_string	-	bool(no)
 ]).
 option_defaults_2(aux_output_option, [
 		% Auxiliary Output Options
@@ -692,6 +694,7 @@
 long_option("compile-to-c",		compile_to_c).
 long_option("compile-to-C",		compile_to_c).
 long_option("compile-only",		compile_only).
+long_option("output-grade-string",	output_grade_string).
 
 % aux output options
 long_option("assume-gmake",		assume_gmake).
@@ -1346,7 +1349,10 @@
 	io__write_string("\t\tGenerate C code in `<module>.c', but not object code.\n"),
 	io__write_string("\t-c, --compile-only\n"),
 	io__write_string("\t\tGenerate C code in `<module>.c' and object code in `<module>.o'\n"),
-	io__write_string("\t\tbut do not attempt to link the named modules.\n").
+	io__write_string("\t\tbut do not attempt to link the named modules.\n"),
+	io__write_string("\t\t--output-grade-string\n"),
+	io__write_string("\t\tCompute the grade of the library to link with based on\n"),
+	io__write_string("\t\tthe command line options.\n").
 
 :- pred options_help_aux_output(io__state::di, io__state::uo) is det.
 
cvs diff: Diffing compiler/notes
cvs diff: Diffing doc
cvs diff: Diffing extras
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/exceptions
cvs diff: Diffing extras/graphics
cvs diff: Diffing extras/graphics/Togl-1.2
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/odbc
cvs diff: Diffing extras/references
cvs diff: Diffing extras/references/samples
cvs diff: Diffing extras/references/tests
cvs diff: Diffing extras/trailed_update
cvs diff: Diffing extras/trailed_update/samples
cvs diff: Diffing extras/trailed_update/tests
cvs diff: Diffing library
Index: library/list.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/library/list.m,v
retrieving revision 1.83
diff -u -r1.83 list.m
--- list.m	1998/06/25 00:34:13	1.83
+++ list.m	1998/07/22 01:33:30
@@ -382,6 +382,8 @@
 :- pred list__foldl2(pred(X, Y, Y, Z, Z), list(X), Y, Y, Z, Z).
 :- mode list__foldl2(pred(in, in, out, in, out) is det,
 		in, in, out, in, out) is det.
+:- mode list__foldl2(pred(in, in, out, in, out) is semidet,
+		in, in, out, in, out) is semidet.
 :- mode list__foldl2(pred(in, in, out, mdi, muo) is det,
 		in, in, out, mdi, muo) is det.
 :- mode list__foldl2(pred(in, in, out, di, uo) is det,
cvs diff: Diffing lp_solve
cvs diff: Diffing lp_solve/lp_examples
cvs diff: Diffing profiler
cvs diff: Diffing runtime
Index: runtime/getopt.h
===================================================================
RCS file: /home/staff/zs/imp/mercury/runtime/getopt.h,v
retrieving revision 1.11
diff -u -r1.11 getopt.h
--- getopt.h	1998/07/07 09:06:18	1.11
+++ getopt.h	1998/07/21 23:07:33
@@ -103,7 +103,7 @@
    errors, only prototype getopt for the GNU C library.  */
 extern int getopt (int argc, char *const *argv, const char *shortopts);
 #else /* not __GNU_LIBRARY__ */
-extern int getopt ();
+extern int getopt (int, char * const *, const char *);
 #endif /* __GNU_LIBRARY__ */
 extern int getopt_long (int argc, char *const *argv, const char *shortopts,
 		        const struct option *longopts, int *longind);
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 scripts
Index: scripts/ml.in
===================================================================
RCS file: /home/staff/zs/imp/mercury/scripts/ml.in,v
retrieving revision 1.45
diff -u -r1.45 ml.in
--- ml.in	1998/07/01 07:41:47	1.45
+++ ml.in	1998/07/23 05:16:49
@@ -304,6 +304,10 @@
 	true,false)	GRADE="$GRADE.strce" ;;
 	false,false)	;;
 esac
+case $thread_safe in
+	true)	GRADE="$GRADE.par" ;;
+	false)	;;
+esac
 
 case "$GRADE" in
 	*.gc.prof*)
Index: scripts/parse_grade_options.sh-subr
===================================================================
RCS file: /home/staff/zs/imp/mercury/scripts/parse_grade_options.sh-subr,v
retrieving revision 1.5
diff -u -r1.5 parse_grade_options.sh-subr
--- parse_grade_options.sh-subr	1998/06/09 02:16:31	1.5
+++ parse_grade_options.sh-subr	1998/07/23 04:51:05
@@ -125,141 +125,95 @@
 		#	compiler/handle_options.m
 		#	scripts/ml.in
 
-		case "$grade" in
-			*.debug)
+	    grade_pieces=`echo $grade | tr '.' ' '`
+	    for grade_piece in $grade_pieces
+	    do
+		case "$grade_piece" in
+			debug)
 				stack_trace=true
 				require_tracing=true
-				grade="` expr $grade : '\(.*\).debug' `"
 				;;
 # The following alternatives have been omitted since
 # they're not very useful and would probably just confuse people.
-#			*.trace)
+#			trace)
 #				stack_trace=false
 #				require_tracing=true
-#				grade="` expr $grade : '\(.*\).trace' `"
 #				;;
-#			*.strce)
+#			strce)
 #				stack_trace=true
 #				require_tracing=false
-#				grade="` expr $grade : '\(.*\).strce' `"
 #				;;
-			*)	
-				stack_trace=false
-				require_tracing=false
-				;;
-		esac
-
-		case "$grade" in
-			*.sa)
+			sa)
 				args_method=simple
-				grade="` expr $grade : '\(.*\).sa' `"
-				;;
-			*)	args_method=compact
-				;;
-		esac
-
-		case "$grade" in
-			*.tr)	use_trail=true
-				grade="` expr $grade : '\(.*\).tr' `"
 				;;
-			*)	use_trail=false
+			tr)	use_trail=true
 				;;
-		esac
-
-		case "$grade" in
-			*.memprof)
+			memprof)
 				profile_time=false
 				profile_calls=true
 				profile_memory=true
-				grade="` expr $grade : '\(.*\).memprof' `"
 				;;
-			*.prof)
+			prof)
 				profile_time=true
 				profile_calls=true
 				profile_memory=false
-				grade="` expr $grade : '\(.*\).prof' `"
 				;;
-			*.proftime)	
+			proftime)	
 				profile_time=true
 				profile_calls=false
 				profile_memory=false
-				grade="` expr $grade : '\(.*\).proftime' `"
 				;;
-			*.profcalls)	
+			profcalls)	
 				profile_time=false
 				profile_calls=true
 				profile_memory=false
-				grade="` expr $grade : '\(.*\).profcalls' `"
 				;;
-			*.profall)
+			profall)
 				profile_time=true
 				profile_calls=true
 				profile_memory=true
-				grade="` expr $grade : '\(.*\).profall' `"
-				;;
-			*)
-				profile_time=false
-				profile_calls=false
-				profile_memory=false
 				;;
-		esac
-
-		case "$grade" in
-			*.agc)	gc_method=accurate
-				grade="` expr $grade : '\(.*\).agc' `"
+			agc)	gc_method=accurate
 				;;
-			*.gc)	gc_method=conservative
-				grade="` expr $grade : '\(.*\).gc' `"
+			gc)	gc_method=conservative
 				;;
-			*)	gc_method=none
+			nogc)	gc_method=none
 				;;
-		esac
-
-		case "$grade" in
-			*.par)	thread_safe=true
-				grade="` expr $grade : '\(.*\).par' `"
+			par)	thread_safe=true
 				;;
-			*)	thread_safe=false
-				;;
-		esac
-
-		case "$grade" in
 			asm_fast)
-				global_regs=true
-				non_local_gotos=true
 				asm_labels=true
-				;;
-			fast)
-				global_regs=true
 				non_local_gotos=true
-				asm_labels=false
-				;;
-			reg)
 				global_regs=true
-				non_local_gotos=false
-				asm_labels=false
 				;;
 			asm_jump)
-				global_regs=false
-				non_local_gotos=true
 				asm_labels=true
+				non_local_gotos=true
 				;;
-			jump)
-				global_regs=false
+			fast)
 				asm_labels=false
 				non_local_gotos=true
+				global_regs=true
 				;;
-			none)
+			jump)
+				asm_labels=false
+				non_local_gotos=true
 				global_regs=false
+				;;
+			reg)
 				asm_labels=false
 				non_local_gotos=false
+				global_regs=true
 				;;
-			*)
-				echo "$0: invalid grade \`$grade'" 1>&2;
-				exit 1
+			none)
+				asm_labels=false
+				non_local_gotos=false
+				global_regs=false
 				;;
 		esac
-		;;
+	    done
+	    ;;
+
 	-s*)
 		grade="` expr $1 : '-s\(.*\)' `"
 		# just insert it as `--grade $grade' and then reparse it
@@ -268,3 +222,4 @@
 			0) set - "x --grade $grade" "$@" ;;
 		esac
 		;;
+
cvs diff: Diffing tools
cvs diff: Diffing trial
cvs diff: Diffing util



More information about the developers mailing list