Browse Source

More inlining edge cases handled

Nicolas Petton 12 năm trước cách đây
mục cha
commit
da32a13ba2

+ 5 - 0
js/Compiler-Core.js

@@ -1,5 +1,6 @@
 smalltalk.addPackage('Compiler-Core', {});
 smalltalk.addClass('Compiler', smalltalk.Object, ['currentClass', 'source', 'unknownVariables', 'codeGeneratorClass'], 'Compiler-Core');
+smalltalk.Compiler.comment="I provide the public interface for compiling Amber source code into JavaScript.\x0a\x0aThe code generator used to produce JavaScript can be plugged with `#codeGeneratorClass`. \x0aThe default code generator is an instance of `InlinedCodeGenerator`"
 smalltalk.addMethod(
 "_codeGeneratorClass",
 smalltalk.method({
@@ -375,9 +376,11 @@ smalltalk.Compiler.klass);
 
 
 smalltalk.addClass('DoIt', smalltalk.Object, [], 'Compiler-Core');
+smalltalk.DoIt.comment="`DoIt` is the class used to compile and evaluate expressions. See `Compiler >> evaluateExpression:`."
 
 
 smalltalk.addClass('NodeVisitor', smalltalk.Object, [], 'Compiler-Core');
+smalltalk.NodeVisitor.comment="I am the abstract super class of all AST node visitors."
 smalltalk.addMethod(
 "_visit_",
 smalltalk.method({
@@ -653,6 +656,7 @@ smalltalk.NodeVisitor);
 
 
 smalltalk.addClass('AbstractCodeGenerator', smalltalk.NodeVisitor, ['currentClass', 'source'], 'Compiler-Core');
+smalltalk.AbstractCodeGenerator.comment="I am the abstract super class of all code generators and provide their common API."
 smalltalk.addMethod(
 "_classNameFor_",
 smalltalk.method({
@@ -784,6 +788,7 @@ smalltalk.AbstractCodeGenerator);
 
 
 smalltalk.addClass('CodeGenerator', smalltalk.AbstractCodeGenerator, [], 'Compiler-Core');
+smalltalk.CodeGenerator.comment="I am a basic code generator. I generate a valid JavaScript output, but no not perform any inlining.\x0aSee `InliningCodeGenerator` for an optimized JavaScript code generation."
 smalltalk.addMethod(
 "_compileNode_",
 smalltalk.method({

+ 1 - 1
js/Compiler-Exceptions.deploy.js

@@ -8,7 +8,7 @@ smalltalk.addClass('ParseError', smalltalk.CompilerError, [], 'Compiler-Exceptio
 smalltalk.addClass('SemanticError', smalltalk.CompilerError, [], 'Compiler-Exceptions');
 
 
-smalltalk.addClass('InliningError', smalltalk.SemanticError, ['variableName'], 'Compiler-Exceptions');
+smalltalk.addClass('InliningError', smalltalk.SemanticError, [], 'Compiler-Exceptions');
 
 
 smalltalk.addClass('InvalidAssignmentError', smalltalk.SemanticError, ['variableName'], 'Compiler-Exceptions');

+ 4 - 1
js/Compiler-Exceptions.js

@@ -1,15 +1,18 @@
 smalltalk.addPackage('Compiler-Exceptions', {});
 smalltalk.addClass('CompilerError', smalltalk.Error, [], 'Compiler-Exceptions');
+smalltalk.CompilerError.comment="I am the common superclass of all compiling errors."
 
 
 smalltalk.addClass('ParseError', smalltalk.CompilerError, [], 'Compiler-Exceptions');
+smalltalk.ParseError.comment="Instance of ParseError are signaled on any parsing error. \x0aSee `Smalltalk >> #parse:`"
 
 
 smalltalk.addClass('SemanticError', smalltalk.CompilerError, [], 'Compiler-Exceptions');
 smalltalk.SemanticError.comment="I represent an abstract semantic error thrown by the SemanticAnalyzer.\x0aSemantic errors can be unknown variable errors, etc.\x0aSee my subclasses for concrete errors.\x0a\x0aThe IDE should catch instances of Semantic error to deal with them when compiling"
 
 
-smalltalk.addClass('InliningError', smalltalk.SemanticError, ['variableName'], 'Compiler-Exceptions');
+smalltalk.addClass('InliningError', smalltalk.SemanticError, [], 'Compiler-Exceptions');
+smalltalk.InliningError.comment="Instances of InliningError are signaled when using an `InliningCodeGenerator`in a `Compiler`."
 
 
 smalltalk.addClass('InvalidAssignmentError', smalltalk.SemanticError, ['variableName'], 'Compiler-Exceptions');

Những thai đổi đã bị hủy bỏ vì nó quá lớn
+ 105 - 18
js/Compiler-IR.deploy.js


Những thai đổi đã bị hủy bỏ vì nó quá lớn
+ 147 - 25
js/Compiler-IR.js


Những thai đổi đã bị hủy bỏ vì nó quá lớn
+ 347 - 202
js/Compiler-Inlining.deploy.js


Những thai đổi đã bị hủy bỏ vì nó quá lớn
+ 355 - 210
js/Compiler-Inlining.js


+ 8 - 11
js/boot.js

@@ -335,11 +335,11 @@ function Smalltalk(){
 
 	/* Handles unhandled errors during message sends */
 
-	st.send = function(receiver, selector, args, klass, index) {
+	st.send = function(receiver, selector, args, klass) {
 		if(st.thisContext) {
-			return withContextSend(receiver, selector, args, klass, index);
+			return withContextSend(receiver, selector, args, klass);
 		} else {
-			try {return withContextSend(receiver, selector, args, klass, index)}
+			try {return withContextSend(receiver, selector, args, klass)}
 			catch(error) {
 				// Reset the context stack in any case
 				st.thisContext = undefined;
@@ -352,14 +352,14 @@ function Smalltalk(){
 		}
 	};
 
-	function withContextSend(receiver, selector, args, klass, index) {
+	function withContextSend(receiver, selector, args, klass) {
 		var call, method;
 		if(receiver == null) {
 			receiver = nil;
 		}
 		method = klass ? klass.fn.prototype[selector] : receiver.klass && receiver[selector];
 		if(method) {
-			var context = pushContext(receiver, selector, method, args, index);
+			var context = pushContext(receiver, selector, method, args);
 			call = method.apply(receiver, args);
 			popContext(context);
 			return call;
@@ -442,10 +442,10 @@ function Smalltalk(){
 		}
 	};
 
-	function pushContext(receiver, selector, method, temps, index) {
+	function pushContext(receiver, selector, method, temps) {
 		var c = st.oldContext, tc = st.thisContext;
 		if (!c) {
-			return st.thisContext = new SmalltalkMethodContext(receiver, selector, method, temps, index, tc);
+			return st.thisContext = new SmalltalkMethodContext(receiver, selector, method, temps, tc);
 		}
 		st.oldContext = null;
 		c.homeContext = tc;
@@ -453,7 +453,6 @@ function Smalltalk(){
 		c.receiver    = receiver;
         c.selector    = selector;
 		c.method      = method;
-        c.index       = index;
 		c.temps       = temps || {};
 		return st.thisContext = c;
 	};
@@ -524,12 +523,11 @@ function Smalltalk(){
     }
 };
 
-function SmalltalkMethodContext(receiver, selector, method, temps, index, home) {
+function SmalltalkMethodContext(receiver, selector, method, temps, home) {
 	this.receiver    = receiver;
     this.selector    = selector;
 	this.method      = method;
 	this.temps       = temps || {};
-    this.index       = index;
 	this.homeContext = home;
 
     this.resume = function() {
@@ -547,7 +545,6 @@ SmalltalkMethodContext.prototype.copy = function() {
         this.selector,
 		this.method, 
 		this.temps, 
-        this.index,
 		home
 	);
 };

+ 14 - 0
st/Compiler-Core.st

@@ -2,6 +2,11 @@ Smalltalk current createPackage: 'Compiler-Core' properties: #{}!
 Object subclass: #Compiler
 	instanceVariableNames: 'currentClass source unknownVariables codeGeneratorClass'
 	package: 'Compiler-Core'!
+!Compiler commentStamp!
+I provide the public interface for compiling Amber source code into JavaScript.
+
+The code generator used to produce JavaScript can be plugged with `#codeGeneratorClass`. 
+The default code generator is an instance of `InlinedCodeGenerator`!
 
 !Compiler methodsFor: 'accessing'!
 
@@ -127,10 +132,14 @@ recompileAll
 Object subclass: #DoIt
 	instanceVariableNames: ''
 	package: 'Compiler-Core'!
+!DoIt commentStamp!
+`DoIt` is the class used to compile and evaluate expressions. See `Compiler >> evaluateExpression:`.!
 
 Object subclass: #NodeVisitor
 	instanceVariableNames: ''
 	package: 'Compiler-Core'!
+!NodeVisitor commentStamp!
+I am the abstract super class of all AST node visitors.!
 
 !NodeVisitor methodsFor: 'visiting'!
 
@@ -205,6 +214,8 @@ visitVariableNode: aNode
 NodeVisitor subclass: #AbstractCodeGenerator
 	instanceVariableNames: 'currentClass source'
 	package: 'Compiler-Core'!
+!AbstractCodeGenerator commentStamp!
+I am the abstract super class of all code generators and provide their common API.!
 
 !AbstractCodeGenerator methodsFor: 'accessing'!
 
@@ -252,6 +263,9 @@ compileNode: aNode
 AbstractCodeGenerator subclass: #CodeGenerator
 	instanceVariableNames: ''
 	package: 'Compiler-Core'!
+!CodeGenerator commentStamp!
+I am a basic code generator. I generate a valid JavaScript output, but no not perform any inlining.
+See `InliningCodeGenerator` for an optimized JavaScript code generation.!
 
 !CodeGenerator methodsFor: 'compiling'!
 

+ 8 - 1
st/Compiler-Exceptions.st

@@ -2,10 +2,15 @@ Smalltalk current createPackage: 'Compiler-Exceptions' properties: #{}!
 Error subclass: #CompilerError
 	instanceVariableNames: ''
 	package: 'Compiler-Exceptions'!
+!CompilerError commentStamp!
+I am the common superclass of all compiling errors.!
 
 CompilerError subclass: #ParseError
 	instanceVariableNames: ''
 	package: 'Compiler-Exceptions'!
+!ParseError commentStamp!
+Instance of ParseError are signaled on any parsing error. 
+See `Smalltalk >> #parse:`!
 
 CompilerError subclass: #SemanticError
 	instanceVariableNames: ''
@@ -18,8 +23,10 @@ See my subclasses for concrete errors.
 The IDE should catch instances of Semantic error to deal with them when compiling!
 
 SemanticError subclass: #InliningError
-	instanceVariableNames: 'variableName'
+	instanceVariableNames: ''
 	package: 'Compiler-Exceptions'!
+!InliningError commentStamp!
+Instances of InliningError are signaled when using an `InliningCodeGenerator`in a `Compiler`.!
 
 SemanticError subclass: #InvalidAssignmentError
 	instanceVariableNames: 'variableName'

+ 65 - 22
st/Compiler-IR.st

@@ -84,24 +84,6 @@ visitAssignmentNode: aNode
 	^ left
 !
 
-visitAssignmentNode: aNode aliasing: aBoolean
-	| left right |
-	
-	aBoolean 
-		ifTrue: [ | assignment |
-			assignment := self visit: aNode right.
-			self sequence add: assignment.
-			right :=  assignment instructions first ]
-		ifFalse: [ right := self visit: aNode right ].
-
-	left := self visit: aNode left.
-	
-	^ IRAssignment new 
-		add: left;
-		add: right;
-		yourself
-!
-
 visitBlockNode: aNode
 	| closure |
 	closure := IRClosure new
@@ -142,6 +124,20 @@ visitCascadeNode: aNode
 	^ self alias: aNode nodes last
 !
 
+visitDynamicArrayNode: aNode
+	| array |
+	array := IRDynamicArray new.
+	aNode nodes do: [ :each | array add: (self visit: each) ].
+	^ array
+!
+
+visitDynamicDictionaryNode: aNode
+	| dictionary |
+	dictionary := IRDynamicDictionary new.
+	aNode nodes do: [ :each | dictionary add: (self visit: each) ].
+	^ dictionary
+!
+
 visitJSStatementNode: aNode
 	^ IRVerbatim new
 		source: aNode source;
@@ -193,7 +189,10 @@ visitSendNode: aNode
 		index: aNode index.
 	aNode superSend ifTrue: [ send classSend: self theClass superclass ].
 
-	receiver := self visit: aNode receiver.
+	receiver := aNode receiver shouldBeInlined 
+		ifTrue: [ self alias: aNode receiver ]
+		ifFalse: [ self visit: aNode receiver ].
+
 	arguments := aNode arguments collect: [ :each | 
 		each shouldBeInlined
 			ifTrue: [ self alias: each ]
@@ -336,6 +335,26 @@ accept: aVisitor
 	^ aVisitor visitIRAssignment: self
 ! !
 
+IRInstruction subclass: #IRDynamicArray
+	instanceVariableNames: ''
+	package: 'Compiler-IR'!
+
+!IRDynamicArray methodsFor: 'visiting'!
+
+accept: aVisitor
+	^ aVisitor visitIRDynamicArray: self
+! !
+
+IRInstruction subclass: #IRDynamicDictionary
+	instanceVariableNames: ''
+	package: 'Compiler-IR'!
+
+!IRDynamicDictionary methodsFor: 'visiting'!
+
+accept: aVisitor
+	^ aVisitor visitIRDynamicDictionary: self
+! !
+
 IRInstruction subclass: #IRScopedInstruction
 	instanceVariableNames: 'scope'
 	package: 'Compiler-IR'!
@@ -687,6 +706,14 @@ visitIRClosure: anIRClosure
 	^ self visitIRInstruction: anIRClosure
 !
 
+visitIRDynamicArray: anIRDynamicArray
+	^ self visitIRInstruction: anIRDynamicArray
+!
+
+visitIRDynamicDictionary: anIRDynamicDictionary
+	^ self visitIRInstruction: anIRDynamicDictionary
+!
+
 visitIRInstruction: anIRInstruction
 	anIRInstruction instructions do: [ :each | self visit: each ].
 	^ anIRInstruction
@@ -771,6 +798,22 @@ visitIRClosure: anIRClosure
 		arguments: anIRClosure arguments
 !
 
+visitIRDynamicArray: anIRDynamicArray
+	self stream nextPutAll: '['.
+	anIRDynamicArray instructions
+		do: [ :each | self visit: each ]
+		separatedBy: [ self stream nextPutAll: ',' ].
+	stream nextPutAll: ']'
+!
+
+visitIRDynamicDictionary: anIRDynamicDictionary
+	self stream nextPutAll: 'smalltalk.HashedCollection._fromPairs_(['.
+		anIRDynamicDictionary instructions 
+			do: [ :each | self visit: each ]
+			separatedBy: [self stream nextPutAll: ',' ].
+	self stream nextPutAll: '])'
+!
+
 visitIRMethod: anIRMethod
 	self stream
 		nextPutMethodDeclaration: anIRMethod 
@@ -805,15 +848,15 @@ visitIRSend: anIRSend
 		do: [ :each | self visit: each ]
 		separatedBy: [ self stream nextPutAll: ',' ].
 	self stream nextPutAll: ']'.
-	anIRSend index > 1 
+	"anIRSend index > 1 
 		ifTrue: [
 			anIRSend classSend 
 				ifNil: [ self stream nextPutAll: ',undefined' ]
 				ifNotNil: [ self stream nextPutAll: ',', anIRSend classSend asJavascript ].
 			self stream nextPutAll: ',', anIRSend index asString ]
-		ifFalse: [
+		ifFalse: ["
 			anIRSend classSend ifNotNil: [  
-				self stream nextPutAll: ',', anIRSend classSend asJavascript ]].
+				self stream nextPutAll: ',', anIRSend classSend asJavascript ]"]".
 	self stream nextPutAll: ')'
 !
 

+ 39 - 1
st/Compiler-Inlining.st

@@ -2,6 +2,8 @@ Smalltalk current createPackage: 'Compiler-Inlining' properties: #{}!
 IRAssignment subclass: #IRInlinedAssignment
 	instanceVariableNames: ''
 	package: 'Compiler-Inlining'!
+!IRInlinedAssignment commentStamp!
+I represent an inlined assignment instruction.!
 
 !IRInlinedAssignment methodsFor: 'testing'!
 
@@ -18,6 +20,8 @@ accept: aVisitor
 IRClosure subclass: #IRInlinedClosure
 	instanceVariableNames: ''
 	package: 'Compiler-Inlining'!
+!IRInlinedClosure commentStamp!
+I represent an inlined closure instruction.!
 
 !IRInlinedClosure methodsFor: 'testing'!
 
@@ -34,6 +38,8 @@ accept: aVisitor
 IRReturn subclass: #IRInlinedReturn
 	instanceVariableNames: ''
 	package: 'Compiler-Inlining'!
+!IRInlinedReturn commentStamp!
+I represent an inlined local return instruction.!
 
 !IRInlinedReturn methodsFor: 'testing'!
 
@@ -50,6 +56,8 @@ accept: aVisitor
 IRInlinedReturn subclass: #IRInlinedNonLocalReturn
 	instanceVariableNames: ''
 	package: 'Compiler-Inlining'!
+!IRInlinedNonLocalReturn commentStamp!
+I represent an inlined non local return instruction.!
 
 !IRInlinedNonLocalReturn methodsFor: 'testing'!
 
@@ -66,6 +74,8 @@ accept: aVisitor
 IRSend subclass: #IRInlinedSend
 	instanceVariableNames: ''
 	package: 'Compiler-Inlining'!
+!IRInlinedSend commentStamp!
+I am the abstract super class of inlined message send instructions.!
 
 !IRInlinedSend methodsFor: 'testing'!
 
@@ -102,6 +112,8 @@ accept: aVisitor
 IRBlockSequence subclass: #IRInlinedSequence
 	instanceVariableNames: ''
 	package: 'Compiler-Inlining'!
+!IRInlinedSequence commentStamp!
+I represent a (block) sequence inside an inlined closure instruction (instance of `IRInlinedClosure`).!
 
 !IRInlinedSequence methodsFor: 'testing'!
 
@@ -156,6 +168,10 @@ accept: aVisitor
 IRVisitor subclass: #IRInliner
 	instanceVariableNames: ''
 	package: 'Compiler-Inlining'!
+!IRInliner commentStamp!
+I visit an IR tree, inlining message sends and block closures.
+
+Message selectors that can be inlined are answered by `IRSendInliner >> #inlinedSelectors`!
 
 !IRInliner methodsFor: 'factory'!
 
@@ -205,6 +221,8 @@ shouldInlineSend: anIRSend
 !IRInliner methodsFor: 'visiting'!
 
 transformNonLocalReturn: anIRNonLocalReturn
+	"Replace a non local return into a local return"
+
 	| localReturn |
 	anIRNonLocalReturn scope canInlineNonLocalReturns ifTrue: [
 		anIRNonLocalReturn scope methodScope removeNonLocalReturn: anIRNonLocalReturn scope.
@@ -245,6 +263,8 @@ visitIRSend: anIRSend
 IRJSTranslator subclass: #IRInliningJSTranslator
 	instanceVariableNames: ''
 	package: 'Compiler-Inlining'!
+!IRInliningJSTranslator commentStamp!
+I am a specialized JavaScript translator able to write inlined IR instructions to JavaScript stream (`JSStream` instance).!
 
 !IRInliningJSTranslator methodsFor: 'visiting'!
 
@@ -434,7 +454,7 @@ inlineClosure: anIRClosure
 
 inlineSend: anIRSend
 	self send: anIRSend.
-	self perform: self send selector withArguments: self send instructions allButFirst
+	^ self perform: self send selector withArguments: self send instructions allButFirst
 ! !
 
 !IRSendInliner class methodsFor: 'accessing'!
@@ -453,6 +473,20 @@ shouldInline: anIRInstruction
 IRSendInliner subclass: #IRAssignmentInliner
 	instanceVariableNames: 'assignment'
 	package: 'Compiler-Inlining'!
+!IRAssignmentInliner commentStamp!
+I inline message sends together with assignments by moving them around into the inline closure instructions. 
+
+##Example
+
+	foo
+		| a |
+		a := true ifTrue: [ 1 ]
+
+Will produce:
+
+	if(smalltalk.assert(true) {
+		a = 1;
+	};!
 
 !IRAssignmentInliner methodsFor: 'accessing'!
 
@@ -488,6 +522,8 @@ inlineAssignment: anIRAssignment
 IRSendInliner subclass: #IRReturnInliner
 	instanceVariableNames: ''
 	package: 'Compiler-Inlining'!
+!IRReturnInliner commentStamp!
+I inline message sends with inlined closure together with a return instruction.!
 
 !IRReturnInliner methodsFor: 'factory'!
 
@@ -528,6 +564,8 @@ inlinedSequence
 CodeGenerator subclass: #InliningCodeGenerator
 	instanceVariableNames: ''
 	package: 'Compiler-Inlining'!
+!InliningCodeGenerator commentStamp!
+I am a specialized code generator that uses inlining to produce more optimized JavaScript output!
 
 !InliningCodeGenerator methodsFor: 'compiling'!
 

Một số tệp đã không được hiển thị bởi vì quá nhiều tập tin thay đổi trong này khác