[m-rev.] for review: various mlds_to_il fixes

Peter Ross peter.ross at miscrit.be
Fri Jul 13 19:46:32 AEST 2001


Hi,

For Tyson or Fergus to review.

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


Estimated hours taken: 4
Branches: main

compiler/mlds_to_il.m:
    Check to see if a field is a field of the current class before
    assuming that it is handwritten.
    Implement renaming of classes and rename every mlds__defn.
    Set fields with local access to .NET private.
    When generating the initializer for arrays use the type information
    to generate arrays of the correct type.  We still treat structs like
    they are an array of System.Object.

Index: mlds_to_il.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mlds_to_il.m,v
retrieving revision 1.44
diff -u -r1.44 mlds_to_il.m
--- mlds_to_il.m	11 Jul 2001 13:10:18 -0000	1.44
+++ mlds_to_il.m	13 Jul 2001 09:44:11 -0000
@@ -165,6 +165,7 @@
 	classdecls	:: list(classdecl),	% class methods and fields 
 	has_main	:: bool,		% class contains main
 	class_foreign_langs :: set(foreign_language),% class foreign code
+	field_names	:: field_names_set,	% field names
 		% method-wide attributes (accumulating)
 	locals 		:: locals_map,		% The current locals
 	instr_tree 	:: instr_tree,		% The instruction tree (unused)
@@ -181,6 +182,7 @@
 :- type locals_map == map(ilds__id, mlds__type).
 :- type arguments_map == assoc_list(ilds__id, mlds__type). 
 :- type mlds_vartypes == map(ilds__id, mlds__type).
+:- type field_names_set == set(string).
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
@@ -244,7 +246,8 @@
 			)
 		), MLDS0 ^ defns, MercuryCodeMembers, Others),
 	MLDS = MLDS0 ^ defns := [wrapper_class(
-			list__map(rename_defn, MercuryCodeMembers)) | Others].
+			list__map(rename_defn, MercuryCodeMembers)) | 
+			list__map(rename_defn, Others)].
 
 
 :- func wrapper_class(mlds__defns) = mlds__defn.
@@ -272,8 +275,12 @@
 			MaybeStmt = no
 		),
 		Entity = function(MaybePredProcId, Params, MaybeStmt)
-	; Entity0 = class(_),
-		unexpected(this_file, "nested class")
+	; Entity0 = class(ClassDefn),
+		ClassDefn = class_defn(Kind, Imports, Inherits, Implements,
+				Ctors, Members),
+		Entity = class(class_defn(Kind, Imports, Inherits, Implements,
+				list__map(rename_defn, Ctors),
+				list__map(rename_defn, Members)))
 	).
 
 :- func rename_statement(mlds__statement) = mlds__statement.
@@ -449,7 +456,7 @@
 	sorry(this_file, "top level function definition!").
 mlds_defn_to_ilasm_decl(defn(Name, _Context, Flags, class(ClassDefn)),
 		Decl, Info0, Info) :-
-	il_info_new_class(Info0, Info1),
+	il_info_new_class(ClassDefn, Info0, Info1),
 
 	generate_class_body(Name, ClassDefn, ClassName, EntityName, Extends,
 			Interfaces, MethodsAndFieldsAndCtors, Info1, Info2),
@@ -654,7 +661,7 @@
 	; AccessFlag = default,
 		Access = [assembly]
 	; AccessFlag = local,
-		error("decl_flags_to_fieldattrs: local access flag")
+		Access = [private]
 	),
 	PerInstanceFlag = per_instance(Flags),
 	( PerInstanceFlag = one_copy,
@@ -711,11 +718,13 @@
 		% and instructions to initialize it.
 		% See the comments about class constructors to
 		% find out why we do this.
-	data_initializer_to_instrs(DataInitializer, AllocInstrsTree,
-			InitInstrTree),
+	DataRep =^ il_data_rep,
+	{ IlType = mlds_type_to_ilds_type(DataRep, Type) },
+	data_initializer_to_instrs(IlType, DataInitializer,
+			AllocInstrsTree, InitInstrTree),
 
 		% Make a field reference for the field
-	{ FieldRef = make_fieldref(il_array_type, ClassName, FieldName) },
+	{ FieldRef = make_fieldref(IlType, ClassName, FieldName) },
 
 		% If we had to allocate memory, the code
 		% we generate looks like this:
@@ -783,8 +792,6 @@
 	il_info_add_alloc_instructions(AllocInstrs),
 	il_info_add_init_instructions(InitInstrs),
 
-	DataRep =^ il_data_rep,
-	{ IlType = mlds_type_to_ilds_type(DataRep, Type) },
 	{ MaybeOffset = no },
 	{ Initializer = none },
 
@@ -968,8 +975,10 @@
 				{ StoreLvalInstrs = node([]) },
 				{ NameString = "unknown" }
 			),
-			data_initializer_to_instrs(Initializer, AllocInstrs,
-				InitInstrs),
+			DataRep =^ il_data_rep,
+			{ IlType = mlds_type_to_ilds_type(DataRep, MLDSType) },
+			data_initializer_to_instrs(IlType, Initializer,
+				AllocInstrs, InitInstrs),
 			{ string__append("initializer for ", NameString, 
 				Comment) },
 			{ Tree = tree__list([
@@ -989,52 +998,75 @@
 	% initialize this value, leave it on the stack.
 	% XXX the code generator doesn't box these values
 	% we need to look ahead at them and box them appropriately.
-:- pred data_initializer_to_instrs(mlds__initializer::in,
+:- pred data_initializer_to_instrs(ilds__type::in, mlds__initializer::in,
 	instr_tree::out, instr_tree::out, il_info::in, il_info::out) is det.
-data_initializer_to_instrs(init_obj(Rval), node([]), InitInstrs) --> 
+data_initializer_to_instrs(_Type, init_obj(Rval), node([]), InitInstrs) --> 
 	load(Rval, InitInstrs).
 
 	% Currently, structs are the same as arrays.
-data_initializer_to_instrs(init_struct(InitList), AllocInstrs, InitInstrs) --> 
-	data_initializer_to_instrs(init_array(InitList), AllocInstrs, 
-		InitInstrs).
+data_initializer_to_instrs(_Type,
+		init_struct(InitList), AllocInstrs, InitInstrs) --> 
+		% XXX This is the old code from init_array.  This is
+		% needed to handle RTTI correctly.  This needs to be
+		% fixed.
+	{ AllocInstrs = node([ldc(int32, i(list__length(InitList))), 
+		newarr(il_generic_type)]) },
+	{ AddInitializer = 
+		(pred(Init0::in, X0 - Tree0::in, (X0 + 1) - Tree::out,
+				in, out) is det -->
+			maybe_box_initializer(Init0, Init),
+			data_initializer_to_instrs(il_generic_type,
+					Init, ATree1, ITree1),
+			{ Tree = tree(tree(Tree0, node(
+					[dup, ldc(int32, i(X0))])), 
+				tree(tree(ATree1, ITree1), 
+					node([stelem(il_generic_simple_type)]
+				))) }
+		) },
+	list__foldl2(AddInitializer, InitList, 0 - empty, _ - InitInstrs).
 
 	% Put the array allocation in AllocInstrs.
 	% For sub-initializations, we don't worry about keeping AllocInstrs
 	% and InitInstrs apart, since we are only interested in top level
 	% allocations.
-data_initializer_to_instrs(init_array(InitList), AllocInstrs, InitInstrs) -->
+data_initializer_to_instrs(Type,
+		init_array(InitList), AllocInstrs, InitInstrs) -->
 
 		% To initialize an array, we generate the following
 		% code:
 		% 	ldc <length of array>
-		% 	newarr System::Object
+		% 	newarr <array element type>
 		%	
 		% Then, for each element in the array:
 		%	dup
 		%	ldc <index of this element in the array>
 		%	... allocation instructions ...
 		%	... initialization instructions ...
-		%	box the value (if necessary)
-		%	stelem System::Object
+		%	stelem <array element type>
 		%
 		% The initialization will leave the array on the stack.
 		%	
+	{ Type = ilds__type(_Mods, '[]'(ElemType0, _Bounds)) ->
+		ElemType = ElemType0,
+		ElemType = ilds__type(_ElemMods, ElemSimpleType)
+	;
+		unexpected(this_file, "non array type")
+	},
 	{ AllocInstrs = node([ldc(int32, i(list__length(InitList))), 
-		newarr(il_generic_type)]) },
+		newarr(ElemType)]) },
 	{ AddInitializer = 
-		(pred(Init0::in, X0 - Tree0::in, (X0 + 1) - Tree::out,
+		(pred(Init::in, X0 - Tree0::in, (X0 + 1) - Tree::out,
 				in, out) is det -->
-			maybe_box_initializer(Init0, Init),
-			data_initializer_to_instrs(Init, ATree1, ITree1),
+			data_initializer_to_instrs(ElemType,
+					Init, ATree1, ITree1),
 			{ Tree = tree(tree(Tree0, node(
 					[dup, ldc(int32, i(X0))])), 
 				tree(tree(ATree1, ITree1), 
-					node([stelem(il_generic_simple_type)]
+					node([stelem(ElemSimpleType)]
 				))) }
 		) },
 	list__foldl2(AddInitializer, InitList, 0 - empty, _ - InitInstrs).
-data_initializer_to_instrs(no_initializer, node([]), node([])) --> [].
+data_initializer_to_instrs(_, no_initializer, node([]), node([])) --> [].
 
 	% If we are initializing an array or struct, we need to box
 	% all the things inside it.
@@ -1619,6 +1651,8 @@
 			Instrs = instr_node(ldloc(name(MangledVarStr)))
 		; is_argument(MangledVarStr, Info) ->
 			Instrs = instr_node(ldarg(name(MangledVarStr)))
+		; is_local_field(Var, VarType, Info, FieldRef) ->
+			Instrs = instr_node(ldsfld(FieldRef))
 		;
 			FieldRef = make_fieldref_for_handdefined_var(DataRep,
 				Var, VarType),
@@ -1705,6 +1739,8 @@
 			Instrs = instr_node(ldloca(name(MangledVarStr)))
 		; is_argument(MangledVarStr, Info) ->
 			Instrs = instr_node(ldarga(name(MangledVarStr)))
+		; is_local_field(Var, VarType, Info, FieldRef) ->
+			Instrs = instr_node(ldsfld(FieldRef))
 		;
 			FieldRef = make_fieldref_for_handdefined_var(DataRep,
 				Var, VarType),
@@ -2704,6 +2740,17 @@
 is_local(VarName, Info) :-
 	map__contains(Info ^ locals, VarName).
 
+:- pred is_local_field(mlds__var, mlds__type, il_info, fieldref).
+:- mode is_local_field(in, in, in, out) is semidet.
+is_local_field(Var, VarType, Info, FieldRef) :-
+	mangle_mlds_var(Var, VarName),
+	set__member(VarName, Info ^ field_names),
+	Var = qual(ModuleName, _),
+	ClassName = mlds_module_name_to_class_name(ModuleName),
+	FieldRef = make_fieldref(
+			mlds_type_to_ilds_type(Info ^ il_data_rep, VarType),
+			ClassName, VarName).
+
 %-----------------------------------------------------------------------------%
 %
 % Preds and funcs to find the types of rvals.
@@ -3202,21 +3249,28 @@
 
 il_info_init(ModuleName, AssemblyName, Imports, ILDataRep, DebugIlAsm) =
 	il_info(ModuleName, AssemblyName, Imports, set__init, ILDataRep,
-		DebugIlAsm, empty, empty, [], no, set__init,
+		DebugIlAsm, empty, empty, [], no, set__init, set__init,
 		map__init, empty, counter__init(1), counter__init(1), no,
 		Args, MethodName, DefaultSignature) :-
 	Args = [],
 	DefaultSignature = signature(call_conv(no, default), void, []),
 	MethodName = id("").
 
-:- pred il_info_new_class(il_info::in, il_info::out) is det.
+:- pred il_info_new_class(class_defn::in, il_info::in, il_info::out) is det.
 
-il_info_new_class -->
+il_info_new_class(ClassDefn) -->
+	{ ClassDefn = class_defn(_, _, _, _, _, Members) },
+	{ list__filter_map((pred(M::in, S::out) is semidet :-
+			M = mlds__defn(Name, _, _, data(_, _)),
+			S = entity_name_to_ilds_id(Name)
+		), Members, FieldNames)
+	},
 	^ alloc_instrs := empty,
 	^ init_instrs := empty,
 	^ classdecls := [],
 	^ has_main := no,
-	^ class_foreign_langs := set__init.
+	^ class_foreign_langs := set__init,
+	^ field_names := set__list_to_set(FieldNames).
 	
 	% reset the il_info for processing a new method
 :- pred il_info_new_method(arguments_map, signature, member_name, 

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