[m-rev.] for review: submodules in the same assembly

Peter Ross peter.ross at miscrit.be
Thu Aug 9 22:43:22 AEST 2001


Hi,


===================================================================


Estimated hours taken: 8
Branches: main

Place sub-modules in the same assembly as their parent on the IL
backend.

This allowes the user to decide how their application should be
packaged.  If the user wishes their application to be deployed as one
assembly then they should use sub modules.

This also simplifies management, as it allows such things as strong keys
(which apply to one assembly) to be used more easily.

compiler/ilasm.m:
    Add the '.file' and '.module extern' declarations.
    Modify output_structured_name so that it outputs
    [.module <sub-module>.dll] or [<assembly>] as the assembly reference
    as necessary.

compiler/ilds.m:
    Change the assembly_name type so that it records both the assembly
    and sub-module name for sub-modules.

compiler/mlds_to_il.m:
    Use the new assembly_name type when generating assembly_names.
    Factor out some duplicate code in class_name.
    Modify generate_extern_assembly so that it outputs `.file' and
    `.module extern' declarations in the top level module of nested
    modules.

compiler/modules.m:
    Add the dependency that the top level dll of a nested module
    hierachy depends on all of it sub-modules dlls, as they are
    referenced from inside the top level dll.

    Change the top level make rule from
        <main> : <main>.exe $(<main>.dlls)
    to
        <main> : <main>.exe
        <main>.exe : $(<main>.dlls)
    so that all the dlls are built before building the exe, as the exe
    may contain references to sub-module dlls.
    
compiler/prog_util.m:
    Add the utility predicate outermost_qualifier which retrieves the
    top level qualifier from a sym_name.

Index: compiler/ilasm.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/ilasm.m,v
retrieving revision 1.17
diff -u -r1.17 ilasm.m
--- compiler/ilasm.m	31 Jul 2001 21:49:24 -0000	1.17
+++ compiler/ilasm.m	9 Aug 2001 12:11:08 -0000
@@ -70,6 +70,13 @@
 			data_body 	 % body of data
 		) 
 
+		% .file
+		% Declares a file associated with the current assembly
+	;	file(ilds__id)
+
+		% .module extern
+		% declares a module name.
+	;	extern_module(ilds__id)
 
 		% .assembly extern
 		% declares an assembly name, and possibly its strong
@@ -263,7 +270,7 @@
 
 :- type ilasm_info ---> 
 		ilasm_info(
-			current_assembly :: assembly_name
+			current_assembly :: ilds__id
 		).
 
 :- pred ilasm__write_list(list(T), string, 
@@ -423,6 +430,14 @@
 			Info0, Info)
 	).
 
+ilasm__output_decl(file(FileName), Info, Info) --> 
+	io__write_string(".file "),
+	output_id(FileName).
+
+ilasm__output_decl(extern_module(ModName), Info, Info) --> 
+	io__write_string(".module extern "),
+	output_id(ModName).
+
 ilasm__output_classdecl(
 		field(FieldAttrs, Type, IlId, MaybeOffset, Initializer),
 		Info0, Info) -->
@@ -1415,14 +1430,32 @@
 
 :- pred output_structured_name(structured_name::in, ilasm_info::in,
 	ilasm_info::out, io__state::di, io__state::uo) is det.
-output_structured_name(structured_name(Assembly, DottedName), Info, Info) -->
+output_structured_name(structured_name(Asm, DottedName), Info, Info) -->
+	( { Asm = assembly(Assembly) },
+		maybe_output_quoted_assembly_name(Assembly, Info)
+	; { Asm = module(Module, Assembly) },
+		(
+			{ Info ^ current_assembly \= "" },
+			{ string__prefix(Module, Info ^ current_assembly) }
+		->
+			{ quote_id(Module ++ ".dll", QuotedModuleName) },
+			io__format("[.module %s]", [s(QuotedModuleName)])
+		;
+			maybe_output_quoted_assembly_name(Assembly, Info)
+		)
+	),
+	output_dotted_name(DottedName).
+
+:- pred maybe_output_quoted_assembly_name(ilds__id::in, ilasm_info::in,
+		io__state::di, io__state::uo) is det.
+
+maybe_output_quoted_assembly_name(Assembly, Info) -->
 	( { Assembly \= "", Assembly \= Info ^ current_assembly } ->
 		{ quote_id(Assembly, QuotedAssemblyName) },
 		io__format("[%s]", [s(QuotedAssemblyName)])
 	;
 		[]
-	),
-	output_dotted_name(DottedName).
+	).
 
 :- pred output_dotted_name(namespace_qual_name::in,
 	io__state::di, io__state::uo) is det.
Index: compiler/ilds.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/ilds.m,v
retrieving revision 1.8
diff -u -r1.8 ilds.m
--- compiler/ilds.m	18 Jul 2001 10:20:51 -0000	1.8
+++ compiler/ilds.m	9 Aug 2001 12:11:08 -0000
@@ -63,7 +63,19 @@
 :- type structured_name ---> 
 		structured_name(assembly_name, namespace_qual_name).
 
-:- type assembly_name == ilds__id. 
+	% If we are referencing a sub-module, then we need to record two
+	% names.  One is the sub-module name, which is used for
+	% references from the parent module, and the other is the
+	% assembly name for when the name is referenced from anywhere
+	% else.
+:- type assembly_name
+	--->	module(
+			il_module_name		:: ilds__id,
+			containing_asm_name	:: ilds__id
+
+		)
+	;	assembly(ilds__id).
+
 :- type namespace_qual_name == list(ilds__id). 
 
 	
Index: compiler/mlds_to_il.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mlds_to_il.m,v
retrieving revision 1.62
diff -u -r1.62 mlds_to_il.m
--- compiler/mlds_to_il.m	8 Aug 2001 14:22:56 -0000	1.62
+++ compiler/mlds_to_il.m	9 Aug 2001 12:11:11 -0000
@@ -141,7 +141,7 @@
 
 :- import_module globals, options, passes_aux.
 :- import_module builtin_ops, c_util, modules, tree.
-:- import_module prog_data, prog_out, llds_out.
+:- import_module prog_data, prog_out, prog_util, llds_out.
 :- import_module rtti, type_util, code_model, foreign.
 
 :- import_module ilasm, il_peephole.
@@ -160,7 +160,7 @@
 :- type il_info ---> il_info(
 		% file-wide attributes (all static)
 	module_name 	:: mlds_module_name,	% the module name
-	assembly_name 	:: assembly_name,	% the assembly name
+	assembly_name 	:: ilds__id,		% the assembly name
 	imports 	:: mlds__imports,	% the imports
 	file_foreign_langs :: set(foreign_language), % file foreign code
 	il_data_rep	:: il_data_rep,		% data representation.
@@ -222,14 +222,25 @@
 		% library.  Standard library modules all go in the one
 		% assembly in a separate step during the build (using
 		% AL.EXE).  
+	PackageName = mlds_module_name_to_package_name(ModuleName),
 	(
-		PackageName = mlds_module_name_to_package_name(ModuleName),
 		PackageName = qualified(unqualified("mercury"), _)
 	->
 		ThisAssembly = [],
 		AssemblerRefs = Imports
 	;
-		ThisAssembly = [assembly(AssemblyName)],
+			% If the package name is qualified then the
+			% we have a sub-module which shouldn't be placed
+			% in it's own module.
+		( PackageName = unqualified(_) ->
+			ThisAssembly = [assembly(AssemblyName)]
+		;
+			ThisAssembly = []
+		),
+
+			% XXX at a later date we should make foreign
+			% code behave like a submodule.
+			%
 			% If not in the library, but we have foreign code,
 			% declare the foreign module as an assembly we
 			% reference
@@ -238,7 +249,7 @@
 			ForeignCodeAssemblerRefs),
 		AssemblerRefs = list__append(ForeignCodeAssemblerRefs, Imports)
 	),
-	generate_extern_assembly(AssemblerRefs, ExternAssemblies),
+	generate_extern_assembly(AssemblyName, AssemblerRefs, ExternAssemblies),
 	Namespace = [namespace(NamespaceName, ILDecls)],
 	ILAsm = list__condense([ThisAssembly, ExternAssemblies, Namespace]).
 
@@ -509,7 +520,7 @@
 		% when that assembly is created by al.exe.
 		% This occurs for nondet environment classes in the
 		% mercury std library.
-	( ClassName = structured_name("mercury", _) ->
+	( ClassName = structured_name(assembly("mercury"), _) ->
 		Flags = set_access(Flags0, public)
 	;
 		Flags = Flags0
@@ -565,18 +576,8 @@
 		)
 	).
 
-class_name(Module, Name) = structured_name(Assembly, ClassName ++ [Name]) :-
-	ClassName = sym_name_to_list(mlds_module_name_to_sym_name(Module)),
-		% Any name beginning with mercury is in the standard
-		% library.  The standard library is placed into one
-		% assembly called mercury.
-	( ClassName = ["mercury" | _] ->
-		Assembly = "mercury"
-	;
-		prog_out__sym_name_to_string(
-				mlds_module_name_to_package_name(Module),
-				".", Assembly)
-	).
+class_name(Module, Name)
+	= append_class_name(mlds_module_name_to_class_name(Module), [Name]).
 
 :- func sym_name_to_list(sym_name) = list(string).
 
@@ -732,7 +733,7 @@
 	( semidet_succeed ->
 		sorry(this_file, "interface_id_to_class_name NYI")
 	;
-		Result = structured_name("XXX", [])
+		Result = structured_name(assembly("XXX"), [])
 		
 	).
 
@@ -959,11 +960,11 @@
 		)},
 		{ RenameNode = (func(N) = list__map(RenameRets, N)) },
 
-		{ ExceptionClassName = structured_name("mscorlib",
+		{ ExceptionClassName = structured_name(assembly("mscorlib"),
 				["System", "Exception"]) },
 
 		{ ConsoleWriteName = class_member_name(structured_name(
-				"mscorlib", ["System", "Console"]),
+				assembly("mscorlib"), ["System", "Console"]),
 				id("Write")) },
 		{ WriteString = methoddef(call_conv(no, default),
 					void, ConsoleWriteName,
@@ -2985,15 +2986,29 @@
 mlds_module_name_to_class_name(MldsModuleName) = 
 		structured_name(AssemblyName, ClassName) :-
 	SymName = mlds_module_name_to_sym_name(MldsModuleName),
+	sym_name_to_class_name(SymName, ClassName),
+	AssemblyName = mlds_module_name_to_assembly_name(MldsModuleName).
+
+:- func mlds_module_name_to_assembly_name(mlds_module_name) = assembly_name.
+
+mlds_module_name_to_assembly_name(MldsModuleName) = AssemblyName :-
+	SymName = mlds_module_name_to_sym_name(MldsModuleName),
 	PackageSymName = mlds_module_name_to_package_name(MldsModuleName),
 	sym_name_to_class_name(SymName, ClassName),
 	( 
 		ClassName = ["mercury" | _]
 	->
-		AssemblyName = "mercury"
+		AssemblyName = assembly("mercury")
 	;
-		mlds_to_il__sym_name_to_string(PackageSymName, AssemblyName)
+		mlds_to_il__sym_name_to_string(PackageSymName, PackageString),
+		( PackageSymName = unqualified(_),
+			AssemblyName = assembly(PackageString)
+		; PackageSymName = qualified(_, _),
+			AssemblyName = module(PackageString,
+					outermost_qualifier(PackageSymName))
+		)
 	).
+	
 
 :- pred sym_name_to_class_name(sym_name, list(ilds__id)).
 :- mode sym_name_to_class_name(in, out) is det.
@@ -3416,7 +3431,8 @@
 	append_class_name(mercury_library_namespace_name, Name).
 
 :- func mercury_library_namespace_name = ilds__class_name.
-mercury_library_namespace_name = structured_name("mercury", ["mercury"]).
+mercury_library_namespace_name
+	= structured_name(assembly("mercury"), ["mercury"]).
 
 %-----------------------------------------------------------------------------
 
@@ -3426,8 +3442,8 @@
 	append_class_name(mercury_runtime_class_name, Name).
 
 :- func mercury_runtime_class_name = ilds__class_name.
-mercury_runtime_class_name = structured_name("mercury",
-	["mercury", "runtime"]).
+mercury_runtime_class_name
+	= structured_name(assembly("mercury"), ["mercury", "runtime"]).
 
 %-----------------------------------------------------------------------------
 
@@ -3436,8 +3452,8 @@
 il_system_name(Name) = structured_name(il_system_assembly_name, 
 		[il_system_namespace_name | Name]).
 
-:- func il_system_assembly_name = string.
-il_system_assembly_name = "mscorlib".
+:- func il_system_assembly_name = assembly_name.
+il_system_assembly_name = assembly("mscorlib").
 
 :- func il_system_namespace_name = string.
 il_system_namespace_name = "System".
@@ -3445,18 +3461,28 @@
 %-----------------------------------------------------------------------------
 
 	% Generate extern decls for any assembly we reference.
-:- pred mlds_to_il__generate_extern_assembly(mlds__imports, list(decl)).
-:- mode mlds_to_il__generate_extern_assembly(in, out) is det.
+:- pred mlds_to_il__generate_extern_assembly(string, mlds__imports, list(decl)).
+:- mode mlds_to_il__generate_extern_assembly(in, in, out) is det.
 
-mlds_to_il__generate_extern_assembly(Imports, AllDecls) :-
+mlds_to_il__generate_extern_assembly(CurrentAssembly, Imports, AllDecls) :-
 	Gen = (pred(Import::in, Decl::out) is semidet :-
-		ClassName = mlds_module_name_to_class_name(Import),
-		ClassName = structured_name(Assembly, _),
-		not (Assembly = "mercury"),
-		Decl = extern_assembly(Assembly, [])
+		AsmName = mlds_module_name_to_assembly_name(Import),
+		( AsmName = assembly(Assembly),
+			Assembly \= "mercury",
+			Decl = [extern_assembly(Assembly, [])]
+		; AsmName = module(ModuleName, Assembly),
+			( Assembly = CurrentAssembly ->
+				ModuleStr = ModuleName ++ ".dll",
+				Decl = [file(ModuleStr),
+					extern_module(ModuleStr)]
+			;
+				Assembly \= "mercury",
+				Decl = [extern_assembly(Assembly, [])]
+			)
+		)
 	),
 	list__filter_map(Gen, Imports, Decls0),
-	list__sort_and_remove_dups(Decls0, Decls),
+	list__sort_and_remove_dups(list__condense(Decls0), Decls),
 	AllDecls = [
 		extern_assembly("mercury", [
 			version(0, 0, 0, 0),
@@ -3564,7 +3590,7 @@
 
 :- func runtime_init_module_name = ilds__class_name.
 runtime_init_module_name = 
-	structured_name("mercury",
+	structured_name(assembly("mercury"),
 		["mercury", "private_builtin__cpp_code", wrapper_class_name]).
 
 :- func runtime_init_method_name = ilds__member_name.
@@ -3575,7 +3601,7 @@
 % Predicates for manipulating il_info.
 %
 
-:- func il_info_init(mlds_module_name, assembly_name, mlds__imports,
+:- func il_info_init(mlds_module_name, ilds__id, mlds__imports,
 		il_data_rep, bool, bool, bool) = il_info.
 
 il_info_init(ModuleName, AssemblyName, Imports, ILDataRep,
Index: compiler/modules.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/modules.m,v
retrieving revision 1.189
diff -u -r1.189 modules.m
--- compiler/modules.m	7 Aug 2001 16:44:59 -0000	1.189
+++ compiler/modules.m	9 Aug 2001 12:11:13 -0000
@@ -2051,6 +2051,18 @@
 
 		globals__io_get_target(Target),
 		globals__io_get_globals(Globals),
+
+		{ SubModules = submodules(ModuleName, AllDeps) },
+		( { Target = il, SubModules \= [] } ->
+			module_name_to_file_name(ModuleName, ".dll", no,
+					DllFileName),
+			io__write_strings(DepStream, [DllFileName, " : "]),
+			write_dll_dependencies_list(SubModules, "", DepStream),
+			io__nl(DepStream)
+		;
+			[]
+		),
+		
 		(
 			{ Target = il },
 			{
@@ -3438,8 +3450,8 @@
 	module_name_to_file_name(SourceModuleName, "", no, ExeFileName),
 
 	{ If = ["ifeq ($(findstring il,$(GRADE)),il)\n"] },
-	{ ILMainRule = [ExeFileName, " : ", ExeFileName, ".exe ",
-			"$(", MakeVarName, ".dlls) ",
+	{ ILMainRule = [ExeFileName, " : ", ExeFileName, ".exe\n",
+			ExeFileName, ".exe : ", "$(", MakeVarName, ".dlls) ",
 			"$(", MakeVarName, ".foreign_dlls)\n"] },
 	{ Else = ["else\n"] },
 	{ MainRule =
@@ -4013,6 +4025,19 @@
 			)
 		),
 		Modules = list__remove_dups(list__map(F, Modules0))
+	).
+
+:- func submodules(module_name, list(module_name)) = list(module_name).
+
+submodules(Module, Modules0) = Modules :-
+	( Module = unqualified(Str), \+ mercury_std_library_module(Str) ->
+		P = (pred(M::in) is semidet :-
+			Str = outermost_qualifier(M),
+			M \= Module
+		),
+		list__filter(P, Modules0, Modules)
+	;
+		Modules = []
 	).
 
 :- pred write_dll_dependencies_list(list(module_name),
Index: compiler/prog_util.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/prog_util.m,v
retrieving revision 1.53
diff -u -r1.53 prog_util.m
--- compiler/prog_util.m	27 Jun 2001 05:04:26 -0000	1.53
+++ compiler/prog_util.m	9 Aug 2001 12:11:15 -0000
@@ -129,6 +129,9 @@
 :- pred construct_qualified_term(sym_name, list(term(T)), prog_context, term(T)).
 :- mode construct_qualified_term(in, in, in, out) is det.
 
+	% Given a sym_name return the top level qualifier of that name.
+:- func outermost_qualifier(sym_name) = string.
+
 %-----------------------------------------------------------------------------%
 
 	% adjust_func_arity(PredOrFunc, FuncArity, PredArity).
@@ -237,6 +240,9 @@
 construct_qualified_term(SymName, Args, Term) :-
 	term__context_init(Context),
 	construct_qualified_term(SymName, Args, Context, Term).
+
+outermost_qualifier(unqualified(Name)) = Name.
+outermost_qualifier(qualified(Module, _Name)) = outermost_qualifier(Module).
 
 %-----------------------------------------------------------------------------%
 

--------------------------------------------------------------------------
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