[m-rev.] for review: GCC back-end: support nested modules

Fergus Henderson fjh at cs.mu.OZ.AU
Wed May 9 00:54:03 AEST 2001


Estimated hours taken: 8
Branches: main

Support nested modules in the GCC back-end.
(TO DO: Mmake support for nested modules is still not yet implemented.)

compiler/mlds_to_gcc.m:
compiler/maybe_mlds_to_gcc.pp:
	In mlds_to_gcc.m, split compile_to_asm into two procedures,
	an outer one called run_gcc_backend and an inner one still
	called compile_to_asm.  Likewise for the wrapper in
	maybe_mlds_to_gcc.m.

compiler/mercury_compile.m:
	For --target asm, invoke run_gcc_backend at the top-level of the
	compilation, to avoid problems that occur with the gcc back-end.
	The problem was that the gcc back-end can only be invoked once
	per process, but previously, when processing nested modules
	or multiple modules on the command line, we were invoking it
	multiple times.  With the new approach, we always invoke the gcc
	back-end once, and generate a single assembler file, regardless
	of how many modules are being compiled.

	This required changing the computation of the set of modules
	to link for --target asm.  I also fixed a bug where it wasn't 
	linking in the object files generated for C foreign code
	with --target asm.

Workspace: /mnt/hg/home/hg/fjh/gcc-cvs/gcc/mercury
Index: compiler/maybe_mlds_to_gcc.pp
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/maybe_mlds_to_gcc.pp,v
retrieving revision 1.3
diff -u -d -r1.3 maybe_mlds_to_gcc.pp
--- compiler/maybe_mlds_to_gcc.pp	2001/01/17 06:01:51	1.3
+++ compiler/maybe_mlds_to_gcc.pp	2001/05/08 14:50:54
@@ -20,6 +20,17 @@
 :- import_module mlds, bool.
 :- use_module io.
 
+:- type frontend_callback(T) == pred(T, io__state, io__state).
+:- inst frontend_callback == (pred(out, di, uo) is det).
+
+	% Invoke the callback either via gcc__run_backend, or directly,
+	% depending on whether the gcc back-end interface has
+	% been enabled.
+:- pred maybe_mlds_to_gcc__run_gcc_backend(mercury_module_name,
+		frontend_callback(T), T, io__state, io__state).
+:- mode maybe_mlds_to_gcc__run_gcc_backend(in, in(frontend_callback), out,
+		di, uo) is det.
+
 	% Either invoke mlds_to_gcc__compile_to_asm, or report an error
 	% message, depending on whether the gcc back-end interface has
 	% been enabled.  In the former case,
@@ -36,6 +47,9 @@
 
 :- use_module mlds_to_gcc.
 
+maybe_mlds_to_gcc__run_gcc_backend(ModuleName, CallBack, CallBackOutput) -->
+	mlds_to_gcc__run_gcc_backend(ModuleName, CallBack, CallBackOutput).
+
 maybe_mlds_to_gcc__compile_to_asm(MLDS, ContainsCCode) -->
 	mlds_to_gcc__compile_to_asm(MLDS, ContainsCCode).
 
@@ -43,6 +57,9 @@
 
 :- import_module passes_aux.
 :- import_module string.
+
+maybe_mlds_to_gcc__run_gcc_backend(_ModuleName, CallBack, CallBackOutput) -->
+	CallBack(CallBackOutput).
 
 maybe_mlds_to_gcc__compile_to_asm(_MLDS, no) -->
 	report_error(
Index: compiler/mercury_compile.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mercury_compile.m,v
retrieving revision 1.199
diff -u -d -r1.199 mercury_compile.m
--- compiler/mercury_compile.m	2001/04/24 03:39:36	1.199
+++ compiler/mercury_compile.m	2001/05/08 14:44:08
@@ -128,11 +128,48 @@
 	; { Args = [], FileNamesFromStdin = no } ->
 		usage
 	;
-		( { FileNamesFromStdin = yes } ->
-			process_stdin_arg_list([], ModulesToLink)
+		% Because of limitations in the GCC back-end,
+		% we can only call the GCC back-end once (per process),
+		% to generate a single assembler file, rather than
+		% calling it multiple times to generate individual
+		% assembler files for each module.
+		% So if we're generating code using the GCC back-end,
+		% we need to call run_gcc_backend here at the top level.
+		globals__io_get_globals(Globals),
+		(
+			{ compiling_to_asm(Globals) },
+			{ Args = [FirstArg | _] }
+		->
+			% The name of the assembler file that we generate
+			% is based on the first argument.
+			{ string__remove_suffix(FirstArg, ".m", ArgBase) ->
+				file_name_to_module_name(ArgBase,
+					FirstModuleName)
+			;
+				file_name_to_module_name(FirstArg,
+					FirstModuleName)
+			},
+			% Invoke run_gcc_backend.  It will call us back,
+			% and then we'll continue with the normal work of
+			% the compilation, which will be done by the callback
+			% function (`process_args').
+			maybe_mlds_to_gcc__run_gcc_backend(FirstModuleName,
+				process_args(Args), ModulesToLink),
+			% Invoke the assembler to produce an object file.
+			module_name_to_file_name(FirstModuleName, ".s", no,
+				AsmFile),
+			object_extension(Obj),
+			module_name_to_file_name(FirstModuleName, Obj, yes,
+				O_File),
+			mercury_compile__asm_to_obj(
+				AsmFile, O_File, _AssembleOK)
 		;
-			process_arg_list(Args, ModulesToLink)
+			% If we're NOT using the GCC back-end,
+			% then we can just call process_args directly,
+			% rather than via GCC.
+			process_args(Args, ModulesToLink)
 		),
+
 		io__get_exit_status(ExitStatus),
 		( { ExitStatus = 0 } ->
 			( { Link = yes } ->
@@ -162,13 +199,34 @@
 		)
 	).
 
-:- pred process_arg_list(list(string), list(string), io__state, io__state).
-:- mode process_arg_list(in, out, di, uo) is det.
+:- pred compiling_to_asm(globals::in) is semidet.
+compiling_to_asm(Globals) :-
+	globals__get_target(Globals, asm),
+	% even if --target asm is specified,
+	% it can be overridden by other options:
+	OptionList = [convert_to_mercury, convert_to_goedel,
+		generate_dependencies, make_interface,
+		make_short_interface, make_private_interface,
+		make_optimization_interface,
+		make_transitive_opt_interface,
+		typecheck_only, errorcheck_only],
+	BoolList = map((func(Opt) = Bool :-
+		globals__lookup_bool_option(Globals, Opt, Bool)),
+		OptionList),
+	bool__or_list(BoolList) = no.
 
-process_arg_list(Args, Modules) -->
-	process_arg_list_2(Args, ModulesList),
-	{ list__condense(ModulesList, Modules) }.
+:- pred process_args(list(string), list(string), io__state, io__state).
+:- mode process_args(in, out, di, uo) is det.
 
+process_args(Args, ModulesToLink) -->
+	globals__io_lookup_bool_option(filenames_from_stdin,
+		FileNamesFromStdin),
+	( { FileNamesFromStdin = yes } ->
+		process_stdin_arg_list([], ModulesToLink)
+	;
+		process_arg_list(Args, ModulesToLink)
+	).
+
 :- pred process_stdin_arg_list(list(string), list(string), 
 		io__state, io__state).
 :- mode process_stdin_arg_list(in, out, di, uo) is det.
@@ -198,6 +256,13 @@
 		io__set_exit_status(1)
 	).
 
+:- pred process_arg_list(list(string), list(string), io__state, io__state).
+:- mode process_arg_list(in, out, di, uo) is det.
+
+process_arg_list(Args, Modules) -->
+	process_arg_list_2(Args, ModulesList),
+	{ list__condense(ModulesList, Modules) }.
+
 :- pred process_arg_list_2(list(string), list(list(string)),
 			io__state, io__state).
 :- mode process_arg_list_2(in, out, di, uo) is det.
@@ -334,27 +399,36 @@
 			globals__io_set_option(trace_stack_layout, bool(no)),
 			globals__io_set_trace_level_none,
 
-			% XXX it would be better to do something like
-			%
-			%	list__map_foldl(compile_to_llds, SubModuleList,
-			%		LLDS_FragmentList),
-			%	merge_llds_fragments(LLDS_FragmentList, LLDS),
-			%	output_pass(LLDS_FragmentList)
-			%
-			% i.e. compile nested modules to a single C file.
-			list__foldl(compile(FileName), SubModuleList),
-			list__map_foldl(module_to_link, SubModuleList,
+			compile_all_submodules(FileName, SubModuleList,
 				ModulesToLink),
 
 			globals__io_set_option(trace_stack_layout, bool(TSL)),
 			globals__io_set_trace_level(TraceLevel)
 		;
-			list__foldl(compile(FileName), SubModuleList),
-			list__map_foldl(module_to_link, SubModuleList,
+			compile_all_submodules(FileName, SubModuleList,
 				ModulesToLink)
 		)
 	).
 
+	% For the MLDS->C and LLDS->C back-ends, we currently
+	% compile each sub-module to its own C file.
+	% XXX it would be better to do something like
+	%
+	%	list__map2_foldl(compile_to_llds, SubModuleList,
+	%		LLDS_FragmentList),
+	%	merge_llds_fragments(LLDS_FragmentList, LLDS),
+	%	output_pass(LLDS_FragmentList)
+	%
+	% i.e. compile nested modules to a single C file.
+
+:- pred compile_all_submodules(string, list(pair(module_name, item_list)),
+		list(string), io__state, io__state).
+:- mode compile_all_submodules(in, in, out, di, uo) is det.
+
+compile_all_submodules(FileName, SubModuleList, ModulesToLink) -->
+	list__foldl(compile(FileName), SubModuleList),
+	list__map_foldl(module_to_link, SubModuleList, ModulesToLink).
+
 :- pred make_interface(file_name, pair(module_name, item_list),
 			io__state, io__state).
 :- mode make_interface(in, in, di, uo) is det.
@@ -398,8 +472,7 @@
 	% The initial arrangement has the stage numbers increasing by three
 	% so that new stages can be slotted in without too much trouble.
 
-:- pred compile(file_name, pair(module_name, item_list),
-		io__state, io__state).
+:- pred compile(file_name, pair(module_name, item_list), io__state, io__state).
 :- mode compile(in, in, di, uo) is det.
 
 compile(SourceFileName, ModuleName - Items) -->
@@ -455,7 +528,7 @@
 		mercury_compile__maybe_magic(HLDS23, Verbose, Stats, _)
 	    ; { MakeOptInt = yes } ->
 		% only run up to typechecking when making the .opt file
-	    	[]
+		[]
 	    ; { MakeTransOptInt = yes } ->
 	    	mercury_compile__output_trans_opt_file(HLDS21)
 	    ;
@@ -474,7 +547,7 @@
 		    mercury_compile__maybe_generate_rl_bytecode(HLDS50,
 				Verbose, MaybeRLFile),
 		    ( { AditiOnly = yes } ->
-		    	[]
+			[]
 		    ; { Target = il } ->
 			mercury_compile__mlds_backend(HLDS50, MLDS),
 			( { TargetCodeOnly = yes } ->
@@ -502,17 +575,11 @@
 			( { TargetCodeOnly = yes } ->
 				[]
 			;
-				% Invoke the assembler to produce an
-				% object file
-				module_name_to_file_name(ModuleName, ".s", no,
-					AsmFile),
-				object_extension(Obj),
-				module_name_to_file_name(ModuleName, Obj, yes,
-					O_File),
-				mercury_compile__asm_to_obj(
-					AsmFile, O_File, _AssembleOK),
+				% We don't invoke the assembler to produce an
+				% object file yet -- that is done at
+				% the top level.
 				%
-				% If the module contained `pragma c_code',
+				% But if the module contained `pragma c_code',
 				% then we will have compiled that to a
 				% separate C file.  We need to invoke the
 				% C compiler on that.
@@ -520,12 +587,20 @@
 				( { ContainsCCode = yes } ->
 					module_name_to_file_name(ModuleName,
 						".c", no, CCode_C_File),
+					object_extension(Obj),
 					module_name_to_file_name(ModuleName,
 						"__c_code" ++ Obj,
 						yes, CCode_O_File),
 					mercury_compile__single_c_to_obj(
 						CCode_C_File, CCode_O_File,
-						_CompileOK)
+						_CompileOK),
+					% add this object file to the list
+					% of extra object files to link in
+					globals__io_lookup_accumulating_option(
+						link_objects, LinkObjects),
+					globals__io_set_option(link_objects,
+						accumulating([CCode_O_File |
+						LinkObjects]))
 				;
 					[]
 				)
@@ -3073,8 +3148,18 @@
 	module_name_to_file_name(ModuleName, "_init.c", yes, InitCFileName),
 	module_name_to_file_name(ModuleName, InitObj, yes, InitObjFileName),
 
+	globals__io_get_target(Target),
 	globals__io_lookup_bool_option(split_c_files, SplitFiles),
-	( { SplitFiles = yes } ->
+	( { Target = asm } ->
+	    % for --target asm, we generate everything into a single object file
+	    ( { Modules = [FirstModule | _] } ->
+		join_module_list([FirstModule], Obj, [], ObjectsList),
+		{ string__append_list(ObjectsList, Objects) }
+	    ;
+		{ error("link_module_list: no modules") }
+	    ),
+	    { MakeLibCmdOK = yes }
+	; { SplitFiles = yes } ->
 	    module_name_to_file_name(ModuleName, ".a", yes, SplitLibFileName),
 	    { string__append(".dir/*", Obj, DirObj) },
 	    join_module_list(Modules, DirObj, [], ObjectList),
Index: compiler/mlds_to_gcc.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mlds_to_gcc.m,v
retrieving revision 1.38
diff -u -d -r1.38 mlds_to_gcc.m
--- compiler/mlds_to_gcc.m	2001/05/08 05:36:50	1.38
+++ compiler/mlds_to_gcc.m	2001/05/08 12:11:38
@@ -41,14 +41,10 @@
 %	  (there is some documentation in gcc/mercury/README,
 %	  but probably there should also be something in the INSTALL
 %	  file in the Mercury distribution)
-%	- set up nightly tests
 %	- test more
 %
 %	Fix unimplemented standard Mercury features:
-%	- support nested modules
-%	  (They can be compiled using `gcc', but compiling them
-%	  with `mmc' doesn't work, see the XXX comment below.
-%	  Also Mmake support is broken.)
+%	- Mmake support for nested modules
 %	- support modules containing foreign_decls but no
 %	  foreign_procs or foreign code
 %
@@ -95,12 +91,39 @@
 :- module mlds_to_gcc.
 :- interface.
 
-:- import_module mlds, bool.
+:- import_module mlds, maybe_mlds_to_gcc, bool.
 :- use_module io.
 
-	% The bool returned is `yes' iff the module contained C code.
-	% In that case, we will have output a separate C file which needs
-	% to be compiled with the C compiler.
+	% run_gcc_backend(ModuleName, CallBack, CallBackOutput):
+	% 
+	% Set things up to generate an assembler file whose name
+	% is based on the specified module name, and then call the
+	% CallBack procedure.  When the CallBack procedure exits
+	% (returning CallBackOutput), finish generating the assembler
+	% file, and then return the CallBackOutput back to the caller.
+	% 
+	% Due to limitations in the GCC back-end, this procedure
+	% must not be called more than once per process.
+
+:- pred mlds_to_gcc__run_gcc_backend(mercury_module_name,
+		frontend_callback(T), T, io__state, io__state).
+:- mode mlds_to_gcc__run_gcc_backend(in, in(frontend_callback), out,
+		di, uo) is det.
+
+	% compile_to_gcc(MLDS, ContainsCCode):
+	%
+	% Generate GCC trees and/or RTL for the given MLDS,
+	% and invoke the GCC back-end to output assembler for
+	% them to the assembler file.
+	%
+	% This procedure must only be called from within a callback
+	% function passed to run_gcc_backend.  Otherwise it may
+	% try to use the GCC back-end before it has been properly
+	% initialized.
+	%
+	% The ContainsCCode bool returned is `yes' iff the module contained
+	% C code. In that case, we will have output a separate C file which
+	% needs to be compiled with the C compiler.
 	%
 	% XXX Currently the only foreign language we handle is C.
 	%     To make it work properly we'd need to change the
@@ -141,8 +164,7 @@
 
 %-----------------------------------------------------------------------------%
 
-mlds_to_gcc__compile_to_asm(MLDS, ContainsCCode) -->
-	{ MLDS = mlds(ModuleName, _, _, _) },
+mlds_to_gcc__run_gcc_backend(ModuleName, CallBack, CallBackOutput) -->
 	globals__io_lookup_bool_option(pic, Pic),
 	{ Pic = yes ->
 		PicExt = ".pic_s",
@@ -185,18 +207,14 @@
 	maybe_write_string(Verbose, "% Invoking GCC back-end as `"),
 	maybe_write_string(Verbose, CommandLine),
 	maybe_write_string(Verbose, "':\n"),
-	gcc__run_backend(CommandLine, Result,
-		mlds_to_gcc__compile_to_gcc(MLDS), ContainsCCode),
+	gcc__run_backend(CommandLine, Result, CallBack, CallBackOutput),
 	( { Result \= 0 } ->
 		report_error("GCC back-end failed!\n")
 	;
 		maybe_write_string(Verbose, "% GCC back-end done.\n")
 	).
-
-:- pred mlds_to_gcc__compile_to_gcc(mlds__mlds, bool, io__state, io__state).
-:- mode mlds_to_gcc__compile_to_gcc(in, out, di, uo) is det.
 
-mlds_to_gcc__compile_to_gcc(MLDS, ContainsCCode) -->
+mlds_to_gcc__compile_to_asm(MLDS, ContainsCCode) -->
 	{ MLDS = mlds(ModuleName, ForeignCode, Imports, Defns0) },
 
 	%

-- 
Fergus Henderson <fjh at cs.mu.oz.au>  |  "I have always known that the pursuit
                                    |  of excellence is a lethal habit"
WWW: <http://www.cs.mu.oz.au/~fjh>  |     -- the last words of T. S. Garp.
--------------------------------------------------------------------------
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