amber/st/Compiler-IR.st in resin-0.3.1 vs amber/st/Compiler-IR.st in resin-0.4.0

- old
+ new

@@ -58,11 +58,11 @@ !IRASTTranslator methodsFor: 'visiting'! alias: aNode | variable | - aNode isValueNode ifTrue: [ ^ self visit: aNode ]. + aNode isImmutable ifTrue: [ ^ self visit: aNode ]. variable := IRVariable new variable: (AliasVar new name: '$', self nextAlias); yourself. @@ -74,10 +74,33 @@ self method internalVariables add: variable. ^ variable ! +aliasTemporally: aCollection + "https://github.com/NicolasPetton/amber/issues/296 + + If a node is aliased, all preceding ones are aliased as well. + The tree is iterated twice. First we get the aliasing dependency, + then the aliasing itself is done" + + | threshold result | + threshold := 0. + + aCollection withIndexDo: [ :each :i | + each subtreeNeedsAliasing + ifTrue: [ threshold := i ]]. + + result := OrderedCollection new. + aCollection withIndexDo: [ :each :i | + result add: (i <= threshold + ifTrue: [ self alias: each ] + ifFalse: [ self visit: each ])]. + + ^result +! + visitAssignmentNode: aNode | left right assignment | right := self visit: aNode right. left := self visit: aNode left. self sequence add: (IRAssignment new @@ -94,10 +117,11 @@ scope: aNode scope; yourself. aNode scope temps do: [ :each | closure add: (IRTempDeclaration new name: each name; + scope: aNode scope; yourself) ]. aNode nodes do: [ :each | closure add: (self visit: each) ]. ^ closure ! @@ -114,11 +138,11 @@ ! visitCascadeNode: aNode | alias | - aNode receiver isValueNode ifFalse: [ + aNode receiver isImmutable ifFalse: [ alias := self alias: aNode receiver. aNode nodes do: [ :each | each receiver: (VariableNode new binding: alias variable) ]]. aNode nodes allButLast do: [ :each | @@ -128,18 +152,18 @@ ! visitDynamicArrayNode: aNode | array | array := IRDynamicArray new. - aNode nodes do: [ :each | array add: (self visit: each) ]. + (self aliasTemporally: aNode nodes) do: [:each | array add: each]. ^ array ! visitDynamicDictionaryNode: aNode | dictionary | dictionary := IRDynamicDictionary new. - aNode nodes do: [ :each | dictionary add: (self visit: each) ]. + (self aliasTemporally: aNode nodes) do: [:each | dictionary add: each]. ^ dictionary ! visitJSStatementNode: aNode ^ IRVerbatim new @@ -149,20 +173,23 @@ visitMethodNode: aNode self method: (IRMethod new source: self source; + theClass: self theClass; arguments: aNode arguments; selector: aNode selector; messageSends: aNode messageSends; + superSends: aNode superSends; classReferences: aNode classReferences; scope: aNode scope; yourself). aNode scope temps do: [ :each | self method add: (IRTempDeclaration new name: each name; + scope: aNode scope; yourself) ]. aNode nodes do: [ :each | self method add: (self visit: each) ]. aNode scope hasLocalReturn ifFalse: [ @@ -183,26 +210,21 @@ return add: (self alias: each) ]. ^ return ! visitSendNode: aNode - | send receiver arguments | + | send all receiver arguments | send := IRSend new. send selector: aNode selector; index: aNode index. aNode superSend ifTrue: [ send classSend: self theClass superclass ]. + + all := self aliasTemporally: { aNode receiver }, aNode arguments. + receiver := all first. + arguments := all allButFirst. - receiver := (aNode receiver shouldBeInlined or: [ aNode receiver shouldBeAliased ]) - ifTrue: [ self alias: aNode receiver ] - ifFalse: [ self visit: aNode receiver ]. - - arguments := aNode arguments collect: [ :each | - each shouldBeInlined - ifTrue: [ self alias: each ] - ifFalse: [ self visit: each ]]. - send add: receiver. arguments do: [ :each | send add: each ]. ^ send ! @@ -240,10 +262,14 @@ instructions ^ instructions ifNil: [ instructions := OrderedCollection new ] ! +method + ^ self parent method +! + parent ^ parent ! parent: anIRInstruction @@ -292,10 +318,14 @@ isLocalReturn ^ false ! +isMethod + ^ false +! + isReturn ^ false ! isSend @@ -370,29 +400,46 @@ scope: aScope scope := aScope ! ! -IRScopedInstruction subclass: #IRClosure +IRScopedInstruction subclass: #IRClosureInstruction instanceVariableNames: 'arguments' package: 'Compiler-IR'! -!IRClosure methodsFor: 'accessing'! +!IRClosureInstruction methodsFor: 'accessing'! arguments ^ arguments ifNil: [ #() ] ! arguments: aCollection arguments := aCollection ! +locals + ^ self arguments copy + addAll: (self tempDeclarations collect: [ :each | each name ]); + yourself +! + scope: aScope super scope: aScope. aScope instruction: self ! +tempDeclarations + ^ self instructions select: [ :each | + each isTempDeclaration ] +! ! + +IRClosureInstruction subclass: #IRClosure + instanceVariableNames: '' + package: 'Compiler-IR'! + +!IRClosure methodsFor: 'accessing'! + sequence ^ self instructions last ! ! !IRClosure methodsFor: 'testing'! @@ -405,26 +452,18 @@ accept: aVisitor ^ aVisitor visitIRClosure: self ! ! -IRScopedInstruction subclass: #IRMethod - instanceVariableNames: 'source selector classReferences messageSends arguments internalVariables' +IRClosureInstruction subclass: #IRMethod + instanceVariableNames: 'theClass source selector classReferences messageSends superSends internalVariables' package: 'Compiler-IR'! !IRMethod commentStamp! I am a method instruction! !IRMethod methodsFor: 'accessing'! -arguments - ^ arguments -! - -arguments: aCollection - arguments := aCollection -! - classReferences ^ classReferences ! classReferences: aCollection @@ -433,21 +472,24 @@ internalVariables ^ internalVariables ifNil: [ internalVariables := Set new ] ! +isMethod + ^ true +! + messageSends ^ messageSends ! messageSends: aCollection messageSends := aCollection ! -scope: aScope - super scope: aScope. - aScope instruction: self +method + ^ self ! selector ^ selector ! @@ -460,10 +502,26 @@ ^ source ! source: aString source := aString +! + +superSends + ^ superSends +! + +superSends: aCollection + superSends := aCollection +! + +theClass + ^ theClass +! + +theClass: aClass + theClass := aClass ! ! !IRMethod methodsFor: 'visiting'! accept: aVisitor @@ -541,10 +599,36 @@ accept: aVisitor ^ aVisitor visitIRNonLocalReturn: self ! ! +IRScopedInstruction subclass: #IRTempDeclaration + instanceVariableNames: 'name' + package: 'Compiler-IR'! + +!IRTempDeclaration methodsFor: 'accessing'! + +name + ^ name +! + +name: aString + name := aString +! ! + +!IRTempDeclaration methodsFor: 'testing'! + +isTempDeclaration + ^ true +! ! + +!IRTempDeclaration methodsFor: 'visiting'! + +accept: aVisitor + ^ aVisitor visitIRTempDeclaration: self +! ! + IRInstruction subclass: #IRSend instanceVariableNames: 'selector classSend index' package: 'Compiler-IR'! !IRSend commentStamp! I am a message send instruction.! @@ -565,10 +649,16 @@ index: anInteger index := anInteger ! +javascriptSelector + ^ self classSend + ifNil: [ self selector asSelector ] + ifNotNil: [ self selector asSuperSelector ] +! + selector ^ selector ! selector: aString @@ -611,36 +701,10 @@ accept: aVisitor ^ aVisitor visitIRBlockSequence: self ! ! -IRInstruction subclass: #IRTempDeclaration - instanceVariableNames: 'name' - package: 'Compiler-IR'! -!IRTempDeclaration commentStamp! -I am a temporary variable declaration instruction! - -!IRTempDeclaration methodsFor: 'accessing'! - -name - ^ name -! - -name: aString - name := aString -! ! - -!IRTempDeclaration methodsFor: 'visiting'! - -accept: aVisitor - ^ aVisitor visitIRTempDeclaration: self -! - -isTempDeclaration - ^ true -! ! - IRInstruction subclass: #IRValue instanceVariableNames: 'value' package: 'Compiler-IR'! !IRValue commentStamp! I am the simplest possible instruction. I represent a value.! @@ -829,11 +893,16 @@ self visit: anIRAssignment instructions last. ! visitIRClosure: anIRClosure self stream - nextPutClosureWith: [ super visitIRClosure: anIRClosure ] + nextPutClosureWith: [ + self stream nextPutVars: (anIRClosure tempDeclarations collect: [ :each | + each name asVariableName ]). + self stream + nextPutBlockContextFor: anIRClosure + during: [ super visitIRClosure: anIRClosure ] ] arguments: anIRClosure arguments ! visitIRDynamicArray: anIRDynamicArray self stream nextPutAll: '['. @@ -850,22 +919,26 @@ separatedBy: [self stream nextPutAll: ',' ]. self stream nextPutAll: '])' ! visitIRMethod: anIRMethod + self stream nextPutMethodDeclaration: anIRMethod with: [ self stream nextPutFunctionWith: [ + self stream nextPutVars: (anIRMethod tempDeclarations collect: [ :each | + each name asVariableName ]). + self stream nextPutContextFor: anIRMethod during: [ anIRMethod internalVariables notEmpty ifTrue: [ self stream nextPutVars: (anIRMethod internalVariables asArray collect: [ :each | each variable alias ]) ]. anIRMethod scope hasNonLocalReturn ifTrue: [ self stream nextPutNonLocalReturnHandlingWith: [ super visitIRMethod: anIRMethod ]] - ifFalse: [ super visitIRMethod: anIRMethod ]] + ifFalse: [ super visitIRMethod: anIRMethod ]]] arguments: anIRMethod arguments ] ! visitIRNonLocalReturn: anIRNonLocalReturn self stream nextPutNonLocalReturnWith: [ @@ -876,37 +949,42 @@ self stream nextPutReturnWith: [ super visitIRReturn: anIRReturn ] ! visitIRSend: anIRSend - self stream nextPutAll: 'smalltalk.send('. - self visit: anIRSend instructions first. - self stream nextPutAll: ',"', anIRSend selector asSelector, '",['. - anIRSend instructions allButFirst - do: [ :each | self visit: each ] - separatedBy: [ self stream nextPutAll: ',' ]. - self stream nextPutAll: ']'. - "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: [" - anIRSend classSend ifNotNil: [ - self stream nextPutAll: ',', anIRSend classSend asJavascript ]"]". - self stream nextPutAll: ')' + anIRSend classSend + ifNil: [ + self stream nextPutAll: '_st('. + self visit: anIRSend instructions first. + self stream nextPutAll: ').', anIRSend selector asSelector, '('. + anIRSend instructions allButFirst + do: [ :each | self visit: each ] + separatedBy: [ self stream nextPutAll: ',' ]. + self stream nextPutAll: ')' ] + ifNotNil: [ + self stream + nextPutAll: anIRSend classSend asJavascript, '.fn.prototype.'; + nextPutAll: anIRSend selector asSelector, '.apply('; + nextPutAll: '_st('. + self visit: anIRSend instructions first. + self stream nextPutAll: '), ['. + anIRSend instructions allButFirst + do: [ :each | self visit: each ] + separatedBy: [ self stream nextPutAll: ',' ]. + self stream nextPutAll: '])' ] ! visitIRSequence: anIRSequence self stream nextPutSequenceWith: [ anIRSequence instructions do: [ :each | self stream nextPutStatementWith: (self visit: each) ]] ! visitIRTempDeclaration: anIRTempDeclaration - self stream nextPutVar: anIRTempDeclaration name asVariableName + "self stream + nextPutAll: 'var ', anIRTempDeclaration name asVariableName, ';'; + lf" ! visitIRValue: anIRValue self stream nextPutAll: anIRValue value asJavascript ! @@ -955,20 +1033,68 @@ nextPutAssignment stream nextPutAll: '=' ! +nextPutBlockContextFor: anIRClosure during: aBlock + self + nextPutAll: 'return smalltalk.withContext(function(', anIRClosure scope alias, ') {'; + nextPutAll: String cr. + + aBlock value. + + self + nextPutAll: '}, function(', anIRClosure scope alias, ') {'; + nextPutAll: anIRClosure scope alias, '.fillBlock({'. + + anIRClosure locals + do: [ :each | + self + nextPutAll: each asVariableName; + nextPutAll: ':'; + nextPutAll: each asVariableName] + separatedBy: [ self nextPutAll: ',' ]. + + self + nextPutAll: '},'; + nextPutAll: anIRClosure method scope alias, ')})' +! + nextPutClosureWith: aBlock arguments: anArray stream nextPutAll: '(function('. anArray do: [ :each | stream nextPutAll: each asVariableName ] separatedBy: [ stream nextPut: ',' ]. stream nextPutAll: '){'; lf. aBlock value. stream nextPutAll: '})' ! +nextPutContextFor: aMethod during: aBlock + self + nextPutAll: 'return smalltalk.withContext(function(', aMethod scope alias, ') { '; + nextPutAll: String cr. + aBlock value. + + self + nextPutAll: '}, function(', aMethod scope alias, ') {', aMethod scope alias; + nextPutAll: '.fill(self,', aMethod selector asJavascript, ',{'. + + aMethod locals + do: [ :each | + self + nextPutAll: each asVariableName; + nextPutAll: ':'; + nextPutAll: each asVariableName] + separatedBy: [ self nextPutAll: ',' ]. + + self + nextPutAll: '}, '; + nextPutAll: aMethod theClass asJavascript; + nextPutAll: ')})' +! + nextPutFunctionWith: aBlock arguments: anArray stream nextPutAll: 'fn: function('. anArray do: [ :each | stream nextPutAll: each asVariableName ] separatedBy: [ stream nextPut: ',' ]. @@ -998,16 +1124,16 @@ nextPutMethodDeclaration: aMethod with: aBlock stream nextPutAll: 'smalltalk.method({'; lf; nextPutAll: 'selector: "', aMethod selector, '",'; lf; - nextPutAll: 'source: ', aMethod source asJavascript, ',';lf. + nextPutAll: 'source: ', aMethod source asJavascript, ',';lf. aBlock value. stream nextPutAll: ',', String lf, 'messageSends: '; nextPutAll: aMethod messageSends asArray asJavascript, ','; lf; - nextPutAll: 'args: ', (aMethod arguments collect: [ :each | each value ]) asArray asJavascript, ','; lf; + nextPutAll: 'args: ', (aMethod arguments collect: [ :each | each value ]) asArray asJavascript, ','; lf; nextPutAll: 'referencedClasses: ['. aMethod classReferences do: [:each | stream nextPutAll: each asJavascript] separatedBy: [stream nextPutAll: ',']. stream @@ -1038,20 +1164,10 @@ nextPutReturnWith: aBlock self nextPutReturn. aBlock value ! -nextPutSendTo: receiver selector: selector arguments: arguments - stream nextPutAll: 'smalltalk.send('. - receiver emitOn: self. - stream nextPutAll: ',"', selector asSelector, '",['. - arguments - do: [ :each | each emitOn: self ] - separatedBy: [ stream nextPutAll: ',' ]. - stream nextPutAll: '])' -! - nextPutSequenceWith: aBlock "stream nextPutAll: 'switch(smalltalk.thisContext.pc){'; lf." aBlock value. "stream @@ -1072,9 +1188,11 @@ nextPutVar: aString stream nextPutAll: 'var ', aString, ';'; lf ! nextPutVars: aCollection + aCollection ifEmpty: [ ^self ]. + stream nextPutAll: 'var '. aCollection do: [ :each | stream nextPutAll: each ] separatedBy: [ stream nextPutAll: ',' ]. stream nextPutAll: ';'; lf