[m-dev.] for review: The .NET MSIL backend.

Tyson Dowd trd at cs.mu.OZ.AU
Fri Sep 22 18:30:55 AEDT 2000


On 22-Sep-2000, Fergus Henderson <fjh at cs.mu.OZ.AU> wrote:
> On 22-Sep-2000, Tyson Dowd <trd at cs.mu.OZ.AU> wrote:
> > The .NET MSIL (Microsoft Intermediate Language) backend. 
> 
> It's great to see this ready for review.
> 
> You should document the new modules added in this change in
> compiler/notes/compiler_design.html.
> 
> > compiler/ilds.m:
> > 	The IL instruction set, 
> 
> That part of the log message looks incomplete.

Actually, the comma should be a full stop.  I couldn't think of anything
else to say.

> 
> > compiler/ml_code_gen.m:
> > 	If generating MLDS for foreign code that calls continuations
> > 	(that is, model_non pragma C code), create a nested function
> > 	(not implemented in foreign code) to call the continuation.
> > 	This is because in managed C++ it isn't possible to call a
> > 	continuation, but it's fine to call a method written in IL that
> > 	calls the continuation instead.
> 
> Shouldn't that only be done if the target is IL?

Yep.

> 
> > Index: compiler/il_peephole.m
> > +	% We zip down to the end of the instruction list, and start attempting
> > +	% to optimize instruction sequences. As long as we can continue
> > +	% optimizing the instruction sequence, we keep doing so;
> > +	% when we find a sequence we can't optimize, we back up and try
> > +	% to optimize the sequence starting with the previous instruction.
> > +
> > +optimize(Decls0, Decls) :-
> > +	list__map_foldl(optimize_decl, Decls0, Decls, no, _Mod).
> > +
> > +:- pred optimize_decl(decl::in, decl::out, bool::in, bool::out) is det.
> > +optimize_decl(Decl0, Decl, Mod0, Mod) :-
> 
> The name `Mod' is not particularly informative; a comment somewhere here
> explaining what that parameter means would be helpful.  (The comment
> at the top here gives some clues, but not quite enough...)

Ok.

> 
> > +	( Decl0 = class(A, B, C, D, ClassDecls0) ->
> > +		list__map_foldl(optimize_class_decl, ClassDecls0, ClassDecls, 
> > +			no, Mod1),
> > +		Decl = class(A, B, C, D, ClassDecls)
> > +	; Decl0 = method(A, MethodDecls0) ->
> > +		list__map_foldl(optimize_method_decl, MethodDecls0,
> > +			MethodDecls, no, Mod1),
> > +		Decl = method(A, MethodDecls)
> > +	; Decl0 = namespace(A, NamespaceDecls0) ->
> > +		list__map_foldl(optimize_decl, NamespaceDecls0,
> > +			NamespaceDecls, no, Mod1),
> > +		Decl = namespace(A, NamespaceDecls)
> > +	;
> > +		Mod1 = no,
> > +	 	Decl0 = Decl 
> > +	),
> > +	bool__or(Mod0, Mod1, Mod).
> 
> Why do you pass in `no' and then do `or' with `Mod0' afterwards,
> rather than just passing in `Mod0'?

No good reason -- I've changed it to do that.

> 
> > +:- pred match(instr, instrs, instrs).
> > +:- mode match(in, in, out) is semidet.
> > +
> > +	% If a ret is followed by anything other than a label,
> > +	% then we can delete the instruction that follows,
> > +	% since it is unreachable.
> > +	% This is needed for verifiability, since otherwise
> > +	% we sometimes generate some redundant instructions
> > +	% that the verify can't handle, even though they are unreachable.
> 
> s/verify/verifier/
> 
> > +	% ldc(X)
> > +	% stloc(X)
> > +	% ... other instrs ... (no branching or labels)
> > +	% ldloc(X)
> > +	%
> > +	% is turned into
> > +	%
> > +	% ... other instrs ... (no branching or labels)
> > +	% ldc(X)
> > +	% dup
> > +	% stloc(X)
> > +
> > +match(ldc(Type, Const), [stloc(Var)| Instrs0], Instrs) :-
> > +		% The pattern
> > +	list__takewhile((pred(X::in) is semidet :- 
> > +		X \= ldloc(Var),
> > +		X \= label(_),
> > +		not can_branch(X)
> > +	), Instrs0, PreLdInstrs, [ldloc(Var) | Rest]),
> > +
> > +		% Comment and replacement
> > +	Comment = comment(
> > +	    "peephole: ldc(X), stloc(X), ldloc(X) --> ldc(X), dup, stloc(X)"),
> > +	Replacement = list__append(PreLdInstrs, 
> > +		[Comment, ldc(Type, Const), dup, stloc(Var)]),
> > +	Instrs = list__append(Replacement, Rest).
> 
> Shouldn't the comments (both the ones in the source and
> also the ones inserted into the generated code) say
> `ldc(C)' rather than `ldc(X)'?

Yes.

> 
> Also, doesn't that pattern do the wrong thing for
> 	ldc(C1)
> 	stloc(X)
> 	ldc(C2)
> 	stloc(X)
> 	ldloc(X)
> That is, don't you also have to check that the other instructions
> don't include any stores (stloc) to X?

Yep.

> Also indirect stores could cause problems too, couldn't they?

Sure.

Actually, even worse, if you do

ldc(C1)
stloc(X)
call(.....)
ldloc(X)

you have to be sure that the address of X was never passed to the call.
So call, calli, callvirt, jmp, jmpi and newobj are also out.
(I'm not so sure about jmp and jmpi being dangerous but I don't think we
will mess with them right now).

If you make sure there is no address of X loaded anywhere you
can probably do a lot better.  We probably don't actually generate any
code that does this since we only do a "ldloca" to return an output
parameter.  But I guess in future we might generate code like this.

> > +	% Two patterns begin with start_scope.
> > +match(start_block(scope(Locals), Id), Instrs0, Instrs) :-
> > +	( 
> > +		match2(start_block(scope(Locals), Id), Instrs0, Instrs1)
> > +	->
> > +		Instrs = Instrs1
> > +	;	
> > +		match3(start_block(scope(Locals), Id), Instrs0, Instrs)
> > +	).
> > +
> > +	% If this is a scope with a local variable that is stored to but not
> > +	% loaded anywhere, we can eliminate the stores.
> > +	% scope([...X...]) ... dup(X), stloc 
> > +	% becomes
> > +	% scope([...X...]) ... <nothing>
> > +	% This relies on other peephole optimizations to create dup,
> > +	% stloc(X) patterns.
> 
> Shouldn't that comment be `dup, stloc(X)' rather than `dup(X), stloc'?

Yes.

> 
> [... to be continued ...]


diff -u il_peephole.m il_peephole.m
--- il_peephole.m
+++ il_peephole.m
@@ -58,38 +58,40 @@
 optimize(Decls0, Decls) :-
 	list__map_foldl(optimize_decl, Decls0, Decls, no, _Mod).
 
+	% Mod is a bool that says whether the code was modified as a
+	% result of the optimization (that is, whether Decl \= Decl0).
+	% This can be used to decide whether to keep repeat the
+	% optimizations.
 :- pred optimize_decl(decl::in, decl::out, bool::in, bool::out) is det.
 optimize_decl(Decl0, Decl, Mod0, Mod) :-
 	( Decl0 = class(A, B, C, D, ClassDecls0) ->
 		list__map_foldl(optimize_class_decl, ClassDecls0, ClassDecls, 
-			no, Mod1),
+			Mod0, Mod),
 		Decl = class(A, B, C, D, ClassDecls)
 	; Decl0 = method(A, MethodDecls0) ->
 		list__map_foldl(optimize_method_decl, MethodDecls0,
-			MethodDecls, no, Mod1),
+			MethodDecls, Mod0, Mod),
 		Decl = method(A, MethodDecls)
 	; Decl0 = namespace(A, NamespaceDecls0) ->
 		list__map_foldl(optimize_decl, NamespaceDecls0,
-			NamespaceDecls, no, Mod1),
+			NamespaceDecls, Mod0, Mod),
 		Decl = namespace(A, NamespaceDecls)
 	;
-		Mod1 = no,
+		Mod = Mod0,
 	 	Decl0 = Decl 
-	),
-	bool__or(Mod0, Mod1, Mod).
+	).
 
 :- pred optimize_class_decl(classdecl::in, classdecl::out, 
 	bool::in, bool::out) is det.
 optimize_class_decl(Decl0, Decl, Mod0, Mod) :-
 	( Decl0 = method(A, MethodDecls0) ->
 		list__map_foldl(optimize_method_decl, MethodDecls0,
-			MethodDecls, no, Mod1),
+			MethodDecls, Mod0, Mod),
 		Decl = method(A, MethodDecls)
 	;
-		Mod1 = no,
+		Mod = no,
 	 	Decl0 = Decl 
-	),
-	bool__or(Mod0, Mod1, Mod).
+	).
 
 :- pred optimize_method_decl(methoddecl::in, methoddecl::out, 
 	bool::in, bool::out) is det.
@@ -149,7 +151,7 @@
 	% since it is unreachable.
 	% This is needed for verifiability, since otherwise
 	% we sometimes generate some redundant instructions
-	% that the verify can't handle, even though they are unreachable.
+	% that the verifier can't handle, even though they are unreachable.
 	%
 	% Push ret past nops so we can find instructions on the other
 	% side of them (but don't eliminate them because they may be
@@ -198,15 +200,15 @@
 	Replacement = list__append([dup | Nops],  [stloc(Var)]),
 	Instrs = [comment(Comment) | list__append(Replacement, Rest)].
 
-	% ldc(X)
+	% ldc(C)
 	% stloc(X)
-	% ... other instrs ... (no branching or labels)
+	% ... other instrs ... (no branching, labels, stores to X or )
 	% ldloc(X)
 	%
 	% is turned into
 	%
 	% ... other instrs ... (no branching or labels)
-	% ldc(X)
+	% ldc(C)
 	% dup
 	% stloc(X)
 
@@ -215,6 +217,9 @@
 	list__takewhile((pred(X::in) is semidet :- 
 		X \= ldloc(Var),
 		X \= label(_),
+		X \= stloc(Var),
+		X \= stind(_),
+		not can_call(X),
 		not can_branch(X)
 	), Instrs0, PreLdInstrs, [ldloc(Var) | Rest]),
 
@@ -237,7 +242,7 @@
 
 	% If this is a scope with a local variable that is stored to but not
 	% loaded anywhere, we can eliminate the stores.
-	% scope([...X...]) ... dup(X), stloc 
+	% scope([...X...]) ... dup, stloc(X)
 	% becomes
 	% scope([...X...]) ... <nothing>
 	% This relies on other peephole optimizations to create dup,
@@ -399,6 +404,16 @@
 can_branch(blt(_, _)).
 can_branch(bne(_, _)).
 can_branch(switch(_)).
+
+	% These instructions can make a call
+:- pred can_call(instr).
+:- mode can_call(in) is semidet.
+can_call(call(_)).
+can_call(calli(_)).
+can_call(callvirt(_)).
+can_call(jmp(_)).
+can_call(jmpi).
+can_call(newobj(_)).
 
 	% keep_looking(Producer, Condition, Input, IntermediateResult0, 
 	%	FinalResult, Leftovers) :-

-- 
       Tyson Dowd           # 
                            #  Surreal humour isn't everyone's cup of fur.
     trd at cs.mu.oz.au        # 
http://www.cs.mu.oz.au/~trd #
--------------------------------------------------------------------------
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