[m-dev.] diff: MLDS back-end: implement --no-gcc-nested-functions

Fergus Henderson fjh at cs.mu.OZ.AU
Tue Nov 9 09:27:15 AEDT 1999


As usual, review comments are always welcome.
But I'll go ahead and commit this now anyway.
(The MLDS back-end is quite separate from the rest of it,
so these changes won't introduce any problems for the main
compiler.)

----------

Estimated hours taken: 30

Modify the MLDS back-end to support the `--no-gcc-nested-functions' option.

compiler/ml_elim_nested.m:
	New module.  Contains an MLDS->MLDS transformation pass
	to eliminated nested functions.

compiler/mercury_compile.m:
	Call the new pass.

compiler/notes/compiler_design.html:
	Mention the new module.

compiler/ml_code_gen.m:
	If --no-gcc-nested-functions is specified, then pass
	environment pointers to the nested continuation functions.

	Note that most of the work of converting nested functions
	into non-nested functions is deferred to the ml_elim_nested
	pass.  But the passing of environment pointers affects the
	calling convention, and so it really needs to be done
	here -- it can't be done in any semantics-preserving
	MLDS transformation later one.  Also it is easier to do
	it in this pass anyway.

	Also fix a bug where it was miscalculating the set of
	variables to declare.

compiler/mlds.m:
	- Add a new alternative `mlds__generic_env_ptr_type',
	  used for environment pointers.
	- Add a new alternative `mlds__class_type' to the
	  `mlds__type' discriminated union, so that types
	  can include user-defined types.  This is needed so
	  that we can define struct types for the nested
	  function enviroments.
	  As part of that change, rename `mlds__class' as `mlds__class_defn'.
	- Change the argument type for the `do_commit' and `try_commit'
	  instructions from `var' to `rval'/`lval'.  This is needed so that
	  these instructions can refer to references defined in the
	  containing function via the environment pointer.

compiler/mlds_to_c.m:
	- Changed to reflect the renaming of `mlds__class'
	  as `mlds__class_defn'.
	- Changed to reflect the change to the `do_commit' and `try_commit'
	  argument types.
	- For the `mlds__cont_type' type, output it as either
	  `MR_NestedCont' or `MR_Cont', depending on whether
	  the `--gcc-nested-functions' option is enabled.
	- Fix a bug where it would incorrectly parenthesizing
	  the left-hand operand of `->'.
	- Insert some additional blank lines in the output,
	  for readability.

runtime/mercury_types.h:
	- Rename the old `Cont' type as `MR_NestedCont',
	  and add a new `MR_Cont' type.

Workspace: /d-drive/home/hg/fjh/mercury
Index: compiler/mercury_compile.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mercury_compile.m,v
retrieving revision 1.142
diff -u -d -r1.142 mercury_compile.m
--- compiler/mercury_compile.m	1999/11/06 05:03:49	1.142
+++ compiler/mercury_compile.m	1999/11/06 12:57:24
@@ -45,7 +45,7 @@
 :- import_module llds_common, transform_llds, llds_out.
 :- import_module continuation_info, stack_layout.
 
-:- import_module mlds, ml_code_gen, mlds_to_c.
+:- import_module mlds, ml_code_gen, ml_elim_nested, mlds_to_c.
 
 	% miscellaneous compiler modules
 :- import_module prog_data, hlds_module, hlds_pred, hlds_out, llds, rl.
@@ -2234,9 +2234,8 @@
 
 	globals__io_lookup_bool_option(gcc_nested_functions, NestedFuncs),
 	( { NestedFuncs = no } ->
-		% XXX the pass to convert nested functions into unnested
-		% functions is not yet implemented.
-		{ error("Sorry, not implemented: --no-gcc-nested-functions.") }
+		maybe_write_string(Verbose, "% Flattening nested functions...\n"),
+		ml_elim_nested(MLDS0, MLDS)
 	;
 		{ MLDS = MLDS0 }
 	),
Index: compiler/ml_code_gen.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/ml_code_gen.m,v
retrieving revision 1.12
diff -u -d -r1.12 ml_code_gen.m
--- compiler/ml_code_gen.m	1999/11/05 21:18:53	1.12
+++ compiler/ml_code_gen.m	1999/11/08 20:41:42
@@ -552,8 +552,8 @@
 %			- constructions
 %			- deconstructions
 %		- switches
+%		- commits
 % TODO:
-%	- commits
 %	- c_code pragmas
 %	- no_tag types
 %	- construction of closures, and higher-order calls
@@ -590,8 +590,9 @@
 :- import_module hlds_pred, hlds_goal, hlds_data, prog_data, special_pred.
 :- import_module hlds_out, builtin_ops, passes_aux, type_util, mode_util.
 :- import_module prog_util.
+:- import_module globals, options.
 
-:- import_module string, int, varset, term.
+:- import_module string, int, bool, varset, term.
 :- import_module list, assoc_list, map, set, stack.
 :- import_module require, std_util.
 
@@ -779,8 +780,9 @@
 	MLDS_Params = ml_gen_params(ModuleInfo, PredId, ProcId),
 	( CodeModel = model_non ->
 		% set up the initial success continuation
-		ml_cont_rval(Cont, MLDSGenInfo0, MLDSGenInfo1),
-		ml_gen_info_push_success_cont(Cont, MLDSGenInfo1, MLDSGenInfo2)
+		ml_initial_cont(InitialCont, MLDSGenInfo0, MLDSGenInfo1),
+		ml_gen_info_push_success_cont(InitialCont,
+			MLDSGenInfo1, MLDSGenInfo2)
 	;
 		MLDSGenInfo2 = MLDSGenInfo0
 	),
@@ -862,17 +864,6 @@
 	DeclFlags = ml_gen_var_decl_flags,
 	MLDS_Defn = mlds__defn(Name, Context, DeclFlags, Defn).
 
-	% Generate the declaration for the `commit' variable.
-	%
-:- func ml_gen_commit_var_decl(mlds__context, mlds__var_name) = mlds__defn.
-ml_gen_commit_var_decl(Context, VarName) = MLDS_Defn :-
-	Name = data(var(VarName)),
-	Type = mlds__commit_type,
-	MaybeInitializer = no,
-	Defn = data(Type, MaybeInitializer),
-	DeclFlags = ml_gen_var_decl_flags,
-	MLDS_Defn = mlds__defn(Name, Context, DeclFlags, Defn).
-
 	% Generate the code for a procedure body.
 	%
 :- pred ml_gen_proc_body(code_model, hlds_goal, mlds__defns, mlds__statements,
@@ -929,27 +920,32 @@
 			ml_gen_info, ml_gen_info).
 :- mode ml_gen_goal(in, in, out, out, in, out) is det.
 
-ml_gen_goal(CodeModel, Goal - GoalInfo, MLDS_Decls, MLDS_Statements) -->
+ml_gen_goal(CodeModel, Goal, MLDS_Decls, MLDS_Statements) -->
+	{ Goal = GoalExpr - GoalInfo },
 	%
 	% Generate the local variables for this goal.
-	%
-	{ goal_info_get_nonlocals(GoalInfo, NonLocals) },
-	{ SubGoalNonLocals =
-		union_of_direct_subgoal_nonlocals(Goal - GoalInfo) },
-	{ set__difference(SubGoalNonLocals, NonLocals, VarsToDeclareHere) },
-	{ set__to_sorted_list(VarsToDeclareHere, LocalVarsList) },
+	% We need to declare any variables which
+	% are local to this goal (including its subgoals),
+	% but which are not local to a subgoal.
+	% (If they're local to a subgoal, they'll be declared
+	% when we generate code for that subgoal.)
+
+	{ Locals = goal_local_vars(Goal) },
+	{ SubGoalLocals = union_of_direct_subgoal_locals(Goal) },
+	{ set__difference(Locals, SubGoalLocals, VarsToDeclareHere) },
+	{ set__to_sorted_list(VarsToDeclareHere, VarsList) },
 	=(MLDSGenInfo),
 	{ ml_gen_info_get_varset(MLDSGenInfo, VarSet) },
 	{ ml_gen_info_get_var_types(MLDSGenInfo, VarTypes) },
-	{ LocalVarDecls = ml_gen_local_var_decls(VarSet, VarTypes,
-		mlds__make_context(Context), LocalVarsList) },
+	{ VarDecls = ml_gen_local_var_decls(VarSet, VarTypes,
+		mlds__make_context(Context), VarsList) },
 
 	%
 	% Generate code for the goal in its own code model.
 	%
 	{ goal_info_get_context(GoalInfo, Context) },
 	{ goal_info_get_code_model(GoalInfo, GoalCodeModel) },
-	ml_gen_goal_expr(Goal, GoalCodeModel, Context,
+	ml_gen_goal_expr(GoalExpr, GoalCodeModel, Context,
 		GoalDecls, GoalStatements0),
 
 	%
@@ -959,25 +955,35 @@
 	ml_gen_wrap_goal(CodeModel, GoalCodeModel, Context,
 		GoalStatements0, GoalStatements),
 	
-	{ ml_join_decls(LocalVarDecls, [], GoalDecls, GoalStatements, Context,
+	{ ml_join_decls(VarDecls, [], GoalDecls, GoalStatements, Context,
 		MLDS_Decls, MLDS_Statements) }.
 
-:- func union_of_direct_subgoal_nonlocals(hlds_goal) = set(prog_var).
+	% Return the set of variables which occur in the specified goal
+	% (including in its subgoals) and which are local to that goal.
+:- func goal_local_vars(hlds_goal) = set(prog_var).
+goal_local_vars(Goal) = LocalVars :-
+	% find all the variables in the goal
+	goal_util__goal_vars(Goal, GoalVars),
+	% delete the non-locals
+	Goal = _ - GoalInfo,
+	goal_info_get_nonlocals(GoalInfo, NonLocalVars),
+	set__difference(GoalVars, NonLocalVars, LocalVars).
 
-union_of_direct_subgoal_nonlocals(Goal - _GoalInfo) =
-	promise_only_solution((pred(UnionOfNonLocals::out) is cc_multi :-
+:- func union_of_direct_subgoal_locals(hlds_goal) = set(prog_var).
+
+union_of_direct_subgoal_locals(Goal - _GoalInfo) =
+	promise_only_solution((pred(UnionOfSubGoalLocals::out) is cc_multi :-
 		set__init(EmptySet),
 		unsorted_aggregate(direct_subgoal(Goal),
-			union_subgoal_nonlocals, EmptySet, UnionOfNonLocals)
+			union_subgoal_locals, EmptySet, UnionOfSubGoalLocals)
 	)).
 
-:- pred union_subgoal_nonlocals(hlds_goal, set(prog_var), set(prog_var)).
-:- mode union_subgoal_nonlocals(in, in, out) is det.
+:- pred union_subgoal_locals(hlds_goal, set(prog_var), set(prog_var)).
+:- mode union_subgoal_locals(in, in, out) is det.
 
-union_subgoal_nonlocals(SubGoal, UnionOfNonLocals0, UnionOfNonLocals) :-
-	SubGoal = _ - SubGoalInfo,
-	goal_info_get_nonlocals(SubGoalInfo, SubGoalNonLocals),
-	set__union(UnionOfNonLocals0, SubGoalNonLocals, UnionOfNonLocals).
+union_subgoal_locals(SubGoal, UnionOfSubGoalLocals0, UnionOfSubGoalLocals) :-
+	SubGoalLocals = goal_local_vars(SubGoal),
+	set__union(UnionOfSubGoalLocals0, SubGoalLocals, UnionOfSubGoalLocals).
 
 	% ml_gen_wrap_goal(OuterCodeModel, InnerCodeModel, Context,
 	%		MLDS_Statements0, MLDS_Statements):
@@ -1089,7 +1095,7 @@
 		%			succeeded = TRUE;
 		%			MR_DO_COMMIT(ref);
 		%		}
-		%		MR_TRY_COMMIT(info, {
+		%		MR_TRY_COMMIT(ref, {
 		%			<Goal && success()>
 		%			succeeded = FALSE;
 		%		}, {
@@ -1102,22 +1108,24 @@
 		{ MLDS_Context = mlds__make_context(Context) },
 		ml_gen_info_new_commit_label(CommitLabelNum),
 		{ string__format("commit_%d", [i(CommitLabelNum)], CommitRef) },
-		ml_commit_var(CommitRef, CommitRefVar),
+		ml_commit_var(CommitRef, CommitRefLval),
 		{ CommitRefDecl = ml_gen_commit_var_decl(MLDS_Context,
 			CommitRef) },
-		{ DoCommitStmt = do_commit(CommitRefVar) },
+		{ DoCommitStmt = do_commit(lval(CommitRefLval)) },
 		{ DoCommitStatement = mlds__statement(DoCommitStmt,
 			MLDS_Context) },
 		/* pop nesting level */
 		ml_gen_label_func(SuccessFuncLabel, Context, DoCommitStatement,
 			SuccessFunc),
 
-		ml_gen_info_push_success_cont(SuccessFuncLabelRval),
+		ml_get_env_ptr(EnvPtrRval),
+		{ SuccessCont = success_cont(SuccessFuncLabelRval, EnvPtrRval) },
+		ml_gen_info_push_success_cont(SuccessCont),
 		ml_gen_goal(model_non, Goal, GoalStatement),
 		ml_gen_info_pop_success_cont,
 		ml_gen_set_success(const(false), Context, SetSuccessFalse),
 		ml_gen_set_success(const(true), Context, SetSuccessTrue),
-		{ TryCommitStmt = try_commit(CommitRefVar,
+		{ TryCommitStmt = try_commit(CommitRefLval,
 			ml_gen_block([], [GoalStatement, SetSuccessFalse],
 				Context),
 			SetSuccessTrue) },
@@ -1146,21 +1154,23 @@
 		{ MLDS_Context = mlds__make_context(Context) },
 		ml_gen_info_new_commit_label(CommitLabelNum),
 		{ string__format("commit_%d", [i(CommitLabelNum)], CommitRef) },
-		ml_commit_var(CommitRef, CommitRefVar),
+		ml_commit_var(CommitRef, CommitRefLval),
 		{ CommitRefDecl = ml_gen_commit_var_decl(MLDS_Context,
 			CommitRef) },
-		{ DoCommitStmt = do_commit(CommitRefVar) },
+		{ DoCommitStmt = do_commit(lval(CommitRefLval)) },
 		{ DoCommitStatement = mlds__statement(DoCommitStmt,
 			MLDS_Context) },
 		/* pop nesting level */
 		ml_gen_label_func(SuccessFuncLabel, Context, DoCommitStatement,
 			SuccessFunc),
 
-		ml_gen_info_push_success_cont(SuccessFuncLabelRval),
+		ml_get_env_ptr(EnvPtrRval),
+		{ SuccessCont = success_cont(SuccessFuncLabelRval, EnvPtrRval) },
+		ml_gen_info_push_success_cont(SuccessCont),
 		ml_gen_goal(model_non, Goal, GoalStatement),
 		ml_gen_info_pop_success_cont,
 
-		{ TryCommitStmt = try_commit(CommitRefVar, GoalStatement,
+		{ TryCommitStmt = try_commit(CommitRefLval, GoalStatement,
 			ml_gen_block([], [], Context)) },
 		{ TryCommitStatement = mlds__statement(TryCommitStmt,
 			MLDS_Context) },
@@ -1172,6 +1182,27 @@
 		ml_gen_goal(CodeModel, Goal, MLDS_Decls, MLDS_Statements)
 	).
 
+	% Generate the declaration for the `commit' variable.
+	%
+:- func ml_gen_commit_var_decl(mlds__context, mlds__var_name) = mlds__defn.
+ml_gen_commit_var_decl(Context, VarName) = MLDS_Defn :-
+	Name = data(var(VarName)),
+	Type = mlds__commit_type,
+	MaybeInitializer = no,
+	Defn = data(Type, MaybeInitializer),
+	DeclFlags = ml_gen_var_decl_flags,
+	MLDS_Defn = mlds__defn(Name, Context, DeclFlags, Defn).
+
+	% Qualify the name of the specified commit var.
+	%
+:- pred ml_commit_var(mlds__var_name, mlds__lval,
+		ml_gen_info, ml_gen_info).
+:- mode ml_commit_var(in, out, in, out) is det.
+ml_commit_var(CommitRef, CommitLval) -->
+	=(MLDSGenInfo),
+	{ ml_gen_info_get_module_name(MLDSGenInfo, ModuleName) },
+	{ MLDS_Module = mercury_module_name_to_mlds(ModuleName) },
+	{ CommitLval = var(qual(MLDS_Module, CommitRef)) }.
 
 	% Generate MLDS code for the different kinds of HLDS goals.
 	%
@@ -1273,7 +1304,14 @@
 		{ CodeModel = model_non },
 		% pass the current success continuation
 		ml_gen_info_current_success_cont(Cont),
-		{ ArgRvals = list__append(ArgRvals0, [Cont]) },
+		{ Cont = success_cont(FuncPtrRval, EnvPtrRval) },
+		ml_gen_info_use_gcc_nested_functions(UseNestedFuncs),
+		( { UseNestedFuncs = yes } ->
+			{ ArgRvals = list__append(ArgRvals0, [FuncPtrRval]) }
+		;
+			{ ArgRvals = list__append(ArgRvals0,
+				[FuncPtrRval, EnvPtrRval]) }
+		),
 		{ RetLvals = RetLvals0 }
 	;
 		{ CodeModel = model_semi },
@@ -1834,7 +1872,9 @@
 
 		% generate the main body
 		ml_gen_set_success(const(false), Context, SetSuccessFalse),
-		ml_gen_info_push_success_cont(ThenFuncLabelRval),
+		ml_get_env_ptr(EnvPtrRval),
+		{ SuccessCont = success_cont(ThenFuncLabelRval, EnvPtrRval) },
+		ml_gen_info_push_success_cont(SuccessCont),
 		ml_gen_goal(model_non, Cond, CondDecls, CondStatements),
 		ml_gen_info_pop_success_cont,
 		ml_gen_test_success(Succeeded),
@@ -1996,7 +2036,9 @@
 		ml_gen_label_func(RestFuncLabel, Context, RestStatement,
 			RestFunc),
 
-		ml_gen_info_push_success_cont(RestFuncLabelRval),
+		ml_get_env_ptr(EnvPtrRval),
+		{ SuccessCont = success_cont(RestFuncLabelRval, EnvPtrRval) },
+		ml_gen_info_push_success_cont(SuccessCont),
 		ml_gen_goal(model_non, First, FirstDecls, FirstStatements),
 		ml_gen_info_pop_success_cont,
 
@@ -2050,7 +2092,13 @@
 	% compute the function definition
 	%
 	{ DeclFlags = ml_gen_label_func_decl_flags },
-	{ FuncParams = mlds__func_params([], []) },
+	ml_gen_info_use_gcc_nested_functions(UseNested),
+	( { UseNested = yes } ->
+		{ FuncParams = mlds__func_params([], []) }
+	;
+		ml_declare_env_ptr_arg(EnvPtrArg),
+		{ FuncParams = mlds__func_params([EnvPtrArg], []) }
+	),
 	{ MaybePredProcId = no },
 	{ FuncDefn = function(MaybePredProcId, FuncParams, yes(Statement)) },
 	{ Func = mlds__defn(FuncName, mlds__make_context(Context), DeclFlags,
@@ -3152,29 +3200,47 @@
 	{ MLDS_Statement = mlds__statement(MLDS_Stmt,
 		mlds__make_context(Context)) }.
 
-	% Return the rval for the current function's `cont' argument.
-	% (The `cont' argument is a continuation function that
-	% will be called when a model_non goal succeeds.)
-	%
-:- pred ml_cont_rval(mlds__rval, ml_gen_info, ml_gen_info).
-:- mode ml_cont_rval(out, in, out) is det.
-ml_cont_rval(ContRval) -->
+	% Return an rval for a pointer to the current environment
+	% (the set of local variables in the containing procedure).
+	% Note that we generate this as a dangling reference.
+	% The ml_elim_nested pass will insert the declaration
+	% of the env_ptr variable.
+:- pred ml_get_env_ptr(mlds__rval, ml_gen_info, ml_gen_info).
+:- mode ml_get_env_ptr(out, in, out) is det.
+ml_get_env_ptr(EnvPtrRval) -->
 	=(MLDSGenInfo),
 	{ ml_gen_info_get_module_name(MLDSGenInfo, ModuleName) },
 	{ MLDS_Module = mercury_module_name_to_mlds(ModuleName) },
-	{ ContRval = lval(var(qual(MLDS_Module, "cont"))) }.
+	{ EnvPtrRval = lval(var(qual(MLDS_Module, "env_ptr"))) }.
 
-	% Return the rval for the current function's `cont' argument.
-	% (The `cont' argument is a continuation function that
-	% will be called when a model_non goal succeeds.)
+	% Return an rval for a pointer to the current environment
+	% (the set of local variables in the containing procedure).
+:- pred ml_declare_env_ptr_arg(pair(mlds__entity_name, mlds__type),
+		ml_gen_info, ml_gen_info).
+:- mode ml_declare_env_ptr_arg(out, in, out) is det.
+ml_declare_env_ptr_arg(Name - mlds__generic_env_ptr_type) -->
+	{ Name = data(var("env_ptr_arg")) }.
+
+	% Return rvals for the success continuation that was
+	% passed as the current function's argument(s).
+	% The success continuation consists of two parts, the
+	% `cont' argument, and the `cont_env' argument.
+	% The `cont' argument is a continuation function that
+	% will be called when a model_non goal succeeds.
+	% The `cont_env' argument is a pointer to the environment (set
+	% of local variables in the containing procedure) for the continuation
+	% function.  (If we're using gcc nested function, the `cont_env'
+	% is not used.)
 	%
-:- pred ml_commit_var(mlds__var_name, mlds__var, ml_gen_info, ml_gen_info).
-:- mode ml_commit_var(in, out, in, out) is det.
-ml_commit_var(CommitRef, CommitVar) -->
+:- pred ml_initial_cont(success_cont, ml_gen_info, ml_gen_info).
+:- mode ml_initial_cont(out, in, out) is det.
+ml_initial_cont(Cont) -->
 	=(MLDSGenInfo),
 	{ ml_gen_info_get_module_name(MLDSGenInfo, ModuleName) },
 	{ MLDS_Module = mercury_module_name_to_mlds(ModuleName) },
-	{ CommitVar = qual(MLDS_Module, CommitRef) }.
+	{ ContRval = lval(var(qual(MLDS_Module, "cont"))) },
+	{ ContEnvRval = lval(var(qual(MLDS_Module, "cont_env_ptr"))) },
+	{ Cont = success_cont(ContRval, ContEnvRval) }.
 
 	% Generate code to call the current success continuation.
 	% This is used for generating success when in a model_non context.
@@ -3185,12 +3251,21 @@
 
 ml_gen_call_current_success_cont(Context, MLDS_Statement) -->
 	ml_gen_info_current_success_cont(SuccCont),
-	{ FuncRval = SuccCont },
-	{ ArgTypes = [] },
+	{ SuccCont = success_cont(FuncRval, EnvPtrRval) },
+	ml_gen_info_use_gcc_nested_functions(UseNestedFuncs),
+	( { UseNestedFuncs = yes } ->
+		{ ArgTypes = [] }
+	;
+		{ ArgTypes = [mlds__generic_env_ptr_type] }
+	),
 	{ RetTypes = [] },
 	{ Signature = mlds__func_signature(ArgTypes, RetTypes) },
 	{ ObjectRval = no },
-	{ ArgRvals = [] },
+	( { UseNestedFuncs = yes } ->
+		{ ArgRvals = [] }
+	;
+		{ ArgRvals = [EnvPtrRval] }
+	),
 	{ RetLvals = [] },
 	{ CallOrTailcall = call },
 	{ MLDS_Stmt = call(Signature, FuncRval, ObjectRval, ArgRvals, RetLvals,
@@ -3198,6 +3273,16 @@
 	{ MLDS_Statement = mlds__statement(MLDS_Stmt,
 			mlds__make_context(Context)) }.
 
+:- pred ml_gen_info_use_gcc_nested_functions(bool, ml_gen_info, ml_gen_info).
+:- mode ml_gen_info_use_gcc_nested_functions(out, in, out) is det.
+
+ml_gen_info_use_gcc_nested_functions(UseNestedFuncs) -->
+	=(Info),
+	{ ml_gen_info_get_module_info(Info, ModuleInfo) },
+	{ module_info_globals(ModuleInfo, Globals) },
+	{ globals__lookup_bool_option(Globals, gcc_nested_functions,
+		UseNestedFuncs) }.
+
 %-----------------------------------------------------------------------------%
 %
 % Code for generating mlds__entity_names.
@@ -3319,7 +3404,19 @@
 		ContType = mlds__cont_type,
 		ContName = data(var("cont")),
 		ContArg = ContName - ContType,
-		FuncArgs = list__append(FuncArgs0, [ContArg])
+		ContEnvType = mlds__generic_env_ptr_type,
+		ContEnvName = data(var("cont_env_ptr")),
+		ContEnvArg = ContEnvName - ContEnvType,
+		(
+			module_info_globals(ModuleInfo, Globals),
+			globals__lookup_bool_option(Globals,
+				gcc_nested_functions, yes)
+		->
+			FuncArgs = list__append(FuncArgs0, [ContArg])
+		;
+			FuncArgs = list__append(FuncArgs0,
+				[ContArg, ContEnvArg])
+		)
 	;
 		FuncArgs = FuncArgs0
 	),
@@ -3594,7 +3691,14 @@
 		ml_gen_info(A, B, C, D, E, F, G, CommitLabel, I)) :-
 	CommitLabel is CommitLabel0 + 1.
 
-:- type success_cont == mlds__rval.
+:- type success_cont 
+	--->	success_cont(
+			mlds__rval,	% function pointer
+			mlds__rval	% environment pointer
+				% note that if we're using nested
+				% functions then the environment
+				% pointer will not be used
+		).
 
 /******
 :- pred ml_gen_info_get_success_cont_stack(ml_gen_info,
cvs diff: compiler/ml_elim_nested.m is a new entry, no comparison available
Index: compiler/mlds.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mlds.m,v
retrieving revision 1.10
diff -u -d -r1.10 mlds.m
--- compiler/mlds.m	1999/11/05 21:18:54	1.10
+++ compiler/mlds.m	1999/11/08 20:32:34
@@ -341,7 +341,7 @@
 	==	mlds__fully_qualified_name(mlds__entity_name).
 
 :- type mlds__entity_name
-	--->	type(string, arity)		% Name, arity.
+	--->	type(mlds__class_name, arity)	% Name, arity.
 	;	data(mlds__data_name)
 	;	function(
 			mlds__pred_label,	% Identifies the source code
@@ -392,7 +392,7 @@
 		)
 		% packages, classes, interfaces, structs, enums
 	;	mlds__class(
-			mlds__class
+			mlds__class_defn
 		).
 
 :- type mlds__initializer == list(mlds__rval).
@@ -434,8 +434,12 @@
 					% (cannot inherit anything).
 	.
 
-:- type mlds__class
-	---> mlds__class(
+
+:- type mlds__class_name == string.
+:- type mlds__class == mlds__fully_qualified_name(mlds__class_name).
+
+:- type mlds__class_defn
+	---> mlds__class_defn(
 		mlds__class_kind,
 		mlds__imports,			% imports these classes (or
 						% modules, packages, ...)
@@ -468,9 +472,20 @@
 	;	mlds__float_type
 	;	mlds__char_type
 
+		% MLDS types defined using mlds__class_defn
+	;	mlds__class_type(mlds__class, arity)	% name, arity
+
 		% Pointer types.
 		% Currently these are used for handling output arguments.
-	;	mlds__ptr_type(mlds__type).
+	;	mlds__ptr_type(mlds__type)
+
+		% A generic pointer type (e.g. `void *' in C)
+		% that can be used to point to the environment
+		% (set of local variables) of the containing function.
+		% This is used for handling nondeterminism
+		% if the target language doesn't supported
+		% nested functions.
+	;	mlds__generic_env_ptr_type.
 
 :- type mercury_type == prog_data__type.
 
@@ -662,8 +677,8 @@
 		% in goals called from the GoalToTry goal in the
 		% try_commit instruction with the same Ref.
 		%	
-	;	try_commit(mlds__var, mlds__statement, mlds__statement)
-	;	do_commit(mlds__var)
+	;	try_commit(mlds__lval, mlds__statement, mlds__statement)
+	;	do_commit(mlds__rval)
 
 	%
 	% exception handling
Index: compiler/mlds_to_c.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mlds_to_c.m,v
retrieving revision 1.9
diff -u -d -r1.9 mlds_to_c.m
--- compiler/mlds_to_c.m	1999/11/06 05:03:50	1.9
+++ compiler/mlds_to_c.m	1999/11/08 20:36:01
@@ -266,6 +266,11 @@
 
 mlds_output_defn(Indent, ModuleName, Defn) -->
 	{ Defn = mlds__defn(Name, Context, Flags, DefnBody) },
+	( { DefnBody \= mlds__data(_, _) } ->
+		io__nl
+	;
+		[]
+	),
 	mlds_output_context(Context),
 	mlds_indent(Indent),
 	mlds_output_decl_flags(Flags),
@@ -325,19 +330,27 @@
 % Code to output type declarations/definitions
 %
 
-:- pred mlds_output_class(int, mlds__qualified_entity_name, mlds__class,
-		io__state, io__state).
-:- mode mlds_output_class(in, in, in, di, uo) is erroneous.
+:- pred mlds_output_class_decl(int, mlds__qualified_entity_name,
+		mlds__class_defn, io__state, io__state).
+:- mode mlds_output_class_decl(in, in, in, di, uo) is det.
 
-mlds_output_class(_Indent, _Name, _ClassDefn) -->
-	{ error("NYI 3") }.
+mlds_output_class_decl(_Indent, Name, _ClassDefn) -->
+	io__write_string("struct "),
+	mlds_output_fully_qualified_name(Name, mlds_output_name).
 
-:- pred mlds_output_class_decl(int, mlds__qualified_entity_name, mlds__class,
+:- pred mlds_output_class(int, mlds__qualified_entity_name, mlds__class_defn,
 		io__state, io__state).
-:- mode mlds_output_class_decl(in, in, in, di, uo) is erroneous.
+:- mode mlds_output_class(in, in, in, di, uo) is det.
 
-mlds_output_class_decl(_Indent, _Name, _ClassDefn) -->
-	{ error("NYI 3b") }.
+mlds_output_class(Indent, Name, ClassDefn) -->
+	mlds_output_class_decl(Indent, Name, ClassDefn),
+	io__write_string(" {\n"),
+	{ ClassDefn = class_defn(_Kind, _Imports, _BaseClasses, _Implements,
+		Defns) },
+	{ Name = qual(ModuleName, _) },
+	mlds_output_defns(Indent + 1, ModuleName, Defns),
+	mlds_indent(Indent),
+	io__write_string("}").
 
 %-----------------------------------------------------------------------------%
 %
@@ -588,14 +601,26 @@
 		% so that distinct Mercury types map to distinct C types
 		io__write_string("Word")
 	).
-mlds_output_type(mlds__cont_type)  --> io__write_string("Cont").
 mlds_output_type(mlds__int_type)   --> io__write_string("int").
 mlds_output_type(mlds__float_type) --> io__write_string("float").
 mlds_output_type(mlds__bool_type)  --> io__write_string("bool").
 mlds_output_type(mlds__char_type)  --> io__write_string("char").
+mlds_output_type(mlds__class_type(Name, Arity)) -->
+	io__write_string("struct "),
+	mlds_output_fully_qualified_name(Name, io__write_string),
+	io__format("_%d", [i(Arity)]).
 mlds_output_type(mlds__ptr_type(Type)) -->
 	mlds_output_type(Type),
 	io__write_string(" *").
+mlds_output_type(mlds__generic_env_ptr_type) -->
+	io__write_string("void *").
+mlds_output_type(mlds__cont_type) -->
+	globals__io_lookup_bool_option(gcc_nested_functions, GCC_NestedFuncs),
+	( { GCC_NestedFuncs = yes } ->
+		io__write_string("MR_NestedCont")
+	;
+		io__write_string("MR_Cont")
+	).
 mlds_output_type(mlds__commit_type) -->
 	globals__io_lookup_bool_option(gcc_local_labels, GCC_LocalLabels),
 	( { GCC_LocalLabels = yes } ->
@@ -839,11 +864,11 @@
 	( { GCC_LocalLabels = yes } ->
 		% output "goto <Ref>"
 		io__write_string("goto "),
-		mlds_output_var(Ref)
+		mlds_output_rval(Ref)
 	;
 		% output "longjmp(<Ref>, 1)"
 		io__write_string("longjmp("),
-		mlds_output_var(Ref),
+		mlds_output_rval(Ref),
 		io__write_string(", 1)")
 	),
 	io__write_string(";\n").
@@ -861,21 +886,25 @@
 		%       <Ref>_done:
 		%               ;
 
+		% Note that <Ref> should be just variable name,
+		% not a complicated expression.  If not, the
+		% C compiler will catch it.
+
 		mlds_output_statement(Indent, FuncName, Stmt0),
 
 		mlds_indent(Indent),
 		io__write_string("goto "),
-		mlds_output_var(Ref),
+		mlds_output_lval(Ref),
 		io__write_string("_done;\n"),
 
 		mlds_indent(Indent - 1),
-		mlds_output_var(Ref),
+		mlds_output_lval(Ref),
 		io__write_string(":\n"),
 
 		mlds_output_statement(Indent, FuncName, Handler),
 
 		mlds_indent(Indent - 1),
-		mlds_output_var(Ref),
+		mlds_output_lval(Ref),
 		io__write_string("_done:\t;\n")
 
 	;
@@ -907,7 +936,7 @@
 
 		mlds_indent(Indent),
 		io__write_string("if (setjmp("),
-		mlds_output_var(Ref),
+		mlds_output_lval(Ref),
 		io__write_string(") == 0)\n"),
 
 		mlds_output_statement(Indent + 1, FuncName, Stmt),
@@ -1078,9 +1107,15 @@
 	io__write_string(", "),
 	mlds_output_rval(OffsetRval),
 	io__write_string(")").
-mlds_output_lval(field(MaybeTag, Rval, named_field(FieldId))) -->
+mlds_output_lval(field(MaybeTag, PtrRval, named_field(FieldId))) -->
 	( { MaybeTag = yes(0) } ->
-		mlds_output_rval(Rval)
+		( { PtrRval = mem_addr(Lval) } ->
+			mlds_output_bracketed_lval(Lval),
+			io__write_string(".")
+		;
+			mlds_output_bracketed_rval(PtrRval),
+			io__write_string("->")
+		)
 	;
 		( { MaybeTag = yes(Tag) } ->
 			io__write_string("MR_body("),
@@ -1089,10 +1124,10 @@
 		;
 			io__write_string("MR_strip_tag(")
 		),
-		mlds_output_rval(Rval),
-		io__write_string(")")
+		mlds_output_rval(PtrRval),
+		io__write_string(")"),
+		io__write_string("->")
 	),
-	io__write_string("->"),
 	mlds_output_fully_qualified_name(FieldId, io__write_string).
 mlds_output_lval(mem_ref(Rval)) -->
 	io__write_string("*"),
@@ -1105,6 +1140,21 @@
 
 mlds_output_var(VarName) -->
 	mlds_output_fully_qualified_name(VarName, io__write_string).
+
+:- pred mlds_output_bracketed_lval(mlds__lval, io__state, io__state).
+:- mode mlds_output_bracketed_lval(in, di, uo) is det.
+
+mlds_output_bracketed_lval(Lval) -->
+	(
+		% if it's just a variable name, then we don't need parentheses
+		{ Lval = var(_) }
+	->
+		mlds_output_lval(Lval)
+	;
+		io__write_char('('),
+		mlds_output_lval(Lval),
+		io__write_char(')')
+	).
 
 :- pred mlds_output_bracketed_rval(mlds__rval, io__state, io__state).
 :- mode mlds_output_bracketed_rval(in, di, uo) is det.
Index: compiler/notes/compiler_design.html
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/notes/compiler_design.html,v
retrieving revision 1.40
diff -u -d -r1.40 compiler_design.html
--- compiler/notes/compiler_design.html	1999/10/25 03:53:07	1.40
+++ compiler/notes/compiler_design.html	1999/11/06 12:31:00
@@ -878,8 +878,9 @@
 </ul>
 
 <h4> 5b. MLDS transformations </h4>
-None yet.  Eventually there will be one or more modules here for
-performing transformations such as hoisting out nested functions.
+<ul>
+<li> ml_elim_nested.m transforms the MLDS to eliminate nested functions.
+</ul>
 
 <h4> 6b. MLDS output </h4>
 mlds_to_c.m converts MLDS to C/C++ code.
Index: runtime/mercury_types.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_types.h,v
retrieving revision 1.18
diff -u -d -r1.18 mercury_types.h
--- runtime/mercury_types.h	1999/08/24 01:35:47	1.18
+++ runtime/mercury_types.h	1999/11/06 12:47:40
@@ -92,7 +92,8 @@
 typedef const Char *ConstString;
 
 /* continuation function type, for --high-level-C option */
-typedef void (*Cont) (void);
+typedef void (*MR_NestedCont) (void);	/* for --gcc-nested-functions */
+typedef void (*MR_Cont) (void *);	/* for --no-gcc-nested-functions */
 
 /*
 ** semidet predicates indicate success or failure by leaving nonzero or zero

-- 
Fergus Henderson <fjh at cs.mu.oz.au>  |  "I have always known that the pursuit
WWW: <http://www.cs.mu.oz.au/~fjh>  |  of excellence is a lethal habit"
PGP: finger fjh at 128.250.37.3        |     -- the last words of T. S. Garp.
--------------------------------------------------------------------------
mercury-developers mailing list
Post messages to:       mercury-developers at cs.mu.oz.au
Administrative Queries: owner-mercury-developers at cs.mu.oz.au
Subscriptions:          mercury-developers-request at cs.mu.oz.au
--------------------------------------------------------------------------



More information about the developers mailing list