Browse Source

Merge branch 'dag'

# Conflicts:
#	src/Compiler-AST.js
#	src/Compiler-AST.st
#	src/Compiler-Interpreter.st
Herbert Vojčík 7 years ago
parent
commit
bf8aa70843

+ 2 - 1
API-CHANGES.txt

@@ -1,7 +1,8 @@
 0.18.0:
 
 * Remove class RethrowErrorHandler (hack for cli before 0.12.3).
-* Some internal API changes in Compiler-*.
+* Add Kernel-Dag package with abstract DAG-node and DAG-node visitor.
+* Some internal API changes in Compiler-* (including the move to DAG-node).
 
 - Object >>
   - throw:

+ 1 - 1
CHANGELOG

@@ -1,4 +1,4 @@
-?? October 2016 - Release 0.18.0
+?? November 2016 - Release 0.18.0
 ===================================
 
 * Remove some old internal pieces.

File diff suppressed because it is too large
+ 117 - 337
src/Compiler-AST.js


+ 79 - 138
src/Compiler-AST.st

@@ -1,30 +1,15 @@
 Smalltalk createPackage: 'Compiler-AST'!
-Object subclass: #Node
-	instanceVariableNames: 'parent position source nodes shouldBeAliased'
+DagParentNode subclass: #ASTNode
+	instanceVariableNames: 'parent position source shouldBeAliased'
 	package: 'Compiler-AST'!
-!Node commentStamp!
+!ASTNode commentStamp!
 I am the abstract root class of the abstract syntax tree.
 
 Concrete classes should implement `#accept:` to allow visiting.
 
 `position` holds a point containing line and column number of the symbol location in the original source file.!
 
-!Node methodsFor: 'accessing'!
-
-addNode: aNode
-	self nodes add: aNode.
-	aNode parent: self
-!
-
-allNodes
-	| allNodes |
-	
-	allNodes := self nodes asSet.
-	self nodes do: [ :each | 
-		allNodes addAll: each allNodes ].
-	
-	^ allNodes
-!
+!ASTNode methodsFor: 'accessing'!
 
 location: aLocation
 	self position: aLocation start line @ aLocation start column
@@ -42,7 +27,7 @@ navigationNodeAt: aPoint ifAbsent: aBlock
 	
 	| children |
 	
-	children := self allNodes select: [ :each | 
+	children := self allDagChildren select: [ :each | 
 		each isNavigationNode and: [ each inPosition: aPoint ] ].
 	
 	children ifEmpty: [ ^ aBlock value ].
@@ -52,10 +37,6 @@ navigationNodeAt: aPoint ifAbsent: aBlock
 		(b positionStart dist: aPoint) ]) first
 !
 
-nodes
-	^ nodes ifNil: [ nodes := Array new ]
-!
-
 parent
 	^ parent
 !
@@ -103,21 +84,7 @@ source: aString
 	source := aString
 ! !
 
-!Node methodsFor: 'building'!
-
-nodes: aCollection
-	nodes := aCollection.
-	aCollection do: [ :each | each parent: self ]
-! !
-
-!Node methodsFor: 'copying'!
-
-postCopy
-	super postCopy.
-	self nodes do: [ :each | each parent: self ]
-! !
-
-!Node methodsFor: 'testing'!
+!ASTNode methodsFor: 'testing'!
 
 inPosition: aPoint
 	^ (self positionStart <= aPoint and: [
@@ -154,10 +121,6 @@ isNavigationNode
 	^ false
 !
 
-isNode
-	^ true
-!
-
 isReturnNode
 	^ false
 !
@@ -189,18 +152,12 @@ requiresSmalltalkContext
 	If no node requires a context, the method will be compiled without one.
 	See `IRJSTranslator` and `JSStream` for context creation"
 	
-	^ (self nodes 
+	^ (self dagChildren 
 		detect: [ :each | each requiresSmalltalkContext ]
 		ifNone: [ nil ]) notNil
 ! !
 
-!Node methodsFor: 'visiting'!
-
-accept: aVisitor
-	^ aVisitor visitNode: self
-! !
-
-Node subclass: #AssignmentNode
+ASTNode subclass: #AssignmentNode
 	instanceVariableNames: 'left right'
 	package: 'Compiler-AST'!
 !AssignmentNode commentStamp!
@@ -208,17 +165,16 @@ I represent an assignment node.!
 
 !AssignmentNode methodsFor: 'accessing'!
 
+dagChildren
+	^ Array with: self left with: self right
+!
+
 left
 	^ left
 !
 
 left: aNode
-	left := aNode.
-	aNode parent: self
-!
-
-nodes
-	^ Array with: self left with: self right
+	left := aNode
 !
 
 right
@@ -226,8 +182,7 @@ right
 !
 
 right: aNode
-	right := aNode.
-	aNode parent: self
+	right := aNode
 ! !
 
 !AssignmentNode methodsFor: 'testing'!
@@ -238,11 +193,11 @@ isAssignmentNode
 
 !AssignmentNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitAssignmentNode: self
 ! !
 
-Node subclass: #BlockNode
+ASTNode subclass: #BlockNode
 	instanceVariableNames: 'parameters scope'
 	package: 'Compiler-AST'!
 !BlockNode commentStamp!
@@ -274,11 +229,11 @@ isBlockNode
 
 !BlockNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitBlockNode: self
 ! !
 
-Node subclass: #CascadeNode
+ASTNode subclass: #CascadeNode
 	instanceVariableNames: 'receiver'
 	package: 'Compiler-AST'!
 !CascadeNode commentStamp!
@@ -302,11 +257,11 @@ isCascadeNode
 
 !CascadeNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitCascadeNode: self
 ! !
 
-Node subclass: #DynamicArrayNode
+ASTNode subclass: #DynamicArrayNode
 	instanceVariableNames: ''
 	package: 'Compiler-AST'!
 !DynamicArrayNode commentStamp!
@@ -314,11 +269,11 @@ I represent an dynamic array node.!
 
 !DynamicArrayNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitDynamicArrayNode: self
 ! !
 
-Node subclass: #DynamicDictionaryNode
+ASTNode subclass: #DynamicDictionaryNode
 	instanceVariableNames: ''
 	package: 'Compiler-AST'!
 !DynamicDictionaryNode commentStamp!
@@ -326,11 +281,11 @@ I represent an dynamic dictionary node.!
 
 !DynamicDictionaryNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitDynamicDictionaryNode: self
 ! !
 
-Node subclass: #JSStatementNode
+ASTNode subclass: #JSStatementNode
 	instanceVariableNames: ''
 	package: 'Compiler-AST'!
 !JSStatementNode commentStamp!
@@ -348,11 +303,11 @@ requiresSmalltalkContext
 
 !JSStatementNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitJSStatementNode: self
 ! !
 
-Node subclass: #MethodNode
+ASTNode subclass: #MethodNode
 	instanceVariableNames: 'selector arguments source scope classReferences sendIndexes'
 	package: 'Compiler-AST'!
 !MethodNode commentStamp!
@@ -411,7 +366,7 @@ sendIndexes: aDictionary
 !
 
 sequenceNode
-	self nodes do: [ :each |
+	self dagChildren do: [ :each |
 		each isSequenceNode ifTrue: [ ^ each ] ].
 		
 	^ nil
@@ -427,11 +382,11 @@ source: aString
 
 !MethodNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitMethodNode: self
 ! !
 
-Node subclass: #ReturnNode
+ASTNode subclass: #ReturnNode
 	instanceVariableNames: 'scope'
 	package: 'Compiler-AST'!
 !ReturnNode commentStamp!
@@ -459,11 +414,11 @@ nonLocalReturn
 
 !ReturnNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitReturnNode: self
 ! !
 
-Node subclass: #SendNode
+ASTNode subclass: #SendNode
 	instanceVariableNames: 'selector arguments receiver index shouldBeInlined'
 	package: 'Compiler-AST'!
 !SendNode commentStamp!
@@ -476,19 +431,14 @@ arguments
 !
 
 arguments: aCollection
-	arguments := aCollection.
-	aCollection do: [ :each | each parent: self ]
+	arguments := aCollection
 !
 
-cascadeNodeWithMessages: aCollection
-	| first |
-	first := SendNode new
-		selector: self selector;
-		arguments: self arguments;
-		yourself.
-	^ CascadeNode new
-		receiver: self receiver;
-		nodes: (Array with: first), aCollection;
+dagChildren
+	self receiver ifNil: [ ^ self arguments copy ].
+	
+	^ (Array with: self receiver)
+		addAll: self arguments;
 		yourself
 !
 
@@ -504,22 +454,12 @@ navigationLink
 	^ self selector
 !
 
-nodes
-	self receiver ifNil: [ ^ self arguments copy ].
-	
-	^ (Array with: self receiver)
-		addAll: self arguments;
-		yourself
-!
-
 receiver
 	^ receiver
 !
 
 receiver: aNode
-	receiver := aNode.
-	aNode isNode ifTrue: [
-		aNode parent: self ]
+	receiver := aNode
 !
 
 selector
@@ -572,11 +512,11 @@ requiresSmalltalkContext
 
 !SendNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitSendNode: self
 ! !
 
-Node subclass: #SequenceNode
+ASTNode subclass: #SequenceNode
 	instanceVariableNames: 'temps scope'
 	package: 'Compiler-AST'!
 !SequenceNode commentStamp!
@@ -606,7 +546,7 @@ asBlockSequenceNode
 	^ BlockSequenceNode new
 		position: self position;
 		source: self source;
-		nodes: self nodes;
+		dagChildren: self dagChildren;
 		temps: self temps;
 		yourself
 ! !
@@ -619,7 +559,7 @@ isSequenceNode
 
 !SequenceNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitSequenceNode: self
 ! !
 
@@ -637,11 +577,11 @@ isBlockSequenceNode
 
 !BlockSequenceNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitBlockSequenceNode: self
 ! !
 
-Node subclass: #ValueNode
+ASTNode subclass: #ValueNode
 	instanceVariableNames: 'value'
 	package: 'Compiler-AST'!
 !ValueNode commentStamp!
@@ -669,7 +609,7 @@ isValueNode
 
 !ValueNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitValueNode: self
 ! !
 
@@ -734,11 +674,27 @@ isVariableNode
 
 !VariableNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitVariableNode: self
 ! !
 
-Object subclass: #NodeVisitor
+PathDagVisitor subclass: #ParentFakingPathDagVisitor
+	instanceVariableNames: 'setParentSelector'
+	package: 'Compiler-AST'!
+!ParentFakingPathDagVisitor commentStamp!
+I am base class of `DagNode` visitor.
+
+I hold the path of ancestors up to actual node
+in `self path`.!
+
+!ParentFakingPathDagVisitor methodsFor: 'visiting'!
+
+visit: aNode
+	self path ifNotEmpty: [ :p | aNode parent: p last ].
+	^ super visit: aNode
+! !
+
+ParentFakingPathDagVisitor subclass: #NodeVisitor
 	instanceVariableNames: ''
 	package: 'Compiler-AST'!
 !NodeVisitor commentStamp!
@@ -746,20 +702,12 @@ I am the abstract super class of all AST node visitors.!
 
 !NodeVisitor methodsFor: 'visiting'!
 
-visit: aNode
-	^ aNode accept: self
-!
-
-visitAll: aCollection
-	^ aCollection collect: [ :each | self visit: each ]
-!
-
 visitAssignmentNode: aNode
-	^ self visitNode: aNode
+	^ self visitDagNode: aNode
 !
 
 visitBlockNode: aNode
-	^ self visitNode: aNode
+	^ self visitDagNode: aNode
 !
 
 visitBlockSequenceNode: aNode
@@ -767,48 +715,47 @@ visitBlockSequenceNode: aNode
 !
 
 visitCascadeNode: aNode
-	^ self visitNode: aNode
+	^ self visitDagNode: aNode
+!
+
+visitDagNode: aNode
+	^ self visitDagNodeVariantSimple: aNode
 !
 
 visitDynamicArrayNode: aNode
-	^ self visitNode: aNode
+	^ self visitDagNode: aNode
 !
 
 visitDynamicDictionaryNode: aNode
-	^ self visitNode: aNode
+	^ self visitDagNode: aNode
 !
 
 visitJSStatementNode: aNode
-	^ self visitNode: aNode
+	^ self visitDagNode: aNode
 !
 
 visitMethodNode: aNode
-	^ self visitNode: aNode
-!
-
-visitNode: aNode
-	self visitAll: aNode nodes.
-	^ aNode
+	^ self visitDagNode: aNode
 !
 
 visitReturnNode: aNode
-	^ self visitNode: aNode
+	^ self visitDagNode: aNode
 !
 
 visitSendNode: aNode
-	^ self visitNode: aNode
+	^ self visitDagNode: aNode
 !
 
 visitSequenceNode: aNode
-	^ self visitNode: aNode
+	^ self visitDagNode: aNode
 !
 
 visitValueNode: aNode
-	^ self visitNode: aNode
+	^ self visitDagNode: aNode
 !
 
 visitVariableNode: aNode
-	^ self visitNode: aNode
+	^ self visitDagNode: aNode
 ! !
 
 !CompiledMethod methodsFor: '*Compiler-AST'!
@@ -819,9 +766,3 @@ ast
 	^ Smalltalk parse: self source
 ! !
 
-!Object methodsFor: '*Compiler-AST'!
-
-isNode
-	^ false
-! !
-

File diff suppressed because it is too large
+ 135 - 188
src/Compiler-IR.js


+ 78 - 93
src/Compiler-IR.st

@@ -121,7 +121,7 @@ visitBlockNode: aNode
 			name: each name;
 			scope: aNode scope;
 			yourself) ].
-	aNode nodes do: [ :each | closure add: (self visit: each) ].
+	aNode dagChildren do: [ :each | closure add: (self visit: each) ].
 	^ closure
 !
 
@@ -129,12 +129,12 @@ visitBlockSequenceNode: aNode
 	^ self
 		withSequence: IRBlockSequence new
 		do: [
-			aNode nodes ifNotEmpty: [
-				aNode nodes allButLast do: [ :each |
+			aNode dagChildren ifNotEmpty: [
+				aNode dagChildren allButLast do: [ :each |
 					self sequence add: (self visitOrAlias: each) ].
-				aNode nodes last isReturnNode
-					ifFalse: [ self sequence add: (IRBlockReturn new add: (self visitOrAlias: aNode nodes last); yourself) ]
-					ifTrue: [ self sequence add: (self visitOrAlias: aNode nodes last) ] ]]
+				aNode dagChildren last isReturnNode
+					ifFalse: [ self sequence add: (IRBlockReturn new add: (self visitOrAlias: aNode dagChildren last); yourself) ]
+					ifTrue: [ self sequence add: (self visitOrAlias: aNode dagChildren last) ] ]]
 !
 
 visitCascadeNode: aNode
@@ -144,25 +144,25 @@ visitCascadeNode: aNode
 		| alias |
 		alias := self alias: receiver.
 		receiver := VariableNode new binding: alias variable ].
-	aNode nodes do: [ :each | each receiver: receiver ].
+	aNode dagChildren do: [ :each | each receiver: receiver ].
 
-	aNode nodes allButLast do: [ :each |
+	aNode dagChildren allButLast do: [ :each |
 		self sequence add: (self visit: each) ].
 
-	^ self visitOrAlias: aNode nodes last
+	^ self visitOrAlias: aNode dagChildren last
 !
 
 visitDynamicArrayNode: aNode
 	| array |
 	array := IRDynamicArray new.
-	(self aliasTemporally: aNode nodes) do: [ :each | array add: each ].
+	(self aliasTemporally: aNode dagChildren) do: [ :each | array add: each ].
 	^ array
 !
 
 visitDynamicDictionaryNode: aNode
 	| dictionary |
 	dictionary := IRDynamicDictionary new.
-	(self aliasTemporally: aNode nodes) do: [ :each | dictionary add: each ].
+	(self aliasTemporally: aNode dagChildren) do: [ :each | dictionary add: each ].
 	^ dictionary
 !
 
@@ -191,7 +191,7 @@ visitMethodNode: aNode
 			scope: aNode scope;
 			yourself) ].
 
-	aNode nodes do: [ :each | self method add: (self visit: each) ].
+	aNode dagChildren do: [ :each | self method add: (self visit: each) ].
 
 	aNode scope hasLocalReturn ifFalse: [self method
 		add: (IRReturn new
@@ -216,7 +216,7 @@ visitReturnNode: aNode
 		ifTrue: [ IRNonLocalReturn new ]
 		ifFalse: [ IRReturn new ].
 	return scope: aNode scope.
-	aNode nodes do: [ :each |
+	aNode dagChildren do: [ :each |
 		return add: (self visitOrAlias: each) ].
 	^ return
 !
@@ -228,7 +228,7 @@ visitSendNode: aNode
 		selector: aNode selector;
 		index: aNode index.
 	
-	(self aliasTemporally: aNode nodes) do: [ :each | send add: each ].
+	(self aliasTemporally: aNode dagChildren) do: [ :each | send add: each ].
 
 	^ send
 !
@@ -237,7 +237,7 @@ visitSequenceNode: aNode
 	^ self
 		withSequence: IRSequence new
 		do: [
-			aNode nodes do: [ :each | | instruction |
+			aNode dagChildren do: [ :each | | instruction |
 				instruction := self visitOrAlias: each.
 				instruction isVariable ifFalse: [
 					self sequence add: instruction ] ]]
@@ -255,8 +255,8 @@ visitVariableNode: aNode
 		yourself
 ! !
 
-Object subclass: #IRInstruction
-	instanceVariableNames: 'parent instructions'
+DagParentNode subclass: #IRInstruction
+	instanceVariableNames: 'parent'
 	package: 'Compiler-IR'!
 !IRInstruction commentStamp!
 I am the abstract root class of the IR (intermediate representation) instructions class hierarchy.
@@ -264,10 +264,6 @@ The IR graph is used to emit JavaScript code using a JSStream.!
 
 !IRInstruction methodsFor: 'accessing'!
 
-instructions
-	^ instructions ifNil: [ instructions := OrderedCollection new ]
-!
-
 method
 	^ self parent method
 !
@@ -289,17 +285,17 @@ scope
 
 add: anObject
 	anObject parent: self.
-	^ self instructions add: anObject
+	^ self dagChildren add: anObject
 !
 
 remove: anIRInstruction
-	self instructions remove: anIRInstruction
+	self dagChildren remove: anIRInstruction
 !
 
 replace: anIRInstruction with: anotherIRInstruction
 	anotherIRInstruction parent: self.
-	self instructions
-		at: (self instructions indexOf: anIRInstruction)
+	self dagChildren
+		at: (self dagChildren indexOf: anIRInstruction)
 		put: anotherIRInstruction
 !
 
@@ -345,12 +341,6 @@ yieldsValue
 	^ true
 ! !
 
-!IRInstruction methodsFor: 'visiting'!
-
-accept: aVisitor
-	^ aVisitor visitIRInstruction: self
-! !
-
 !IRInstruction class methodsFor: 'instance creation'!
 
 on: aBuilder
@@ -366,16 +356,16 @@ IRInstruction subclass: #IRAssignment
 !IRAssignment methodsFor: 'accessing'!
 
 left
-	^ self instructions first
+	^ self dagChildren first
 !
 
 right
-	^ self instructions last
+	^ self dagChildren last
 ! !
 
 !IRAssignment methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitIRAssignment: self
 ! !
 
@@ -385,7 +375,7 @@ IRInstruction subclass: #IRDynamicArray
 
 !IRDynamicArray methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitIRDynamicArray: self
 ! !
 
@@ -395,7 +385,7 @@ IRInstruction subclass: #IRDynamicDictionary
 
 !IRDynamicDictionary methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitIRDynamicDictionary: self
 ! !
 
@@ -447,7 +437,7 @@ scope: aScope
 !
 
 tempDeclarations
-	^ self instructions select: [ :each |
+	^ self dagChildren select: [ :each |
 		each isTempDeclaration ]
 ! !
 
@@ -458,7 +448,7 @@ IRClosureInstruction subclass: #IRClosure
 !IRClosure methodsFor: 'accessing'!
 
 sequence
-	^ self instructions last
+	^ self dagChildren last
 ! !
 
 !IRClosure methodsFor: 'testing'!
@@ -469,7 +459,7 @@ isClosure
 
 !IRClosure methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitIRClosure: self
 ! !
 
@@ -541,7 +531,7 @@ isMethod
 
 !IRMethod methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitIRMethod: self
 ! !
 
@@ -554,7 +544,7 @@ I am a local return instruction.!
 !IRReturn methodsFor: 'accessing'!
 
 expression
-	^ self instructions single
+	^ self dagChildren single
 !
 
 scope
@@ -569,7 +559,7 @@ yieldsValue
 
 !IRReturn methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitIRReturn: self
 ! !
 
@@ -581,7 +571,7 @@ Smalltalk blocks return their last statement. I am a implicit block return instr
 
 !IRBlockReturn methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitIRBlockReturn: self
 ! !
 
@@ -596,7 +586,7 @@ See `IRNonLocalReturnHandling` class.!
 
 !IRNonLocalReturn methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitIRNonLocalReturn: self
 ! !
 
@@ -622,7 +612,7 @@ isTempDeclaration
 
 !IRTempDeclaration methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitIRTempDeclaration: self
 ! !
 
@@ -635,7 +625,7 @@ I am a message send instruction.!
 !IRSend methodsFor: 'accessing'!
 
 arguments
-	^ self instructions allButFirst
+	^ self dagChildren allButFirst
 !
 
 index
@@ -647,7 +637,7 @@ index: anInteger
 !
 
 receiver
-	^ self instructions first
+	^ self dagChildren first
 !
 
 selector
@@ -672,7 +662,7 @@ isSuperSend
 
 !IRSend methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitIRSend: self
 ! !
 
@@ -688,7 +678,7 @@ isSequence
 
 !IRSequence methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitIRSequence: self
 ! !
 
@@ -698,7 +688,7 @@ IRSequence subclass: #IRBlockSequence
 
 !IRBlockSequence methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitIRBlockSequence: self
 ! !
 
@@ -726,7 +716,7 @@ needsBoxingAsReceiver
 
 !IRValue methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitIRValue: self
 ! !
 
@@ -758,7 +748,7 @@ needsBoxingAsReceiver
 
 !IRVariable methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitIRVariable: self
 ! !
 
@@ -778,22 +768,22 @@ source: aString
 
 !IRVerbatim methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitIRVerbatim: self
 ! !
 
-Object subclass: #IRVisitor
+ParentFakingPathDagVisitor subclass: #IRVisitor
 	instanceVariableNames: ''
 	package: 'Compiler-IR'!
 
 !IRVisitor methodsFor: 'visiting'!
 
-visit: anIRInstruction
-	^ anIRInstruction accept: self
+visitDagNode: aNode
+	^ self visitDagNodeVariantSimple: aNode
 !
 
 visitIRAssignment: anIRAssignment
-	^ self visitIRInstruction: anIRAssignment
+	^ self visitDagNode: anIRAssignment
 !
 
 visitIRBlockReturn: anIRBlockReturn
@@ -805,15 +795,15 @@ visitIRBlockSequence: anIRBlockSequence
 !
 
 visitIRClosure: anIRClosure
-	^ self visitIRInstruction: anIRClosure
+	^ self visitDagNode: anIRClosure
 !
 
 visitIRDynamicArray: anIRDynamicArray
-	^ self visitIRInstruction: anIRDynamicArray
+	^ self visitDagNode: anIRDynamicArray
 !
 
 visitIRDynamicDictionary: anIRDynamicDictionary
-	^ self visitIRInstruction: anIRDynamicDictionary
+	^ self visitDagNode: anIRDynamicDictionary
 !
 
 visitIRInlinedClosure: anIRInlinedClosure
@@ -824,49 +814,44 @@ visitIRInlinedSequence: anIRInlinedSequence
 	^ self visitIRSequence: anIRInlinedSequence
 !
 
-visitIRInstruction: anIRInstruction
-	anIRInstruction instructions do: [ :each | self visit: each ].
-	^ anIRInstruction
-!
-
 visitIRMethod: anIRMethod
-	^ self visitIRInstruction: anIRMethod
+	^ self visitDagNode: anIRMethod
 !
 
 visitIRNonLocalReturn: anIRNonLocalReturn
-	^ self visitIRInstruction: anIRNonLocalReturn
+	^ self visitDagNode: anIRNonLocalReturn
 !
 
 visitIRNonLocalReturnHandling: anIRNonLocalReturnHandling
-	^ self visitIRInstruction: anIRNonLocalReturnHandling
+	^ self visitDagNode: anIRNonLocalReturnHandling
 !
 
 visitIRReturn: anIRReturn
-	^ self visitIRInstruction: anIRReturn
+	^ self visitDagNode: anIRReturn
 !
 
 visitIRSend: anIRSend
-	^ self visitIRInstruction: anIRSend
+	^ self visitDagNode: anIRSend
 !
 
 visitIRSequence: anIRSequence
-	^ self visitIRInstruction: anIRSequence
+	^ self visitDagNode: anIRSequence
 !
 
 visitIRTempDeclaration: anIRTempDeclaration
-	^ self visitIRInstruction: anIRTempDeclaration
+	^ self visitDagNode: anIRTempDeclaration
 !
 
 visitIRValue: anIRValue
-	^ self visitIRInstruction: anIRValue
+	^ self visitDagNode: anIRValue
 !
 
 visitIRVariable: anIRVariable
-	^ self visitIRInstruction: anIRVariable
+	^ self visitDagNode: anIRVariable
 !
 
 visitIRVerbatim: anIRVerbatim
-	^ self visitIRInstruction: anIRVerbatim
+	^ self visitDagNode: anIRVerbatim
 ! !
 
 IRVisitor subclass: #IRJSTranslator
@@ -923,13 +908,13 @@ visitIRClosure: anIRClosure
 
 visitIRDynamicArray: anIRDynamicArray
 	self
-		visitInstructionList: anIRDynamicArray instructions
+		visitInstructionList: anIRDynamicArray dagChildren
 		enclosedBetween: '[' and: ']'
 !
 
 visitIRDynamicDictionary: anIRDynamicDictionary
 	self
-		visitInstructionList: anIRDynamicDictionary instructions
+		visitInstructionList: anIRDynamicDictionary dagChildren
 		enclosedBetween: '$globals.HashedCollection._newFromPairs_([' and: '])'
 !
 
@@ -977,7 +962,7 @@ visitIRSend: anIRSend
 
 visitIRSequence: anIRSequence
 	self stream nextPutSequenceWith: [
-		anIRSequence instructions do: [ :each |
+		anIRSequence dagChildren do: [ :each |
 			self stream nextPutStatementWith: (self visit: each) ] ]
 !
 
@@ -1265,6 +1250,21 @@ nextPutVars: aCollection
 		stream nextPutAll: ';'; lf ]
 ! !
 
+!ASTNode methodsFor: '*Compiler-IR'!
+
+isReferenced
+	"Answer true if the receiver is referenced by other nodes.
+	Do not take sequences or assignments into account"
+	
+	^ (self parent isSequenceNode or: [
+		self parent isAssignmentNode ]) not
+!
+
+subtreeNeedsAliasing
+	^ self shouldBeAliased or: [
+		self dagChildren anySatisfy: [ :each | each subtreeNeedsAliasing ] ]
+! !
+
 !AssignmentNode methodsFor: '*Compiler-IR'!
 
 shouldBeAliased
@@ -1289,21 +1289,6 @@ subtreeNeedsAliasing
 	^ self parent isSequenceNode not
 ! !
 
-!Node methodsFor: '*Compiler-IR'!
-
-isReferenced
-	"Answer true if the receiver is referenced by other nodes.
-	Do not take sequences or assignments into account"
-	
-	^ (self parent isSequenceNode or: [
-		self parent isAssignmentNode ]) not
-!
-
-subtreeNeedsAliasing
-	^ self shouldBeAliased or: [
-		self nodes anySatisfy: [ :each | each subtreeNeedsAliasing ] ]
-! !
-
 !SendNode methodsFor: '*Compiler-IR'!
 
 shouldBeAliased

+ 63 - 71
src/Compiler-Inlining.js

@@ -12,7 +12,7 @@ $globals.IRInlinedClosure.comment="I represent an inlined closure instruction.";
 //>>excludeEnd("ide");
 $core.addMethod(
 $core.method({
-selector: "accept:",
+selector: "acceptDagVisitor:",
 protocol: 'visiting',
 fn: function (aVisitor){
 var self=this;
@@ -22,12 +22,12 @@ return $core.withContext(function($ctx1) {
 $recv(aVisitor)._visitIRInlinedClosure_(self);
 return self;
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-}, function($ctx1) {$ctx1.fill(self,"accept:",{aVisitor:aVisitor},$globals.IRInlinedClosure)});
+}, function($ctx1) {$ctx1.fill(self,"acceptDagVisitor:",{aVisitor:aVisitor},$globals.IRInlinedClosure)});
 //>>excludeEnd("ctx");
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["aVisitor"],
-source: "accept: aVisitor\x0a\x09aVisitor visitIRInlinedClosure: self",
+source: "acceptDagVisitor: aVisitor\x0a\x09aVisitor visitIRInlinedClosure: self",
 referencedClasses: [],
 //>>excludeEnd("ide");
 messageSends: ["visitIRInlinedClosure:"]
@@ -60,7 +60,7 @@ $globals.IRInlinedSend.comment="I am the abstract super class of inlined message
 //>>excludeEnd("ide");
 $core.addMethod(
 $core.method({
-selector: "accept:",
+selector: "acceptDagVisitor:",
 protocol: 'visiting',
 fn: function (aVisitor){
 var self=this;
@@ -70,12 +70,12 @@ return $core.withContext(function($ctx1) {
 $recv(aVisitor)._visitInlinedSend_(self);
 return self;
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-}, function($ctx1) {$ctx1.fill(self,"accept:",{aVisitor:aVisitor},$globals.IRInlinedSend)});
+}, function($ctx1) {$ctx1.fill(self,"acceptDagVisitor:",{aVisitor:aVisitor},$globals.IRInlinedSend)});
 //>>excludeEnd("ctx");
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["aVisitor"],
-source: "accept: aVisitor\x0a\x09aVisitor visitInlinedSend: self",
+source: "acceptDagVisitor: aVisitor\x0a\x09aVisitor visitInlinedSend: self",
 referencedClasses: [],
 //>>excludeEnd("ide");
 messageSends: ["visitInlinedSend:"]
@@ -126,7 +126,7 @@ $globals.IRInlinedIfFalse.comment="I represent an inlined `#ifFalse:` message se
 //>>excludeEnd("ide");
 $core.addMethod(
 $core.method({
-selector: "accept:",
+selector: "acceptDagVisitor:",
 protocol: 'visiting',
 fn: function (aVisitor){
 var self=this;
@@ -136,12 +136,12 @@ return $core.withContext(function($ctx1) {
 $recv(aVisitor)._visitIRInlinedIfFalse_(self);
 return self;
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-}, function($ctx1) {$ctx1.fill(self,"accept:",{aVisitor:aVisitor},$globals.IRInlinedIfFalse)});
+}, function($ctx1) {$ctx1.fill(self,"acceptDagVisitor:",{aVisitor:aVisitor},$globals.IRInlinedIfFalse)});
 //>>excludeEnd("ctx");
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["aVisitor"],
-source: "accept: aVisitor\x0a\x09aVisitor visitIRInlinedIfFalse: self",
+source: "acceptDagVisitor: aVisitor\x0a\x09aVisitor visitIRInlinedIfFalse: self",
 referencedClasses: [],
 //>>excludeEnd("ide");
 messageSends: ["visitIRInlinedIfFalse:"]
@@ -156,7 +156,7 @@ $globals.IRInlinedIfNilIfNotNil.comment="I represent an inlined `#ifNil:ifNotNil
 //>>excludeEnd("ide");
 $core.addMethod(
 $core.method({
-selector: "accept:",
+selector: "acceptDagVisitor:",
 protocol: 'visiting',
 fn: function (aVisitor){
 var self=this;
@@ -166,12 +166,12 @@ return $core.withContext(function($ctx1) {
 $recv(aVisitor)._visitIRInlinedIfNilIfNotNil_(self);
 return self;
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-}, function($ctx1) {$ctx1.fill(self,"accept:",{aVisitor:aVisitor},$globals.IRInlinedIfNilIfNotNil)});
+}, function($ctx1) {$ctx1.fill(self,"acceptDagVisitor:",{aVisitor:aVisitor},$globals.IRInlinedIfNilIfNotNil)});
 //>>excludeEnd("ctx");
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["aVisitor"],
-source: "accept: aVisitor\x0a\x09aVisitor visitIRInlinedIfNilIfNotNil: self",
+source: "acceptDagVisitor: aVisitor\x0a\x09aVisitor visitIRInlinedIfNilIfNotNil: self",
 referencedClasses: [],
 //>>excludeEnd("ide");
 messageSends: ["visitIRInlinedIfNilIfNotNil:"]
@@ -256,7 +256,7 @@ $globals.IRInlinedIfTrue.comment="I represent an inlined `#ifTrue:` message send
 //>>excludeEnd("ide");
 $core.addMethod(
 $core.method({
-selector: "accept:",
+selector: "acceptDagVisitor:",
 protocol: 'visiting',
 fn: function (aVisitor){
 var self=this;
@@ -266,12 +266,12 @@ return $core.withContext(function($ctx1) {
 $recv(aVisitor)._visitIRInlinedIfTrue_(self);
 return self;
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-}, function($ctx1) {$ctx1.fill(self,"accept:",{aVisitor:aVisitor},$globals.IRInlinedIfTrue)});
+}, function($ctx1) {$ctx1.fill(self,"acceptDagVisitor:",{aVisitor:aVisitor},$globals.IRInlinedIfTrue)});
 //>>excludeEnd("ctx");
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["aVisitor"],
-source: "accept: aVisitor\x0a\x09aVisitor visitIRInlinedIfTrue: self",
+source: "acceptDagVisitor: aVisitor\x0a\x09aVisitor visitIRInlinedIfTrue: self",
 referencedClasses: [],
 //>>excludeEnd("ide");
 messageSends: ["visitIRInlinedIfTrue:"]
@@ -286,7 +286,7 @@ $globals.IRInlinedIfTrueIfFalse.comment="I represent an inlined `#ifTrue:ifFalse
 //>>excludeEnd("ide");
 $core.addMethod(
 $core.method({
-selector: "accept:",
+selector: "acceptDagVisitor:",
 protocol: 'visiting',
 fn: function (aVisitor){
 var self=this;
@@ -296,12 +296,12 @@ return $core.withContext(function($ctx1) {
 $recv(aVisitor)._visitIRInlinedIfTrueIfFalse_(self);
 return self;
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-}, function($ctx1) {$ctx1.fill(self,"accept:",{aVisitor:aVisitor},$globals.IRInlinedIfTrueIfFalse)});
+}, function($ctx1) {$ctx1.fill(self,"acceptDagVisitor:",{aVisitor:aVisitor},$globals.IRInlinedIfTrueIfFalse)});
 //>>excludeEnd("ctx");
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["aVisitor"],
-source: "accept: aVisitor\x0a\x09aVisitor visitIRInlinedIfTrueIfFalse: self",
+source: "acceptDagVisitor: aVisitor\x0a\x09aVisitor visitIRInlinedIfTrueIfFalse: self",
 referencedClasses: [],
 //>>excludeEnd("ide");
 messageSends: ["visitIRInlinedIfTrueIfFalse:"]
@@ -316,7 +316,7 @@ $globals.IRInlinedSequence.comment="I represent a (block) sequence inside an inl
 //>>excludeEnd("ide");
 $core.addMethod(
 $core.method({
-selector: "accept:",
+selector: "acceptDagVisitor:",
 protocol: 'visiting',
 fn: function (aVisitor){
 var self=this;
@@ -326,12 +326,12 @@ return $core.withContext(function($ctx1) {
 $recv(aVisitor)._visitIRInlinedSequence_(self);
 return self;
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-}, function($ctx1) {$ctx1.fill(self,"accept:",{aVisitor:aVisitor},$globals.IRInlinedSequence)});
+}, function($ctx1) {$ctx1.fill(self,"acceptDagVisitor:",{aVisitor:aVisitor},$globals.IRInlinedSequence)});
 //>>excludeEnd("ctx");
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["aVisitor"],
-source: "accept: aVisitor\x0a\x09aVisitor visitIRInlinedSequence: self",
+source: "acceptDagVisitor: aVisitor\x0a\x09aVisitor visitIRInlinedSequence: self",
 referencedClasses: [],
 //>>excludeEnd("ide");
 messageSends: ["visitIRInlinedSequence:"]
@@ -636,7 +636,7 @@ $6=$recv($globals.IRReturn)._new();
 $recv($6)._scope_($recv(anIRNonLocalReturn)._scope());
 localReturn=$recv($6)._yourself();
 localReturn;
-$recv($recv(anIRNonLocalReturn)._instructions())._do_((function(each){
+$recv($recv(anIRNonLocalReturn)._dagChildren())._do_((function(each){
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 return $core.withContext(function($ctx2) {
 //>>excludeEnd("ctx");
@@ -663,10 +663,10 @@ return $7;
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["anIRNonLocalReturn"],
-source: "visitIRNonLocalReturn: anIRNonLocalReturn\x0a\x09| localReturn |\x0a\x09anIRNonLocalReturn scope canInlineNonLocalReturns ifTrue: [\x0a\x09\x09anIRNonLocalReturn scope methodScope removeNonLocalReturn: anIRNonLocalReturn scope.\x0a\x09\x09localReturn := IRReturn new\x0a\x09\x09\x09scope: anIRNonLocalReturn scope;\x0a\x09\x09\x09yourself.\x0a\x09\x09anIRNonLocalReturn instructions do: [ :each |\x0a\x09\x09\x09localReturn add: each ].\x0a\x09\x09anIRNonLocalReturn replaceWith: localReturn.\x0a\x09\x09^ self visitIRReturn: localReturn ].\x0a\x09^ super visitIRNonLocalReturn: anIRNonLocalReturn",
+source: "visitIRNonLocalReturn: anIRNonLocalReturn\x0a\x09| localReturn |\x0a\x09anIRNonLocalReturn scope canInlineNonLocalReturns ifTrue: [\x0a\x09\x09anIRNonLocalReturn scope methodScope removeNonLocalReturn: anIRNonLocalReturn scope.\x0a\x09\x09localReturn := IRReturn new\x0a\x09\x09\x09scope: anIRNonLocalReturn scope;\x0a\x09\x09\x09yourself.\x0a\x09\x09anIRNonLocalReturn dagChildren do: [ :each |\x0a\x09\x09\x09localReturn add: each ].\x0a\x09\x09anIRNonLocalReturn replaceWith: localReturn.\x0a\x09\x09^ self visitIRReturn: localReturn ].\x0a\x09^ super visitIRNonLocalReturn: anIRNonLocalReturn",
 referencedClasses: ["IRReturn"],
 //>>excludeEnd("ide");
-messageSends: ["ifTrue:", "canInlineNonLocalReturns", "scope", "removeNonLocalReturn:", "methodScope", "scope:", "new", "yourself", "do:", "instructions", "add:", "replaceWith:", "visitIRReturn:", "visitIRNonLocalReturn:"]
+messageSends: ["ifTrue:", "canInlineNonLocalReturns", "scope", "removeNonLocalReturn:", "methodScope", "scope:", "new", "yourself", "do:", "dagChildren", "add:", "replaceWith:", "visitIRReturn:", "visitIRNonLocalReturn:"]
 }),
 $globals.IRInliner);
 
@@ -766,15 +766,7 @@ return $recv($recv(each)._name())._asVariableName();
 }, function($ctx2) {$ctx2.fillBlock({each:each},$ctx1,1)});
 //>>excludeEnd("ctx");
 })));
-$recv($recv(anIRInlinedClosure)._instructions())._do_((function(each){
-//>>excludeStart("ctx", pragmas.excludeDebugContexts);
-return $core.withContext(function($ctx2) {
-//>>excludeEnd("ctx");
-return self._visit_(each);
-//>>excludeStart("ctx", pragmas.excludeDebugContexts);
-}, function($ctx2) {$ctx2.fillBlock({each:each},$ctx1,2)});
-//>>excludeEnd("ctx");
-}));
+self._visitAll_($recv(anIRInlinedClosure)._dagChildren());
 return self;
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 }, function($ctx1) {$ctx1.fill(self,"visitIRInlinedClosure:",{anIRInlinedClosure:anIRInlinedClosure},$globals.IRInliningJSTranslator)});
@@ -782,10 +774,10 @@ return self;
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["anIRInlinedClosure"],
-source: "visitIRInlinedClosure: anIRInlinedClosure\x0a\x09self stream nextPutVars: (anIRInlinedClosure tempDeclarations collect: [ :each |\x0a\x09\x09each name asVariableName ]).\x0a\x09anIRInlinedClosure instructions do: [ :each |\x0a\x09\x09self visit: each ]",
+source: "visitIRInlinedClosure: anIRInlinedClosure\x0a\x09self stream nextPutVars: (anIRInlinedClosure tempDeclarations collect: [ :each |\x0a\x09\x09each name asVariableName ]).\x0a\x09self visitAll: anIRInlinedClosure dagChildren",
 referencedClasses: [],
 //>>excludeEnd("ide");
-messageSends: ["nextPutVars:", "stream", "collect:", "tempDeclarations", "asVariableName", "name", "do:", "instructions", "visit:"]
+messageSends: ["nextPutVars:", "stream", "collect:", "tempDeclarations", "asVariableName", "name", "visitAll:", "dagChildren"]
 }),
 $globals.IRInliningJSTranslator);
 
@@ -815,9 +807,9 @@ $recv($2)._nextPutAll_("!$core.assert(");
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx2.sendIdx["nextPutAll:"]=1;
 //>>excludeEnd("ctx");
-$4=$recv(anIRInlinedIfFalse)._instructions();
+$4=$recv(anIRInlinedIfFalse)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx2.sendIdx["instructions"]=1;
+$ctx2.sendIdx["dagChildren"]=1;
 //>>excludeEnd("ctx");
 $3=$recv($4)._first();
 self._visit_($3);
@@ -832,7 +824,7 @@ return $recv(self._stream())._nextPutAll_(")");
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 return $core.withContext(function($ctx2) {
 //>>excludeEnd("ctx");
-return self._visit_($recv($recv(anIRInlinedIfFalse)._instructions())._last());
+return self._visit_($recv($recv(anIRInlinedIfFalse)._dagChildren())._last());
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 }, function($ctx2) {$ctx2.fillBlock({},$ctx1,2)});
 //>>excludeEnd("ctx");
@@ -844,10 +836,10 @@ return self;
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["anIRInlinedIfFalse"],
-source: "visitIRInlinedIfFalse: anIRInlinedIfFalse\x0a\x09self stream nextPutIf: [\x0a\x09\x09self stream nextPutAll: '!$core.assert('.\x0a\x09\x09self visit: anIRInlinedIfFalse instructions first.\x0a\x09\x09self stream nextPutAll: ')' ]\x0a\x09\x09then: [ self visit: anIRInlinedIfFalse instructions last ]",
+source: "visitIRInlinedIfFalse: anIRInlinedIfFalse\x0a\x09self stream nextPutIf: [\x0a\x09\x09self stream nextPutAll: '!$core.assert('.\x0a\x09\x09self visit: anIRInlinedIfFalse dagChildren first.\x0a\x09\x09self stream nextPutAll: ')' ]\x0a\x09\x09then: [ self visit: anIRInlinedIfFalse dagChildren last ]",
 referencedClasses: [],
 //>>excludeEnd("ide");
-messageSends: ["nextPutIf:then:", "stream", "nextPutAll:", "visit:", "first", "instructions", "last"]
+messageSends: ["nextPutIf:then:", "stream", "nextPutAll:", "visit:", "first", "dagChildren", "last"]
 }),
 $globals.IRInliningJSTranslator);
 
@@ -888,9 +880,9 @@ $recv($2)._nextPutAll_($3);
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx2.sendIdx["nextPutAll:"]=1;
 //>>excludeEnd("ctx");
-$6=$recv(anIRInlinedIfNilIfNotNil)._instructions();
+$6=$recv(anIRInlinedIfNilIfNotNil)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx2.sendIdx["instructions"]=1;
+$ctx2.sendIdx["dagChildren"]=1;
 //>>excludeEnd("ctx");
 $5=$recv($6)._first();
 self._visit_($5);
@@ -910,9 +902,9 @@ return $recv($7)._nextPutAll_($8);
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 return $core.withContext(function($ctx2) {
 //>>excludeEnd("ctx");
-$10=$recv(anIRInlinedIfNilIfNotNil)._instructions();
+$10=$recv(anIRInlinedIfNilIfNotNil)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx2.sendIdx["instructions"]=2;
+$ctx2.sendIdx["dagChildren"]=2;
 //>>excludeEnd("ctx");
 $9=$recv($10)._second();
 return self._visit_($9);
@@ -926,7 +918,7 @@ $ctx2.sendIdx["visit:"]=2;
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 return $core.withContext(function($ctx2) {
 //>>excludeEnd("ctx");
-return self._visit_($recv($recv(anIRInlinedIfNilIfNotNil)._instructions())._third());
+return self._visit_($recv($recv(anIRInlinedIfNilIfNotNil)._dagChildren())._third());
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 }, function($ctx2) {$ctx2.fillBlock({},$ctx1,3)});
 //>>excludeEnd("ctx");
@@ -938,10 +930,10 @@ return self;
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["anIRInlinedIfNilIfNotNil"],
-source: "visitIRInlinedIfNilIfNotNil: anIRInlinedIfNilIfNotNil\x0a\x09self stream\x0a\x09\x09nextPutIf: [\x0a\x09\x09\x09| recvVarName |\x0a\x09\x09\x09recvVarName := anIRInlinedIfNilIfNotNil receiverInternalVariableName.\x0a\x09\x09\x09self stream nextPutAll: '(', recvVarName, ' = '.\x0a\x09\x09\x09self visit: anIRInlinedIfNilIfNotNil instructions first.\x0a\x09\x09\x09self stream nextPutAll: ') == null || ', recvVarName, '.isNil' ]\x0a\x09\x09then: [ self visit: anIRInlinedIfNilIfNotNil instructions second ]\x0a\x09\x09else: [ self visit: anIRInlinedIfNilIfNotNil instructions third ]",
+source: "visitIRInlinedIfNilIfNotNil: anIRInlinedIfNilIfNotNil\x0a\x09self stream\x0a\x09\x09nextPutIf: [\x0a\x09\x09\x09| recvVarName |\x0a\x09\x09\x09recvVarName := anIRInlinedIfNilIfNotNil receiverInternalVariableName.\x0a\x09\x09\x09self stream nextPutAll: '(', recvVarName, ' = '.\x0a\x09\x09\x09self visit: anIRInlinedIfNilIfNotNil dagChildren first.\x0a\x09\x09\x09self stream nextPutAll: ') == null || ', recvVarName, '.isNil' ]\x0a\x09\x09then: [ self visit: anIRInlinedIfNilIfNotNil dagChildren second ]\x0a\x09\x09else: [ self visit: anIRInlinedIfNilIfNotNil dagChildren third ]",
 referencedClasses: [],
 //>>excludeEnd("ide");
-messageSends: ["nextPutIf:then:else:", "stream", "receiverInternalVariableName", "nextPutAll:", ",", "visit:", "first", "instructions", "second", "third"]
+messageSends: ["nextPutIf:then:else:", "stream", "receiverInternalVariableName", "nextPutAll:", ",", "visit:", "first", "dagChildren", "second", "third"]
 }),
 $globals.IRInliningJSTranslator);
 
@@ -971,9 +963,9 @@ $recv($2)._nextPutAll_("$core.assert(");
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx2.sendIdx["nextPutAll:"]=1;
 //>>excludeEnd("ctx");
-$4=$recv(anIRInlinedIfTrue)._instructions();
+$4=$recv(anIRInlinedIfTrue)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx2.sendIdx["instructions"]=1;
+$ctx2.sendIdx["dagChildren"]=1;
 //>>excludeEnd("ctx");
 $3=$recv($4)._first();
 self._visit_($3);
@@ -988,7 +980,7 @@ return $recv(self._stream())._nextPutAll_(")");
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 return $core.withContext(function($ctx2) {
 //>>excludeEnd("ctx");
-return self._visit_($recv($recv(anIRInlinedIfTrue)._instructions())._last());
+return self._visit_($recv($recv(anIRInlinedIfTrue)._dagChildren())._last());
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 }, function($ctx2) {$ctx2.fillBlock({},$ctx1,2)});
 //>>excludeEnd("ctx");
@@ -1000,10 +992,10 @@ return self;
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["anIRInlinedIfTrue"],
-source: "visitIRInlinedIfTrue: anIRInlinedIfTrue\x0a\x09self stream nextPutIf: [\x0a\x09\x09self stream nextPutAll: '$core.assert('.\x0a\x09\x09self visit: anIRInlinedIfTrue instructions first.\x0a\x09\x09self stream nextPutAll: ')' ]\x0a\x09\x09then: [ self visit: anIRInlinedIfTrue instructions last ]",
+source: "visitIRInlinedIfTrue: anIRInlinedIfTrue\x0a\x09self stream nextPutIf: [\x0a\x09\x09self stream nextPutAll: '$core.assert('.\x0a\x09\x09self visit: anIRInlinedIfTrue dagChildren first.\x0a\x09\x09self stream nextPutAll: ')' ]\x0a\x09\x09then: [ self visit: anIRInlinedIfTrue dagChildren last ]",
 referencedClasses: [],
 //>>excludeEnd("ide");
-messageSends: ["nextPutIf:then:", "stream", "nextPutAll:", "visit:", "first", "instructions", "last"]
+messageSends: ["nextPutIf:then:", "stream", "nextPutAll:", "visit:", "first", "dagChildren", "last"]
 }),
 $globals.IRInliningJSTranslator);
 
@@ -1033,9 +1025,9 @@ $recv($2)._nextPutAll_("$core.assert(");
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx2.sendIdx["nextPutAll:"]=1;
 //>>excludeEnd("ctx");
-$4=$recv(anIRInlinedIfTrueIfFalse)._instructions();
+$4=$recv(anIRInlinedIfTrueIfFalse)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx2.sendIdx["instructions"]=1;
+$ctx2.sendIdx["dagChildren"]=1;
 //>>excludeEnd("ctx");
 $3=$recv($4)._first();
 self._visit_($3);
@@ -1050,9 +1042,9 @@ return $recv(self._stream())._nextPutAll_(")");
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 return $core.withContext(function($ctx2) {
 //>>excludeEnd("ctx");
-$6=$recv(anIRInlinedIfTrueIfFalse)._instructions();
+$6=$recv(anIRInlinedIfTrueIfFalse)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx2.sendIdx["instructions"]=2;
+$ctx2.sendIdx["dagChildren"]=2;
 //>>excludeEnd("ctx");
 $5=$recv($6)._second();
 return self._visit_($5);
@@ -1066,7 +1058,7 @@ $ctx2.sendIdx["visit:"]=2;
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 return $core.withContext(function($ctx2) {
 //>>excludeEnd("ctx");
-return self._visit_($recv($recv(anIRInlinedIfTrueIfFalse)._instructions())._third());
+return self._visit_($recv($recv(anIRInlinedIfTrueIfFalse)._dagChildren())._third());
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 }, function($ctx2) {$ctx2.fillBlock({},$ctx1,3)});
 //>>excludeEnd("ctx");
@@ -1078,10 +1070,10 @@ return self;
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["anIRInlinedIfTrueIfFalse"],
-source: "visitIRInlinedIfTrueIfFalse: anIRInlinedIfTrueIfFalse\x0a\x09self stream\x0a\x09\x09nextPutIf: [\x0a\x09\x09\x09self stream nextPutAll: '$core.assert('.\x0a\x09\x09\x09self visit: anIRInlinedIfTrueIfFalse instructions first.\x0a\x09\x09\x09self stream nextPutAll: ')' ]\x0a\x09\x09then: [ self visit: anIRInlinedIfTrueIfFalse instructions second ]\x0a\x09\x09else: [ self visit: anIRInlinedIfTrueIfFalse instructions third ]",
+source: "visitIRInlinedIfTrueIfFalse: anIRInlinedIfTrueIfFalse\x0a\x09self stream\x0a\x09\x09nextPutIf: [\x0a\x09\x09\x09self stream nextPutAll: '$core.assert('.\x0a\x09\x09\x09self visit: anIRInlinedIfTrueIfFalse dagChildren first.\x0a\x09\x09\x09self stream nextPutAll: ')' ]\x0a\x09\x09then: [ self visit: anIRInlinedIfTrueIfFalse dagChildren second ]\x0a\x09\x09else: [ self visit: anIRInlinedIfTrueIfFalse dagChildren third ]",
 referencedClasses: [],
 //>>excludeEnd("ide");
-messageSends: ["nextPutIf:then:else:", "stream", "nextPutAll:", "visit:", "first", "instructions", "second", "third"]
+messageSends: ["nextPutIf:then:else:", "stream", "nextPutAll:", "visit:", "first", "dagChildren", "second", "third"]
 }),
 $globals.IRInliningJSTranslator);
 
@@ -1094,7 +1086,7 @@ var self=this;
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 return $core.withContext(function($ctx1) {
 //>>excludeEnd("ctx");
-$recv($recv(anIRInlinedSequence)._instructions())._do_((function(each){
+$recv($recv(anIRInlinedSequence)._dagChildren())._do_((function(each){
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 return $core.withContext(function($ctx2) {
 //>>excludeEnd("ctx");
@@ -1118,10 +1110,10 @@ return self;
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["anIRInlinedSequence"],
-source: "visitIRInlinedSequence: anIRInlinedSequence\x0a\x09anIRInlinedSequence instructions do: [ :each |\x0a\x09\x09self stream nextPutStatementWith: [ self visit: each ]]",
+source: "visitIRInlinedSequence: anIRInlinedSequence\x0a\x09anIRInlinedSequence dagChildren do: [ :each |\x0a\x09\x09self stream nextPutStatementWith: [ self visit: each ]]",
 referencedClasses: [],
 //>>excludeEnd("ide");
-messageSends: ["do:", "instructions", "nextPutStatementWith:", "stream", "visit:"]
+messageSends: ["do:", "dagChildren", "nextPutStatementWith:", "stream", "visit:"]
 }),
 $globals.IRInliningJSTranslator);
 
@@ -1490,7 +1482,7 @@ $recv(inlinedClosure)._add_(sequence);
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx1.sendIdx["add:"]=6;
 //>>excludeEnd("ctx");
-statements=$recv($recv(anIRClosure)._sequence())._instructions();
+statements=$recv($recv(anIRClosure)._sequence())._dagChildren();
 $recv(statements)._ifNotEmpty_((function(){
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 return $core.withContext(function($ctx2) {
@@ -1519,10 +1511,10 @@ return inlinedClosure;
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["anIRClosure"],
-source: "inlineClosure: anIRClosure\x0a\x09| inlinedClosure sequence statements |\x0a\x0a\x09inlinedClosure := self inlinedClosure.\x0a\x09inlinedClosure \x0a\x09\x09scope: anIRClosure scope;\x0a\x09\x09parent: anIRClosure parent.\x0a\x0a\x09\x22Add the possible temp declarations\x22\x0a\x09anIRClosure tempDeclarations do: [ :each |\x0a\x09\x09\x09inlinedClosure add: each ].\x0a\x0a\x09\x22Add a block sequence\x22\x0a\x09sequence := self inlinedSequence.\x0a\x0a\x09\x22Map the closure arguments to the receiver of the message send\x22\x0a\x09anIRClosure arguments do: [ :each |\x0a\x09\x09inlinedClosure add: (IRTempDeclaration new name: each; yourself).\x0a\x09\x09sequence add: (IRAssignment new\x0a\x09\x09\x09add: (IRVariable new variable: (AliasVar new scope: inlinedClosure scope; name: each; yourself));\x0a\x09\x09\x09add: (IRVariable new variable: (AliasVar new scope: inlinedClosure scope; name: '$receiver'; yourself));\x0a\x09\x09\x09yourself) ].\x0a\x09\x09\x09\x0a\x09\x22To ensure the correct order of the closure instructions: first the temps then the sequence\x22\x0a\x09inlinedClosure add: sequence.\x0a\x0a\x09\x22Get all the statements\x22\x0a\x09statements := anIRClosure sequence instructions.\x0a\x09\x0a\x09statements ifNotEmpty: [\x0a\x09\x09statements allButLast do: [ :each | sequence add: each ].\x0a\x0a\x09\x09\x22Inlined closures change local returns into result value itself\x22\x0a\x09\x09sequence add: statements last asInlinedBlockResult ].\x0a\x0a\x09^ inlinedClosure",
+source: "inlineClosure: anIRClosure\x0a\x09| inlinedClosure sequence statements |\x0a\x0a\x09inlinedClosure := self inlinedClosure.\x0a\x09inlinedClosure \x0a\x09\x09scope: anIRClosure scope;\x0a\x09\x09parent: anIRClosure parent.\x0a\x0a\x09\x22Add the possible temp declarations\x22\x0a\x09anIRClosure tempDeclarations do: [ :each |\x0a\x09\x09\x09inlinedClosure add: each ].\x0a\x0a\x09\x22Add a block sequence\x22\x0a\x09sequence := self inlinedSequence.\x0a\x0a\x09\x22Map the closure arguments to the receiver of the message send\x22\x0a\x09anIRClosure arguments do: [ :each |\x0a\x09\x09inlinedClosure add: (IRTempDeclaration new name: each; yourself).\x0a\x09\x09sequence add: (IRAssignment new\x0a\x09\x09\x09add: (IRVariable new variable: (AliasVar new scope: inlinedClosure scope; name: each; yourself));\x0a\x09\x09\x09add: (IRVariable new variable: (AliasVar new scope: inlinedClosure scope; name: '$receiver'; yourself));\x0a\x09\x09\x09yourself) ].\x0a\x09\x09\x09\x0a\x09\x22To ensure the correct order of the closure instructions: first the temps then the sequence\x22\x0a\x09inlinedClosure add: sequence.\x0a\x0a\x09\x22Get all the statements\x22\x0a\x09statements := anIRClosure sequence dagChildren.\x0a\x09\x0a\x09statements ifNotEmpty: [\x0a\x09\x09statements allButLast do: [ :each | sequence add: each ].\x0a\x0a\x09\x09\x22Inlined closures change local returns into result value itself\x22\x0a\x09\x09sequence add: statements last asInlinedBlockResult ].\x0a\x0a\x09^ inlinedClosure",
 referencedClasses: ["IRTempDeclaration", "IRAssignment", "IRVariable", "AliasVar"],
 //>>excludeEnd("ide");
-messageSends: ["inlinedClosure", "scope:", "scope", "parent:", "parent", "do:", "tempDeclarations", "add:", "inlinedSequence", "arguments", "name:", "new", "yourself", "variable:", "instructions", "sequence", "ifNotEmpty:", "allButLast", "asInlinedBlockResult", "last"]
+messageSends: ["inlinedClosure", "scope:", "scope", "parent:", "parent", "do:", "tempDeclarations", "add:", "inlinedSequence", "arguments", "name:", "new", "yourself", "variable:", "dagChildren", "sequence", "ifNotEmpty:", "allButLast", "asInlinedBlockResult", "last"]
 }),
 $globals.IRSendInliner);
 
@@ -1953,7 +1945,7 @@ $ctx1.supercall = true,
 $ctx1.supercall = false;
 //>>excludeEnd("ctx");;
 sequence=$recv(closure)._sequence();
-statements=$recv(sequence)._instructions();
+statements=$recv(sequence)._dagChildren();
 $recv(statements)._ifNotEmpty_((function(){
 var final;
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
@@ -1985,10 +1977,10 @@ return closure;
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["anIRClosure"],
-source: "inlineClosure: anIRClosure\x0a\x09| closure sequence statements |\x0a\x0a\x09closure := super inlineClosure: anIRClosure.\x0a\x09sequence := closure sequence.\x0a\x09statements := sequence instructions.\x0a\x09\x0a\x09statements ifNotEmpty: [\x0a\x09\x09| final |\x0a\x09\x09final := statements last.\x0a\x09\x09final yieldsValue ifTrue: [\x0a\x09\x09\x09sequence replace: final with: (IRAssignment new\x0a\x09\x09\x09\x09add: self target;\x0a\x09\x09\x09\x09add: final copy;\x0a\x09\x09\x09\x09yourself) ] ].\x0a\x0a\x09^ closure",
+source: "inlineClosure: anIRClosure\x0a\x09| closure sequence statements |\x0a\x0a\x09closure := super inlineClosure: anIRClosure.\x0a\x09sequence := closure sequence.\x0a\x09statements := sequence dagChildren.\x0a\x09\x0a\x09statements ifNotEmpty: [\x0a\x09\x09| final |\x0a\x09\x09final := statements last.\x0a\x09\x09final yieldsValue ifTrue: [\x0a\x09\x09\x09sequence replace: final with: (IRAssignment new\x0a\x09\x09\x09\x09add: self target;\x0a\x09\x09\x09\x09add: final copy;\x0a\x09\x09\x09\x09yourself) ] ].\x0a\x0a\x09^ closure",
 referencedClasses: ["IRAssignment"],
 //>>excludeEnd("ide");
-messageSends: ["inlineClosure:", "sequence", "instructions", "ifNotEmpty:", "last", "ifTrue:", "yieldsValue", "replace:with:", "add:", "new", "target", "copy", "yourself"]
+messageSends: ["inlineClosure:", "sequence", "dagChildren", "ifNotEmpty:", "last", "ifTrue:", "yieldsValue", "replace:with:", "add:", "new", "target", "copy", "yourself"]
 }),
 $globals.IRAssignmentInliner);
 
@@ -2055,7 +2047,7 @@ $ctx1.supercall = true,
 $ctx1.supercall = false;
 //>>excludeEnd("ctx");;
 sequence=$recv(closure)._sequence();
-statements=$recv(sequence)._instructions();
+statements=$recv(sequence)._dagChildren();
 $recv(statements)._ifNotEmpty_((function(){
 var final;
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
@@ -2083,10 +2075,10 @@ return closure;
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["anIRClosure"],
-source: "inlineClosure: anIRClosure\x0a\x09| closure sequence statements |\x0a\x0a\x09closure := super inlineClosure: anIRClosure.\x0a\x09sequence := closure sequence.\x0a\x09statements := sequence instructions.\x0a\x09\x0a\x09statements ifNotEmpty: [\x0a\x09\x09| final |\x0a\x09\x09final := statements last.\x0a\x09\x09final yieldsValue ifTrue: [\x0a\x09\x09\x09sequence replace: final with: (IRReturn new\x0a\x09\x09\x09\x09add: final copy;\x0a\x09\x09\x09\x09yourself) ] ].\x0a\x0a\x09^ closure",
+source: "inlineClosure: anIRClosure\x0a\x09| closure sequence statements |\x0a\x0a\x09closure := super inlineClosure: anIRClosure.\x0a\x09sequence := closure sequence.\x0a\x09statements := sequence dagChildren.\x0a\x09\x0a\x09statements ifNotEmpty: [\x0a\x09\x09| final |\x0a\x09\x09final := statements last.\x0a\x09\x09final yieldsValue ifTrue: [\x0a\x09\x09\x09sequence replace: final with: (IRReturn new\x0a\x09\x09\x09\x09add: final copy;\x0a\x09\x09\x09\x09yourself) ] ].\x0a\x0a\x09^ closure",
 referencedClasses: ["IRReturn"],
 //>>excludeEnd("ide");
-messageSends: ["inlineClosure:", "sequence", "instructions", "ifNotEmpty:", "last", "ifTrue:", "yieldsValue", "replace:with:", "add:", "new", "copy", "yourself"]
+messageSends: ["inlineClosure:", "sequence", "dagChildren", "ifNotEmpty:", "last", "ifTrue:", "yieldsValue", "replace:with:", "add:", "new", "copy", "yourself"]
 }),
 $globals.IRReturnInliner);
 

+ 23 - 24
src/Compiler-Inlining.st

@@ -13,7 +13,7 @@ isInlined
 
 !IRInlinedClosure methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	aVisitor visitIRInlinedClosure: self
 ! !
 
@@ -40,7 +40,7 @@ isInlined
 
 !IRInlinedSend methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	aVisitor visitInlinedSend: self
 ! !
 
@@ -52,7 +52,7 @@ I represent an inlined `#ifFalse:` message send instruction.!
 
 !IRInlinedIfFalse methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	aVisitor visitIRInlinedIfFalse: self
 ! !
 
@@ -80,7 +80,7 @@ receiverInternalVariableName
 
 !IRInlinedIfNilIfNotNil methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	aVisitor visitIRInlinedIfNilIfNotNil: self
 ! !
 
@@ -92,7 +92,7 @@ I represent an inlined `#ifTrue:` message send instruction.!
 
 !IRInlinedIfTrue methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	aVisitor visitIRInlinedIfTrue: self
 ! !
 
@@ -104,7 +104,7 @@ I represent an inlined `#ifTrue:ifFalse:` message send instruction.!
 
 !IRInlinedIfTrueIfFalse methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	aVisitor visitIRInlinedIfTrueIfFalse: self
 ! !
 
@@ -122,7 +122,7 @@ isInlined
 
 !IRInlinedSequence methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	aVisitor visitIRInlinedSequence: self
 ! !
 
@@ -188,7 +188,7 @@ visitIRNonLocalReturn: anIRNonLocalReturn
 		localReturn := IRReturn new
 			scope: anIRNonLocalReturn scope;
 			yourself.
-		anIRNonLocalReturn instructions do: [ :each |
+		anIRNonLocalReturn dagChildren do: [ :each |
 			localReturn add: each ].
 		anIRNonLocalReturn replaceWith: localReturn.
 		^ self visitIRReturn: localReturn ].
@@ -218,16 +218,15 @@ I am a specialized JavaScript translator able to write inlined IR instructions t
 visitIRInlinedClosure: anIRInlinedClosure
 	self stream nextPutVars: (anIRInlinedClosure tempDeclarations collect: [ :each |
 		each name asVariableName ]).
-	anIRInlinedClosure instructions do: [ :each |
-		self visit: each ]
+	self visitAll: anIRInlinedClosure dagChildren
 !
 
 visitIRInlinedIfFalse: anIRInlinedIfFalse
 	self stream nextPutIf: [
 		self stream nextPutAll: '!!$core.assert('.
-		self visit: anIRInlinedIfFalse instructions first.
+		self visit: anIRInlinedIfFalse dagChildren first.
 		self stream nextPutAll: ')' ]
-		then: [ self visit: anIRInlinedIfFalse instructions last ]
+		then: [ self visit: anIRInlinedIfFalse dagChildren last ]
 !
 
 visitIRInlinedIfNilIfNotNil: anIRInlinedIfNilIfNotNil
@@ -236,32 +235,32 @@ visitIRInlinedIfNilIfNotNil: anIRInlinedIfNilIfNotNil
 			| recvVarName |
 			recvVarName := anIRInlinedIfNilIfNotNil receiverInternalVariableName.
 			self stream nextPutAll: '(', recvVarName, ' = '.
-			self visit: anIRInlinedIfNilIfNotNil instructions first.
+			self visit: anIRInlinedIfNilIfNotNil dagChildren first.
 			self stream nextPutAll: ') == null || ', recvVarName, '.isNil' ]
-		then: [ self visit: anIRInlinedIfNilIfNotNil instructions second ]
-		else: [ self visit: anIRInlinedIfNilIfNotNil instructions third ]
+		then: [ self visit: anIRInlinedIfNilIfNotNil dagChildren second ]
+		else: [ self visit: anIRInlinedIfNilIfNotNil dagChildren third ]
 !
 
 visitIRInlinedIfTrue: anIRInlinedIfTrue
 	self stream nextPutIf: [
 		self stream nextPutAll: '$core.assert('.
-		self visit: anIRInlinedIfTrue instructions first.
+		self visit: anIRInlinedIfTrue dagChildren first.
 		self stream nextPutAll: ')' ]
-		then: [ self visit: anIRInlinedIfTrue instructions last ]
+		then: [ self visit: anIRInlinedIfTrue dagChildren last ]
 !
 
 visitIRInlinedIfTrueIfFalse: anIRInlinedIfTrueIfFalse
 	self stream
 		nextPutIf: [
 			self stream nextPutAll: '$core.assert('.
-			self visit: anIRInlinedIfTrueIfFalse instructions first.
+			self visit: anIRInlinedIfTrueIfFalse dagChildren first.
 			self stream nextPutAll: ')' ]
-		then: [ self visit: anIRInlinedIfTrueIfFalse instructions second ]
-		else: [ self visit: anIRInlinedIfTrueIfFalse instructions third ]
+		then: [ self visit: anIRInlinedIfTrueIfFalse dagChildren second ]
+		else: [ self visit: anIRInlinedIfTrueIfFalse dagChildren third ]
 !
 
 visitIRInlinedSequence: anIRInlinedSequence
-	anIRInlinedSequence instructions do: [ :each |
+	anIRInlinedSequence dagChildren do: [ :each |
 		self stream nextPutStatementWith: [ self visit: each ]]
 ! !
 
@@ -382,7 +381,7 @@ inlineClosure: anIRClosure
 	inlinedClosure add: sequence.
 
 	"Get all the statements"
-	statements := anIRClosure sequence instructions.
+	statements := anIRClosure sequence dagChildren.
 	
 	statements ifNotEmpty: [
 		statements allButLast do: [ :each | sequence add: each ].
@@ -498,7 +497,7 @@ inlineClosure: anIRClosure
 
 	closure := super inlineClosure: anIRClosure.
 	sequence := closure sequence.
-	statements := sequence instructions.
+	statements := sequence dagChildren.
 	
 	statements ifNotEmpty: [
 		| final |
@@ -525,7 +524,7 @@ inlineClosure: anIRClosure
 
 	closure := super inlineClosure: anIRClosure.
 	sequence := closure sequence.
-	statements := sequence instructions.
+	statements := sequence dagChildren.
 	
 	statements ifNotEmpty: [
 		| final |

+ 91 - 91
src/Compiler-Interpreter.js

@@ -247,7 +247,7 @@ return $core.withContext(function($ctx1) {
 //>>excludeEnd("ctx");
 var $1,$2,$3;
 context=$recv(self["@outerContext"])._newInnerContext();
-$1=$recv($recv($recv(self["@node"])._nodes())._first())._copy();
+$1=$recv($recv($recv(self["@node"])._dagChildren())._first())._copy();
 $recv($1)._parent_(nil);
 sequenceNode=$recv($1)._yourself();
 $recv($recv(sequenceNode)._temps())._do_((function(each){
@@ -294,10 +294,10 @@ return $recv($recv(context)._interpreter())._pop();
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["aCollection"],
-source: "valueWithPossibleArguments: aCollection\x0a\x09| context sequenceNode |\x0a\x09context := outerContext newInnerContext.\x0a\x0a\x09\x22Interpret a copy of the sequence node to avoid creating a new AIBlockClosure\x22\x0a\x09sequenceNode := node nodes first copy\x0a\x09\x09parent: nil;\x0a\x09\x09yourself.\x0a\x09\x09\x0a\x09\x22Define locals in the context\x22\x0a\x09sequenceNode temps do: [ :each |\x0a\x09\x09context defineLocal: each ].\x0a\x09\x09\x0a\x09\x22Populate the arguments into the context locals\x22\x09\x0a\x09node parameters withIndexDo: [ :each :index |\x0a\x09\x09context defineLocal: each.\x0a\x09\x09context localAt: each put: (aCollection at: index ifAbsent: [ nil ]) ].\x0a\x0a\x09\x22Interpret the first node of the BlockSequenceNode\x22\x0a\x09context interpreter\x0a\x09\x09node: sequenceNode;\x0a\x09\x09enterNode;\x0a\x09\x09proceed.\x0a\x09\x09\x0a\x09outerContext interpreter\x0a\x09\x09setNonLocalReturnFromContext: context.\x0a\x09\x09\x0a\x09^ context interpreter pop",
+source: "valueWithPossibleArguments: aCollection\x0a\x09| context sequenceNode |\x0a\x09context := outerContext newInnerContext.\x0a\x0a\x09\x22Interpret a copy of the sequence node to avoid creating a new AIBlockClosure\x22\x0a\x09sequenceNode := node dagChildren first copy\x0a\x09\x09parent: nil;\x0a\x09\x09yourself.\x0a\x09\x09\x0a\x09\x22Define locals in the context\x22\x0a\x09sequenceNode temps do: [ :each |\x0a\x09\x09context defineLocal: each ].\x0a\x09\x09\x0a\x09\x22Populate the arguments into the context locals\x22\x09\x0a\x09node parameters withIndexDo: [ :each :index |\x0a\x09\x09context defineLocal: each.\x0a\x09\x09context localAt: each put: (aCollection at: index ifAbsent: [ nil ]) ].\x0a\x0a\x09\x22Interpret the first node of the BlockSequenceNode\x22\x0a\x09context interpreter\x0a\x09\x09node: sequenceNode;\x0a\x09\x09enterNode;\x0a\x09\x09proceed.\x0a\x09\x09\x0a\x09outerContext interpreter\x0a\x09\x09setNonLocalReturnFromContext: context.\x0a\x09\x09\x0a\x09^ context interpreter pop",
 referencedClasses: [],
 //>>excludeEnd("ide");
-messageSends: ["newInnerContext", "parent:", "copy", "first", "nodes", "yourself", "do:", "temps", "defineLocal:", "withIndexDo:", "parameters", "localAt:put:", "at:ifAbsent:", "node:", "interpreter", "enterNode", "proceed", "setNonLocalReturnFromContext:", "pop"]
+messageSends: ["newInnerContext", "parent:", "copy", "first", "dagChildren", "yourself", "do:", "temps", "defineLocal:", "withIndexDo:", "parameters", "localAt:put:", "at:ifAbsent:", "node:", "interpreter", "enterNode", "proceed", "setNonLocalReturnFromContext:", "pop"]
 }),
 $globals.AIBlockClosure);
 
@@ -2098,7 +2098,7 @@ $globals.ASTEnterNode);
 
 $core.addMethod(
 $core.method({
-selector: "visitNode:",
+selector: "visitDagNode:",
 protocol: 'visiting',
 fn: function (aNode){
 var self=this;
@@ -2107,7 +2107,7 @@ return $core.withContext(function($ctx1) {
 //>>excludeEnd("ctx");
 var $early={};
 try {
-$recv($recv(aNode)._nodes())._ifEmpty_ifNotEmpty_((function(){
+$recv($recv(aNode)._dagChildren())._ifEmpty_ifNotEmpty_((function(){
 throw $early=[aNode];
 
 }),(function(nodes){
@@ -2123,15 +2123,15 @@ return self;
 }
 catch(e) {if(e===$early)return e[0]; throw e}
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-}, function($ctx1) {$ctx1.fill(self,"visitNode:",{aNode:aNode},$globals.ASTEnterNode)});
+}, function($ctx1) {$ctx1.fill(self,"visitDagNode:",{aNode:aNode},$globals.ASTEnterNode)});
 //>>excludeEnd("ctx");
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["aNode"],
-source: "visitNode: aNode\x0a\x09aNode nodes\x0a\x09\x09ifEmpty: [ ^ aNode ]\x0a\x09\x09ifNotEmpty: [ :nodes | ^ self visit: nodes first ]",
+source: "visitDagNode: aNode\x0a\x09aNode dagChildren\x0a\x09\x09ifEmpty: [ ^ aNode ]\x0a\x09\x09ifNotEmpty: [ :nodes | ^ self visit: nodes first ]",
 referencedClasses: [],
 //>>excludeEnd("ide");
-messageSends: ["ifEmpty:ifNotEmpty:", "nodes", "visit:", "first"]
+messageSends: ["ifEmpty:ifNotEmpty:", "dagChildren", "visit:", "first"]
 }),
 $globals.ASTEnterNode);
 
@@ -3211,6 +3211,24 @@ messageSends: ["visitBlockSequenceNode:"]
 }),
 $globals.ASTInterpreter);
 
+$core.addMethod(
+$core.method({
+selector: "visitDagNode:",
+protocol: 'visiting',
+fn: function (aNode){
+var self=this;
+return self;
+
+},
+//>>excludeStart("ide", pragmas.excludeIdeData);
+args: ["aNode"],
+source: "visitDagNode: aNode\x0a\x09\x22Do nothing by default. Especially, do not visit children recursively.\x22",
+referencedClasses: [],
+//>>excludeEnd("ide");
+messageSends: []
+}),
+$globals.ASTInterpreter);
+
 $core.addMethod(
 $core.method({
 selector: "visitDynamicArrayNode:",
@@ -3222,7 +3240,7 @@ var array;
 return $core.withContext(function($ctx1) {
 //>>excludeEnd("ctx");
 array=[];
-$recv($recv(aNode)._nodes())._do_((function(each){
+$recv($recv(aNode)._dagChildren())._do_((function(each){
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 return $core.withContext(function($ctx2) {
 //>>excludeEnd("ctx");
@@ -3239,10 +3257,10 @@ return self;
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["aNode"],
-source: "visitDynamicArrayNode: aNode\x0a\x09| array |\x0a\x09\x0a\x09array := #().\x0a\x09aNode nodes do: [ :each |\x0a\x09\x09array addFirst: self pop ].\x0a\x09\x0a\x09self push: array",
+source: "visitDynamicArrayNode: aNode\x0a\x09| array |\x0a\x09\x0a\x09array := #().\x0a\x09aNode dagChildren do: [ :each |\x0a\x09\x09array addFirst: self pop ].\x0a\x09\x0a\x09self push: array",
 referencedClasses: [],
 //>>excludeEnd("ide");
-messageSends: ["do:", "nodes", "addFirst:", "pop", "push:"]
+messageSends: ["do:", "dagChildren", "addFirst:", "pop", "push:"]
 }),
 $globals.ASTInterpreter);
 
@@ -3257,7 +3275,7 @@ var keyValueList;
 return $core.withContext(function($ctx1) {
 //>>excludeEnd("ctx");
 keyValueList=$recv($globals.OrderedCollection)._new();
-$recv($recv(aNode)._nodes())._do_((function(each){
+$recv($recv(aNode)._dagChildren())._do_((function(each){
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 return $core.withContext(function($ctx2) {
 //>>excludeEnd("ctx");
@@ -3274,10 +3292,10 @@ return self;
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["aNode"],
-source: "visitDynamicDictionaryNode: aNode\x0a\x09| keyValueList |\x0a\x09\x0a\x09keyValueList := OrderedCollection new.\x0a\x09\x0a\x09aNode nodes do: [ :each | \x0a\x09\x09keyValueList add: self pop ].\x0a\x09\x0a\x09self push: (HashedCollection newFromPairs: keyValueList reversed)",
+source: "visitDynamicDictionaryNode: aNode\x0a\x09| keyValueList |\x0a\x09\x0a\x09keyValueList := OrderedCollection new.\x0a\x09\x0a\x09aNode dagChildren do: [ :each | \x0a\x09\x09keyValueList add: self pop ].\x0a\x09\x0a\x09self push: (HashedCollection newFromPairs: keyValueList reversed)",
 referencedClasses: ["OrderedCollection", "HashedCollection"],
 //>>excludeEnd("ide");
-messageSends: ["new", "do:", "nodes", "add:", "pop", "push:", "newFromPairs:", "reversed"]
+messageSends: ["new", "do:", "dagChildren", "add:", "pop", "push:", "newFromPairs:", "reversed"]
 }),
 $globals.ASTInterpreter);
 
@@ -3306,24 +3324,6 @@ messageSends: ["returnValue:", "eval:", "source"]
 }),
 $globals.ASTInterpreter);
 
-$core.addMethod(
-$core.method({
-selector: "visitNode:",
-protocol: 'visiting',
-fn: function (aNode){
-var self=this;
-return self;
-
-},
-//>>excludeStart("ide", pragmas.excludeIdeData);
-args: ["aNode"],
-source: "visitNode: aNode\x0a\x09\x22Do nothing by default. Especially, do not visit children recursively.\x22",
-referencedClasses: [],
-//>>excludeEnd("ide");
-messageSends: []
-}),
-$globals.ASTInterpreter);
-
 $core.addMethod(
 $core.method({
 selector: "visitReturnNode:",
@@ -3762,21 +3762,26 @@ $globals.ASTPCNodeVisitor);
 
 $core.addMethod(
 $core.method({
-selector: "isSteppingNode",
+selector: "isLastChild",
 protocol: '*Compiler-Interpreter',
 fn: function (){
 var self=this;
-return true;
-
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+return $core.withContext(function($ctx1) {
+//>>excludeEnd("ctx");
+return $recv($recv($recv(self._parent())._dagChildren())._last()).__eq(self);
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+}, function($ctx1) {$ctx1.fill(self,"isLastChild",{},$globals.ASTNode)});
+//>>excludeEnd("ctx");
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: [],
-source: "isSteppingNode\x0a\x09^ true",
+source: "isLastChild\x0a\x09^ self parent dagChildren last = self",
 referencedClasses: [],
 //>>excludeEnd("ide");
-messageSends: []
+messageSends: ["=", "last", "dagChildren", "parent"]
 }),
-$globals.AssignmentNode);
+$globals.ASTNode);
 
 $core.addMethod(
 $core.method({
@@ -3784,17 +3789,17 @@ selector: "isSteppingNode",
 protocol: '*Compiler-Interpreter',
 fn: function (){
 var self=this;
-return true;
+return false;
 
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: [],
-source: "isSteppingNode\x0a\x09^ true",
+source: "isSteppingNode\x0a\x09^ false",
 referencedClasses: [],
 //>>excludeEnd("ide");
 messageSends: []
 }),
-$globals.BlockNode);
+$globals.ASTNode);
 
 $core.addMethod(
 $core.method({
@@ -3802,17 +3807,34 @@ selector: "nextSiblingNode:",
 protocol: '*Compiler-Interpreter',
 fn: function (aNode){
 var self=this;
-return nil;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+return $core.withContext(function($ctx1) {
+//>>excludeEnd("ctx");
+var $1;
+var $early={};
+try {
+$1=self._dagChildren();
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+$ctx1.sendIdx["dagChildren"]=1;
+//>>excludeEnd("ctx");
+return $recv($1)._at_ifAbsent_($recv($recv(self._dagChildren())._indexOf_(aNode)).__plus((1)),(function(){
+throw $early=[nil];
 
+}));
+}
+catch(e) {if(e===$early)return e[0]; throw e}
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+}, function($ctx1) {$ctx1.fill(self,"nextSiblingNode:",{aNode:aNode},$globals.ASTNode)});
+//>>excludeEnd("ctx");
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["aNode"],
-source: "nextSiblingNode: aNode\x0a\x09\x22Answer nil as we want to avoid eager evaluation\x22\x0a\x09\x0a\x09\x22In fact, this should not have been called, ever. IMO. -- herby\x22\x0a\x09\x0a\x09^ nil",
+source: "nextSiblingNode: aNode\x0a\x09\x22Answer the next node after aNode or nil\x22\x0a\x09\x0a\x09^ self dagChildren \x0a\x09\x09at: (self dagChildren indexOf: aNode) + 1\x0a\x09\x09ifAbsent: [ ^ nil ]",
 referencedClasses: [],
 //>>excludeEnd("ide");
-messageSends: []
+messageSends: ["at:ifAbsent:", "dagChildren", "+", "indexOf:"]
 }),
-$globals.BlockNode);
+$globals.ASTNode);
 
 $core.addMethod(
 $core.method({
@@ -3830,7 +3852,7 @@ referencedClasses: [],
 //>>excludeEnd("ide");
 messageSends: []
 }),
-$globals.DynamicArrayNode);
+$globals.AssignmentNode);
 
 $core.addMethod(
 $core.method({
@@ -3848,48 +3870,43 @@ referencedClasses: [],
 //>>excludeEnd("ide");
 messageSends: []
 }),
-$globals.DynamicDictionaryNode);
+$globals.BlockNode);
 
 $core.addMethod(
 $core.method({
-selector: "isSteppingNode",
+selector: "nextSiblingNode:",
 protocol: '*Compiler-Interpreter',
-fn: function (){
+fn: function (aNode){
 var self=this;
-return true;
+return nil;
 
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
-args: [],
-source: "isSteppingNode\x0a\x09^ true",
+args: ["aNode"],
+source: "nextSiblingNode: aNode\x0a\x09\x22Answer nil as we want to avoid eager evaluation\x22\x0a\x09\x0a\x09\x22In fact, this should not have been called, ever. IMO. -- herby\x22\x0a\x09\x0a\x09^ nil",
 referencedClasses: [],
 //>>excludeEnd("ide");
 messageSends: []
 }),
-$globals.JSStatementNode);
+$globals.BlockNode);
 
 $core.addMethod(
 $core.method({
-selector: "isLastChild",
+selector: "isSteppingNode",
 protocol: '*Compiler-Interpreter',
 fn: function (){
 var self=this;
-//>>excludeStart("ctx", pragmas.excludeDebugContexts);
-return $core.withContext(function($ctx1) {
-//>>excludeEnd("ctx");
-return $recv($recv($recv(self._parent())._nodes())._last()).__eq(self);
-//>>excludeStart("ctx", pragmas.excludeDebugContexts);
-}, function($ctx1) {$ctx1.fill(self,"isLastChild",{},$globals.Node)});
-//>>excludeEnd("ctx");
+return true;
+
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: [],
-source: "isLastChild\x0a\x09^ self parent nodes last = self",
+source: "isSteppingNode\x0a\x09^ true",
 referencedClasses: [],
 //>>excludeEnd("ide");
-messageSends: ["=", "last", "nodes", "parent"]
+messageSends: []
 }),
-$globals.Node);
+$globals.DynamicArrayNode);
 
 $core.addMethod(
 $core.method({
@@ -3897,52 +3914,35 @@ selector: "isSteppingNode",
 protocol: '*Compiler-Interpreter',
 fn: function (){
 var self=this;
-return false;
+return true;
 
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: [],
-source: "isSteppingNode\x0a\x09^ false",
+source: "isSteppingNode\x0a\x09^ true",
 referencedClasses: [],
 //>>excludeEnd("ide");
 messageSends: []
 }),
-$globals.Node);
+$globals.DynamicDictionaryNode);
 
 $core.addMethod(
 $core.method({
-selector: "nextSiblingNode:",
+selector: "isSteppingNode",
 protocol: '*Compiler-Interpreter',
-fn: function (aNode){
+fn: function (){
 var self=this;
-//>>excludeStart("ctx", pragmas.excludeDebugContexts);
-return $core.withContext(function($ctx1) {
-//>>excludeEnd("ctx");
-var $1;
-var $early={};
-try {
-$1=self._nodes();
-//>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["nodes"]=1;
-//>>excludeEnd("ctx");
-return $recv($1)._at_ifAbsent_($recv($recv(self._nodes())._indexOf_(aNode)).__plus((1)),(function(){
-throw $early=[nil];
+return true;
 
-}));
-}
-catch(e) {if(e===$early)return e[0]; throw e}
-//>>excludeStart("ctx", pragmas.excludeDebugContexts);
-}, function($ctx1) {$ctx1.fill(self,"nextSiblingNode:",{aNode:aNode},$globals.Node)});
-//>>excludeEnd("ctx");
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
-args: ["aNode"],
-source: "nextSiblingNode: aNode\x0a\x09\x22Answer the next node after aNode or nil\x22\x0a\x09\x0a\x09^ self nodes \x0a\x09\x09at: (self nodes indexOf: aNode) + 1\x0a\x09\x09ifAbsent: [ ^ nil ]",
+args: [],
+source: "isSteppingNode\x0a\x09^ true",
 referencedClasses: [],
 //>>excludeEnd("ide");
-messageSends: ["at:ifAbsent:", "nodes", "+", "indexOf:"]
+messageSends: []
 }),
-$globals.Node);
+$globals.JSStatementNode);
 
 $core.addMethod(
 $core.method({

+ 27 - 27
src/Compiler-Interpreter.st

@@ -60,7 +60,7 @@ valueWithPossibleArguments: aCollection
 	context := outerContext newInnerContext.
 
 	"Interpret a copy of the sequence node to avoid creating a new AIBlockClosure"
-	sequenceNode := node nodes first copy
+	sequenceNode := node dagChildren first copy
 		parent: nil;
 		yourself.
 		
@@ -560,8 +560,8 @@ visitBlockNode: aNode
 	^ aNode
 !
 
-visitNode: aNode
-	aNode nodes
+visitDagNode: aNode
+	aNode dagChildren
 		ifEmpty: [ ^ aNode ]
 		ifNotEmpty: [ :nodes | ^ self visit: nodes first ]
 !
@@ -834,11 +834,15 @@ visitBlockSequenceNode: aNode
 	forceAtEnd := true
 !
 
+visitDagNode: aNode
+	"Do nothing by default. Especially, do not visit children recursively."
+!
+
 visitDynamicArrayNode: aNode
 	| array |
 	
 	array := #().
-	aNode nodes do: [ :each |
+	aNode dagChildren do: [ :each |
 		array addFirst: self pop ].
 	
 	self push: array
@@ -849,7 +853,7 @@ visitDynamicDictionaryNode: aNode
 	
 	keyValueList := OrderedCollection new.
 	
-	aNode nodes do: [ :each | 
+	aNode dagChildren do: [ :each | 
 		keyValueList add: self pop ].
 	
 	self push: (HashedCollection newFromPairs: keyValueList reversed)
@@ -860,10 +864,6 @@ visitJSStatementNode: aNode
 	self returnValue: (self eval: aNode source)
 !
 
-visitNode: aNode
-	"Do nothing by default. Especially, do not visit children recursively."
-!
-
 visitReturnNode: aNode
 	returned := true.
 	self returnValue: self pop
@@ -971,6 +971,24 @@ visitSendNode: aNode
 		self increaseTrackedIndex ]
 ! !
 
+!ASTNode methodsFor: '*Compiler-Interpreter'!
+
+isLastChild
+	^ self parent dagChildren last = self
+!
+
+isSteppingNode
+	^ false
+!
+
+nextSiblingNode: aNode
+	"Answer the next node after aNode or nil"
+	
+	^ self dagChildren 
+		at: (self dagChildren indexOf: aNode) + 1
+		ifAbsent: [ ^ nil ]
+! !
+
 !AssignmentNode methodsFor: '*Compiler-Interpreter'!
 
 isSteppingNode
@@ -1009,24 +1027,6 @@ isSteppingNode
 	^ true
 ! !
 
-!Node methodsFor: '*Compiler-Interpreter'!
-
-isLastChild
-	^ self parent nodes last = self
-!
-
-isSteppingNode
-	^ false
-!
-
-nextSiblingNode: aNode
-	"Answer the next node after aNode or nil"
-	
-	^ self nodes 
-		at: (self nodes indexOf: aNode) + 1
-		ifAbsent: [ ^ nil ]
-! !
-
 !SendNode methodsFor: '*Compiler-Interpreter'!
 
 isCascadeSendNode

+ 3 - 3
src/Compiler-Semantic.js

@@ -2248,7 +2248,7 @@ var self=this;
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 return $core.withContext(function($ctx1) {
 //>>excludeEnd("ctx");
-$recv(aNode)._receiver_($recv($recv($recv(aNode)._nodes())._first())._receiver());
+$recv(aNode)._receiver_($recv($recv($recv(aNode)._dagChildren())._first())._receiver());
 (
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx1.supercall = true,
@@ -2264,10 +2264,10 @@ return self;
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["aNode"],
-source: "visitCascadeNode: aNode\x0a\x09aNode receiver: aNode nodes first receiver.\x0a\x09super visitCascadeNode: aNode",
+source: "visitCascadeNode: aNode\x0a\x09aNode receiver: aNode dagChildren first receiver.\x0a\x09super visitCascadeNode: aNode",
 referencedClasses: [],
 //>>excludeEnd("ide");
-messageSends: ["receiver:", "receiver", "first", "nodes", "visitCascadeNode:"]
+messageSends: ["receiver:", "receiver", "first", "dagChildren", "visitCascadeNode:"]
 }),
 $globals.SemanticAnalyzer);
 

+ 1 - 1
src/Compiler-Semantic.st

@@ -550,7 +550,7 @@ visitBlockNode: aNode
 !
 
 visitCascadeNode: aNode
-	aNode receiver: aNode nodes first receiver.
+	aNode receiver: aNode dagChildren first receiver.
 	super visitCascadeNode: aNode
 !
 

+ 48 - 48
src/Compiler-Tests.js

@@ -2435,9 +2435,9 @@ var $4,$3,$2,$1;
 src="foo | a | a + 1. [ | b | b := a ]";
 ast=$recv($globals.Smalltalk)._parse_(src);
 $recv(self["@analyzer"])._visit_(ast);
-$4=$recv($recv($recv(ast)._nodes())._first())._nodes();
+$4=$recv($recv($recv(ast)._dagChildren())._first())._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["nodes"]=1;
+$ctx1.sendIdx["dagChildren"]=1;
 //>>excludeEnd("ctx");
 $3=$recv($4)._last();
 $2=$recv($3)._scope();
@@ -2453,10 +2453,10 @@ return self;
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: [],
-source: "testScope\x0a\x09| src ast |\x0a\x0a\x09src := 'foo | a | a + 1. [ | b | b := a ]'.\x0a\x09ast := Smalltalk parse: src.\x0a\x09analyzer visit: ast.\x0a\x0a\x09self deny: ast nodes first nodes last scope == ast scope.",
+source: "testScope\x0a\x09| src ast |\x0a\x0a\x09src := 'foo | a | a + 1. [ | b | b := a ]'.\x0a\x09ast := Smalltalk parse: src.\x0a\x09analyzer visit: ast.\x0a\x0a\x09self deny: ast dagChildren first dagChildren last scope == ast scope.",
 referencedClasses: ["Smalltalk"],
 //>>excludeEnd("ide");
-messageSends: ["parse:", "visit:", "deny:", "==", "scope", "last", "nodes", "first"]
+messageSends: ["parse:", "visit:", "deny:", "==", "scope", "last", "dagChildren", "first"]
 }),
 $globals.SemanticAnalyzerTest);
 
@@ -2474,22 +2474,22 @@ var $8,$7,$6,$5,$4,$3,$2,$1;
 src="foo | a | a + 1. [ [ | b | b := a ] ]";
 ast=$recv($globals.Smalltalk)._parse_(src);
 $recv(self["@analyzer"])._visit_(ast);
-$8=$recv($recv($recv(ast)._nodes())._first())._nodes();
+$8=$recv($recv($recv(ast)._dagChildren())._first())._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["nodes"]=3;
+$ctx1.sendIdx["dagChildren"]=3;
 //>>excludeEnd("ctx");
 $7=$recv($8)._last();
-$6=$recv($7)._nodes();
+$6=$recv($7)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["nodes"]=2;
+$ctx1.sendIdx["dagChildren"]=2;
 //>>excludeEnd("ctx");
 $5=$recv($6)._first();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx1.sendIdx["first"]=2;
 //>>excludeEnd("ctx");
-$4=$recv($5)._nodes();
+$4=$recv($5)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["nodes"]=1;
+$ctx1.sendIdx["dagChildren"]=1;
 //>>excludeEnd("ctx");
 $3=$recv($4)._first();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
@@ -2508,10 +2508,10 @@ return self;
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: [],
-source: "testScope2\x0a\x09| src ast |\x0a\x0a\x09src := 'foo | a | a + 1. [ [ | b | b := a ] ]'.\x0a\x09ast := Smalltalk parse: src.\x0a\x09analyzer visit: ast.\x0a\x0a\x09self deny: ast nodes first nodes last nodes first nodes first scope == ast scope.",
+source: "testScope2\x0a\x09| src ast |\x0a\x0a\x09src := 'foo | a | a + 1. [ [ | b | b := a ] ]'.\x0a\x09ast := Smalltalk parse: src.\x0a\x09analyzer visit: ast.\x0a\x0a\x09self deny: ast dagChildren first dagChildren last dagChildren first dagChildren first scope == ast scope.",
 referencedClasses: ["Smalltalk"],
 //>>excludeEnd("ide");
-messageSends: ["parse:", "visit:", "deny:", "==", "scope", "first", "nodes", "last"]
+messageSends: ["parse:", "visit:", "deny:", "==", "scope", "first", "dagChildren", "last"]
 }),
 $globals.SemanticAnalyzerTest);
 
@@ -2541,22 +2541,22 @@ self._assert_equals_($1,(1));
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx1.sendIdx["assert:equals:"]=1;
 //>>excludeEnd("ctx");
-$10=$recv($recv($recv(ast)._nodes())._first())._nodes();
+$10=$recv($recv($recv(ast)._dagChildren())._first())._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["nodes"]=3;
+$ctx1.sendIdx["dagChildren"]=3;
 //>>excludeEnd("ctx");
 $9=$recv($10)._last();
-$8=$recv($9)._nodes();
+$8=$recv($9)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["nodes"]=2;
+$ctx1.sendIdx["dagChildren"]=2;
 //>>excludeEnd("ctx");
 $7=$recv($8)._first();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx1.sendIdx["first"]=2;
 //>>excludeEnd("ctx");
-$6=$recv($7)._nodes();
+$6=$recv($7)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["nodes"]=1;
+$ctx1.sendIdx["dagChildren"]=1;
 //>>excludeEnd("ctx");
 $5=$recv($6)._first();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
@@ -2572,10 +2572,10 @@ return self;
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: [],
-source: "testScopeLevel\x0a\x09| src ast |\x0a\x0a\x09src := 'foo | a | a + 1. [ [ | b | b := a ] ]'.\x0a\x09ast := Smalltalk parse: src.\x0a\x09analyzer visit: ast.\x0a\x0a\x09self assert: ast scope scopeLevel equals: 1.\x0a\x09self assert: ast nodes first nodes last nodes first nodes first scope scopeLevel equals: 3",
+source: "testScopeLevel\x0a\x09| src ast |\x0a\x0a\x09src := 'foo | a | a + 1. [ [ | b | b := a ] ]'.\x0a\x09ast := Smalltalk parse: src.\x0a\x09analyzer visit: ast.\x0a\x0a\x09self assert: ast scope scopeLevel equals: 1.\x0a\x09self assert: ast dagChildren first dagChildren last dagChildren first dagChildren first scope scopeLevel equals: 3",
 referencedClasses: ["Smalltalk"],
 //>>excludeEnd("ide");
-messageSends: ["parse:", "visit:", "assert:equals:", "scopeLevel", "scope", "first", "nodes", "last"]
+messageSends: ["parse:", "visit:", "assert:equals:", "scopeLevel", "scope", "first", "dagChildren", "last"]
 }),
 $globals.SemanticAnalyzerTest);
 
@@ -2814,17 +2814,17 @@ var $7,$6,$5,$4,$3,$2,$1,$15,$14,$13,$12,$11,$10,$9,$16,$8,$27,$26,$25,$24,$23,$
 src="foo | a | a + 1. [ | b | b := a ]";
 ast=$recv($globals.Smalltalk)._parse_(src);
 $recv(self["@analyzer"])._visit_(ast);
-$7=$recv(ast)._nodes();
+$7=$recv(ast)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["nodes"]=2;
+$ctx1.sendIdx["dagChildren"]=2;
 //>>excludeEnd("ctx");
 $6=$recv($7)._first();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx1.sendIdx["first"]=2;
 //>>excludeEnd("ctx");
-$5=$recv($6)._nodes();
+$5=$recv($6)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["nodes"]=1;
+$ctx1.sendIdx["dagChildren"]=1;
 //>>excludeEnd("ctx");
 $4=$recv($5)._first();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
@@ -2846,17 +2846,17 @@ self._assert_($1);
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx1.sendIdx["assert:"]=1;
 //>>excludeEnd("ctx");
-$15=$recv(ast)._nodes();
+$15=$recv(ast)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["nodes"]=4;
+$ctx1.sendIdx["dagChildren"]=4;
 //>>excludeEnd("ctx");
 $14=$recv($15)._first();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx1.sendIdx["first"]=4;
 //>>excludeEnd("ctx");
-$13=$recv($14)._nodes();
+$13=$recv($14)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["nodes"]=3;
+$ctx1.sendIdx["dagChildren"]=3;
 //>>excludeEnd("ctx");
 $12=$recv($13)._first();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
@@ -2883,33 +2883,33 @@ self._assert_($8);
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx1.sendIdx["assert:"]=2;
 //>>excludeEnd("ctx");
-$27=$recv(ast)._nodes();
+$27=$recv(ast)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["nodes"]=8;
+$ctx1.sendIdx["dagChildren"]=8;
 //>>excludeEnd("ctx");
 $26=$recv($27)._first();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx1.sendIdx["first"]=7;
 //>>excludeEnd("ctx");
-$25=$recv($26)._nodes();
+$25=$recv($26)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["nodes"]=7;
+$ctx1.sendIdx["dagChildren"]=7;
 //>>excludeEnd("ctx");
 $24=$recv($25)._last();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx1.sendIdx["last"]=1;
 //>>excludeEnd("ctx");
-$23=$recv($24)._nodes();
+$23=$recv($24)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["nodes"]=6;
+$ctx1.sendIdx["dagChildren"]=6;
 //>>excludeEnd("ctx");
 $22=$recv($23)._first();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx1.sendIdx["first"]=6;
 //>>excludeEnd("ctx");
-$21=$recv($22)._nodes();
+$21=$recv($22)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["nodes"]=5;
+$ctx1.sendIdx["dagChildren"]=5;
 //>>excludeEnd("ctx");
 $20=$recv($21)._first();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
@@ -2928,33 +2928,33 @@ self._assert_($17);
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx1.sendIdx["assert:"]=3;
 //>>excludeEnd("ctx");
-$39=$recv(ast)._nodes();
+$39=$recv(ast)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["nodes"]=12;
+$ctx1.sendIdx["dagChildren"]=12;
 //>>excludeEnd("ctx");
 $38=$recv($39)._first();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx1.sendIdx["first"]=10;
 //>>excludeEnd("ctx");
-$37=$recv($38)._nodes();
+$37=$recv($38)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["nodes"]=11;
+$ctx1.sendIdx["dagChildren"]=11;
 //>>excludeEnd("ctx");
 $36=$recv($37)._last();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx1.sendIdx["last"]=2;
 //>>excludeEnd("ctx");
-$35=$recv($36)._nodes();
+$35=$recv($36)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["nodes"]=10;
+$ctx1.sendIdx["dagChildren"]=10;
 //>>excludeEnd("ctx");
 $34=$recv($35)._first();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx1.sendIdx["first"]=9;
 //>>excludeEnd("ctx");
-$33=$recv($34)._nodes();
+$33=$recv($34)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["nodes"]=9;
+$ctx1.sendIdx["dagChildren"]=9;
 //>>excludeEnd("ctx");
 $32=$recv($33)._first();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
@@ -2966,9 +2966,9 @@ $29=$recv($30)._scope();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx1.sendIdx["scope"]=3;
 //>>excludeEnd("ctx");
-$42=$recv($recv($recv(ast)._nodes())._first())._nodes();
+$42=$recv($recv($recv(ast)._dagChildren())._first())._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["nodes"]=13;
+$ctx1.sendIdx["dagChildren"]=13;
 //>>excludeEnd("ctx");
 $41=$recv($42)._last();
 $40=$recv($41)._scope();
@@ -2981,10 +2981,10 @@ return self;
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: [],
-source: "testVariablesLookup\x0a\x09| src ast |\x0a\x0a\x09src := 'foo | a | a + 1. [ | b | b := a ]'.\x0a\x09ast := Smalltalk parse: src.\x0a\x09analyzer visit: ast.\x0a\x0a\x09\x22Binding for `a` in the message send\x22\x0a\x09self assert: ast nodes first nodes first receiver binding isTempVar.\x0a\x09self assert: ast nodes first nodes first receiver binding scope == ast scope.\x0a\x0a\x09\x22Binding for `b`\x22\x0a\x09self assert: ast nodes first nodes last nodes first nodes first left binding isTempVar.\x0a\x09self assert: ast nodes first nodes last nodes first nodes first left binding scope == ast nodes first nodes last scope.",
+source: "testVariablesLookup\x0a\x09| src ast |\x0a\x0a\x09src := 'foo | a | a + 1. [ | b | b := a ]'.\x0a\x09ast := Smalltalk parse: src.\x0a\x09analyzer visit: ast.\x0a\x0a\x09\x22Binding for `a` in the message send\x22\x0a\x09self assert: ast dagChildren first dagChildren first receiver binding isTempVar.\x0a\x09self assert: ast dagChildren first dagChildren first receiver binding scope == ast scope.\x0a\x0a\x09\x22Binding for `b`\x22\x0a\x09self assert: ast dagChildren first dagChildren last dagChildren first dagChildren first left binding isTempVar.\x0a\x09self assert: ast dagChildren first dagChildren last dagChildren first dagChildren first left binding scope == ast dagChildren first dagChildren last scope.",
 referencedClasses: ["Smalltalk"],
 //>>excludeEnd("ide");
-messageSends: ["parse:", "visit:", "assert:", "isTempVar", "binding", "receiver", "first", "nodes", "==", "scope", "left", "last"]
+messageSends: ["parse:", "visit:", "assert:", "isTempVar", "binding", "receiver", "first", "dagChildren", "==", "scope", "left", "last"]
 }),
 $globals.SemanticAnalyzerTest);
 

+ 7 - 7
src/Compiler-Tests.st

@@ -685,7 +685,7 @@ testScope
 	ast := Smalltalk parse: src.
 	analyzer visit: ast.
 
-	self deny: ast nodes first nodes last scope == ast scope.
+	self deny: ast dagChildren first dagChildren last scope == ast scope.
 !
 
 testScope2
@@ -695,7 +695,7 @@ testScope2
 	ast := Smalltalk parse: src.
 	analyzer visit: ast.
 
-	self deny: ast nodes first nodes last nodes first nodes first scope == ast scope.
+	self deny: ast dagChildren first dagChildren last dagChildren first dagChildren first scope == ast scope.
 !
 
 testScopeLevel
@@ -706,7 +706,7 @@ testScopeLevel
 	analyzer visit: ast.
 
 	self assert: ast scope scopeLevel equals: 1.
-	self assert: ast nodes first nodes last nodes first nodes first scope scopeLevel equals: 3
+	self assert: ast dagChildren first dagChildren last dagChildren first dagChildren first scope scopeLevel equals: 3
 !
 
 testUnknownVariables
@@ -770,12 +770,12 @@ testVariablesLookup
 	analyzer visit: ast.
 
 	"Binding for `a` in the message send"
-	self assert: ast nodes first nodes first receiver binding isTempVar.
-	self assert: ast nodes first nodes first receiver binding scope == ast scope.
+	self assert: ast dagChildren first dagChildren first receiver binding isTempVar.
+	self assert: ast dagChildren first dagChildren first receiver binding scope == ast scope.
 
 	"Binding for `b`"
-	self assert: ast nodes first nodes last nodes first nodes first left binding isTempVar.
-	self assert: ast nodes first nodes last nodes first nodes first left binding scope == ast nodes first nodes last scope.
+	self assert: ast dagChildren first dagChildren last dagChildren first dagChildren first left binding isTempVar.
+	self assert: ast dagChildren first dagChildren last dagChildren first dagChildren first left binding scope == ast dagChildren first dagChildren last scope.
 ! !
 
 SemanticAnalyzerTest subclass: #AISemanticAnalyzerTest

+ 628 - 0
src/Kernel-Dag.js

@@ -0,0 +1,628 @@
+define(["amber/boot", "amber_core/Kernel-Objects"], function($boot){"use strict";
+if(!$boot.nilAsReceiver)$boot.nilAsReceiver=$boot.nil;
+var $core=$boot.api,nil=$boot.nilAsReceiver,$recv=$boot.asReceiver,$globals=$boot.globals;
+if(!$boot.nilAsClass)$boot.nilAsClass=$boot.dnu;
+$core.addPackage('Kernel-Dag');
+$core.packages["Kernel-Dag"].innerEval = function (expr) { return eval(expr); };
+$core.packages["Kernel-Dag"].transport = {"type":"amd","amdNamespace":"amber_core"};
+
+$core.addClass('AbstractDagVisitor', $globals.Object, [], 'Kernel-Dag');
+//>>excludeStart("ide", pragmas.excludeIdeData);
+$globals.AbstractDagVisitor.comment="I am base class of `DagNode` visitor.\x0a\x0aConcrete classes should implement `visitDagNode:`,\x0athey can reuse possible variants of implementation\x0aoffered directly: `visitDagNodeVariantSimple:`\x0aand `visitDagNodeVariantRedux:`.";
+//>>excludeEnd("ide");
+$core.addMethod(
+$core.method({
+selector: "visit:",
+protocol: 'visiting',
+fn: function (aNode){
+var self=this;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+return $core.withContext(function($ctx1) {
+//>>excludeEnd("ctx");
+return $recv(aNode)._acceptDagVisitor_(self);
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+}, function($ctx1) {$ctx1.fill(self,"visit:",{aNode:aNode},$globals.AbstractDagVisitor)});
+//>>excludeEnd("ctx");
+},
+//>>excludeStart("ide", pragmas.excludeIdeData);
+args: ["aNode"],
+source: "visit: aNode\x0a\x09^ aNode acceptDagVisitor: self",
+referencedClasses: [],
+//>>excludeEnd("ide");
+messageSends: ["acceptDagVisitor:"]
+}),
+$globals.AbstractDagVisitor);
+
+$core.addMethod(
+$core.method({
+selector: "visitAll:",
+protocol: 'visiting',
+fn: function (aCollection){
+var self=this;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+return $core.withContext(function($ctx1) {
+//>>excludeEnd("ctx");
+return $recv(aCollection)._collect_((function(each){
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+return $core.withContext(function($ctx2) {
+//>>excludeEnd("ctx");
+return self._visit_(each);
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+}, function($ctx2) {$ctx2.fillBlock({each:each},$ctx1,1)});
+//>>excludeEnd("ctx");
+}));
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+}, function($ctx1) {$ctx1.fill(self,"visitAll:",{aCollection:aCollection},$globals.AbstractDagVisitor)});
+//>>excludeEnd("ctx");
+},
+//>>excludeStart("ide", pragmas.excludeIdeData);
+args: ["aCollection"],
+source: "visitAll: aCollection\x0a\x09^ aCollection collect: [ :each | self visit: each ]",
+referencedClasses: [],
+//>>excludeEnd("ide");
+messageSends: ["collect:", "visit:"]
+}),
+$globals.AbstractDagVisitor);
+
+$core.addMethod(
+$core.method({
+selector: "visitAllChildren:",
+protocol: 'visiting',
+fn: function (aDagNode){
+var self=this;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+return $core.withContext(function($ctx1) {
+//>>excludeEnd("ctx");
+return self._visitAll_($recv(aDagNode)._dagChildren());
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+}, function($ctx1) {$ctx1.fill(self,"visitAllChildren:",{aDagNode:aDagNode},$globals.AbstractDagVisitor)});
+//>>excludeEnd("ctx");
+},
+//>>excludeStart("ide", pragmas.excludeIdeData);
+args: ["aDagNode"],
+source: "visitAllChildren: aDagNode\x0a\x09^ self visitAll: aDagNode dagChildren",
+referencedClasses: [],
+//>>excludeEnd("ide");
+messageSends: ["visitAll:", "dagChildren"]
+}),
+$globals.AbstractDagVisitor);
+
+$core.addMethod(
+$core.method({
+selector: "visitDagNode:",
+protocol: 'visiting',
+fn: function (aNode){
+var self=this;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+return $core.withContext(function($ctx1) {
+//>>excludeEnd("ctx");
+self._subclassResponsibility();
+return self;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+}, function($ctx1) {$ctx1.fill(self,"visitDagNode:",{aNode:aNode},$globals.AbstractDagVisitor)});
+//>>excludeEnd("ctx");
+},
+//>>excludeStart("ide", pragmas.excludeIdeData);
+args: ["aNode"],
+source: "visitDagNode: aNode\x0a\x09self subclassResponsibility",
+referencedClasses: [],
+//>>excludeEnd("ide");
+messageSends: ["subclassResponsibility"]
+}),
+$globals.AbstractDagVisitor);
+
+$core.addMethod(
+$core.method({
+selector: "visitDagNodeVariantRedux:",
+protocol: 'visiting',
+fn: function (aNode){
+var self=this;
+var newChildren,oldChildren;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+return $core.withContext(function($ctx1) {
+//>>excludeEnd("ctx");
+var $2,$3,$1,$4,$5;
+var $early={};
+try {
+oldChildren=$recv(aNode)._dagChildren();
+newChildren=self._visitAllChildren_(aNode);
+$2=$recv(oldChildren)._size();
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+$ctx1.sendIdx["size"]=1;
+//>>excludeEnd("ctx");
+$3=$recv(newChildren)._size();
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+$ctx1.sendIdx["size"]=2;
+//>>excludeEnd("ctx");
+$1=$recv($2).__eq($3);
+if($core.assert($1)){
+$recv((1)._to_($recv(oldChildren)._size()))._detect_ifNone_((function(i){
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+return $core.withContext(function($ctx2) {
+//>>excludeEnd("ctx");
+$4=$recv(oldChildren)._at_(i);
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+$ctx2.sendIdx["at:"]=1;
+//>>excludeEnd("ctx");
+return $recv($4).__tild_eq($recv(newChildren)._at_(i));
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+}, function($ctx2) {$ctx2.fillBlock({i:i},$ctx1,2)});
+//>>excludeEnd("ctx");
+}),(function(){
+throw $early=[aNode];
+
+}));
+};
+$5=$recv(aNode)._copy();
+$recv($5)._dagChildren_(newChildren);
+return $recv($5)._yourself();
+}
+catch(e) {if(e===$early)return e[0]; throw e}
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+}, function($ctx1) {$ctx1.fill(self,"visitDagNodeVariantRedux:",{aNode:aNode,newChildren:newChildren,oldChildren:oldChildren},$globals.AbstractDagVisitor)});
+//>>excludeEnd("ctx");
+},
+//>>excludeStart("ide", pragmas.excludeIdeData);
+args: ["aNode"],
+source: "visitDagNodeVariantRedux: aNode\x0a\x09\x22Immutable-guarded implementation of visitDagNode:.\x0a\x09Visits all children and checks if there were changes.\x0a\x09If not, returns aNode.\x0a\x09If yes, returns copy of aNode with new children.\x22\x0a\x0a\x09| newChildren oldChildren |\x0a\x09oldChildren := aNode dagChildren.\x0a\x09newChildren := self visitAllChildren: aNode.\x0a\x09oldChildren size = newChildren size ifTrue: [\x0a\x09\x09(1 to: oldChildren size) detect: [ :i |\x0a\x09\x09\x09(oldChildren at: i) ~= (newChildren at: i)\x0a\x09\x09] ifNone: [ \x22no change\x22 ^ aNode ] ].\x0a\x09^ aNode copy dagChildren: newChildren; yourself",
+referencedClasses: [],
+//>>excludeEnd("ide");
+messageSends: ["dagChildren", "visitAllChildren:", "ifTrue:", "=", "size", "detect:ifNone:", "to:", "~=", "at:", "dagChildren:", "copy", "yourself"]
+}),
+$globals.AbstractDagVisitor);
+
+$core.addMethod(
+$core.method({
+selector: "visitDagNodeVariantSimple:",
+protocol: 'visiting',
+fn: function (aNode){
+var self=this;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+return $core.withContext(function($ctx1) {
+//>>excludeEnd("ctx");
+self._visitAllChildren_(aNode);
+return aNode;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+}, function($ctx1) {$ctx1.fill(self,"visitDagNodeVariantSimple:",{aNode:aNode},$globals.AbstractDagVisitor)});
+//>>excludeEnd("ctx");
+},
+//>>excludeStart("ide", pragmas.excludeIdeData);
+args: ["aNode"],
+source: "visitDagNodeVariantSimple: aNode\x0a\x09\x22Simple implementation of visitDagNode:.\x0a\x09Visits children, then returns aNode\x22\x0a\x0a\x09self visitAllChildren: aNode.\x0a\x09^ aNode",
+referencedClasses: [],
+//>>excludeEnd("ide");
+messageSends: ["visitAllChildren:"]
+}),
+$globals.AbstractDagVisitor);
+
+
+
+$core.addClass('PathDagVisitor', $globals.AbstractDagVisitor, ['path'], 'Kernel-Dag');
+//>>excludeStart("ide", pragmas.excludeIdeData);
+$globals.PathDagVisitor.comment="I am base class of `DagNode` visitor.\x0a\x0aI hold the path of ancestors up to actual node\x0ain `self path`.";
+//>>excludeEnd("ide");
+$core.addMethod(
+$core.method({
+selector: "initialize",
+protocol: 'initialization',
+fn: function (){
+var self=this;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+return $core.withContext(function($ctx1) {
+//>>excludeEnd("ctx");
+(
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+$ctx1.supercall = true,
+//>>excludeEnd("ctx");
+($globals.PathDagVisitor.superclass||$boot.nilAsClass).fn.prototype._initialize.apply($recv(self), []));
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+$ctx1.supercall = false;
+//>>excludeEnd("ctx");;
+self["@path"]=[];
+return self;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+}, function($ctx1) {$ctx1.fill(self,"initialize",{},$globals.PathDagVisitor)});
+//>>excludeEnd("ctx");
+},
+//>>excludeStart("ide", pragmas.excludeIdeData);
+args: [],
+source: "initialize\x0a\x09super initialize.\x0a\x0a\x09path := #()",
+referencedClasses: [],
+//>>excludeEnd("ide");
+messageSends: ["initialize"]
+}),
+$globals.PathDagVisitor);
+
+$core.addMethod(
+$core.method({
+selector: "path",
+protocol: 'accessing',
+fn: function (){
+var self=this;
+return self["@path"];
+
+},
+//>>excludeStart("ide", pragmas.excludeIdeData);
+args: [],
+source: "path\x0a\x09^ path",
+referencedClasses: [],
+//>>excludeEnd("ide");
+messageSends: []
+}),
+$globals.PathDagVisitor);
+
+$core.addMethod(
+$core.method({
+selector: "visit:",
+protocol: 'visiting',
+fn: function (aNode){
+var self=this;
+var oldPath,result;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+return $core.withContext(function($ctx1) {
+//>>excludeEnd("ctx");
+result=aNode;
+oldPath=self["@path"];
+$recv((function(){
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+return $core.withContext(function($ctx2) {
+//>>excludeEnd("ctx");
+self["@path"]=$recv(self["@path"]).__comma([aNode]);
+self["@path"];
+result=(
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+$ctx2.supercall = true,
+//>>excludeEnd("ctx");
+($globals.PathDagVisitor.superclass||$boot.nilAsClass).fn.prototype._visit_.apply($recv(self), [aNode]));
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+$ctx2.supercall = false;
+//>>excludeEnd("ctx");;
+return result;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+}, function($ctx2) {$ctx2.fillBlock({},$ctx1,1)});
+//>>excludeEnd("ctx");
+}))._ensure_((function(){
+self["@path"]=oldPath;
+return self["@path"];
+
+}));
+return result;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+}, function($ctx1) {$ctx1.fill(self,"visit:",{aNode:aNode,oldPath:oldPath,result:result},$globals.PathDagVisitor)});
+//>>excludeEnd("ctx");
+},
+//>>excludeStart("ide", pragmas.excludeIdeData);
+args: ["aNode"],
+source: "visit: aNode\x0a\x09| oldPath result |\x0a\x09result := aNode.\x0a\x09oldPath := path.\x0a\x09[\x0a\x09\x09path := path, {aNode}.\x0a\x09\x09result := super visit: aNode\x0a\x09] ensure: [ path := oldPath ].\x0a\x09^ result",
+referencedClasses: [],
+//>>excludeEnd("ide");
+messageSends: ["ensure:", ",", "visit:"]
+}),
+$globals.PathDagVisitor);
+
+$core.addMethod(
+$core.method({
+selector: "visitDagNodeVariantRedux:",
+protocol: 'visiting',
+fn: function (aNode){
+var self=this;
+var newNode;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+return $core.withContext(function($ctx1) {
+//>>excludeEnd("ctx");
+var $1;
+newNode=(
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+$ctx1.supercall = true,
+//>>excludeEnd("ctx");
+($globals.PathDagVisitor.superclass||$boot.nilAsClass).fn.prototype._visitDagNodeVariantRedux_.apply($recv(self), [aNode]));
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+$ctx1.supercall = false;
+//>>excludeEnd("ctx");;
+$1=$recv(aNode).__eq_eq(newNode);
+if(!$core.assert($1)){
+$recv(self["@path"])._at_put_($recv(self["@path"])._size(),newNode);
+};
+return newNode;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+}, function($ctx1) {$ctx1.fill(self,"visitDagNodeVariantRedux:",{aNode:aNode,newNode:newNode},$globals.PathDagVisitor)});
+//>>excludeEnd("ctx");
+},
+//>>excludeStart("ide", pragmas.excludeIdeData);
+args: ["aNode"],
+source: "visitDagNodeVariantRedux: aNode\x0a\x09| newNode |\x0a\x09newNode := super visitDagNodeVariantRedux: aNode.\x0a\x09aNode == newNode ifFalse: [ path at: path size put: newNode ].\x0a\x09^ newNode",
+referencedClasses: [],
+//>>excludeEnd("ide");
+messageSends: ["visitDagNodeVariantRedux:", "ifFalse:", "==", "at:put:", "size"]
+}),
+$globals.PathDagVisitor);
+
+
+
+$core.addClass('DagNode', $globals.Object, [], 'Kernel-Dag');
+//>>excludeStart("ide", pragmas.excludeIdeData);
+$globals.DagNode.comment="I am the abstract root class of any directed acyclic graph.\x0a\x0aConcrete classes should implement `dagChildren` and `dagChildren:`\x0ato get / set direct successor nodes (aka child nodes / subnodes).";
+//>>excludeEnd("ide");
+$core.addMethod(
+$core.method({
+selector: "acceptDagVisitor:",
+protocol: 'visiting',
+fn: function (aVisitor){
+var self=this;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+return $core.withContext(function($ctx1) {
+//>>excludeEnd("ctx");
+return $recv(aVisitor)._visitDagNode_(self);
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+}, function($ctx1) {$ctx1.fill(self,"acceptDagVisitor:",{aVisitor:aVisitor},$globals.DagNode)});
+//>>excludeEnd("ctx");
+},
+//>>excludeStart("ide", pragmas.excludeIdeData);
+args: ["aVisitor"],
+source: "acceptDagVisitor: aVisitor\x0a\x09^ aVisitor visitDagNode: self",
+referencedClasses: [],
+//>>excludeEnd("ide");
+messageSends: ["visitDagNode:"]
+}),
+$globals.DagNode);
+
+$core.addMethod(
+$core.method({
+selector: "allDagChildren",
+protocol: 'accessing',
+fn: function (){
+var self=this;
+var allNodes;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+return $core.withContext(function($ctx1) {
+//>>excludeEnd("ctx");
+var $1;
+$1=self._dagChildren();
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+$ctx1.sendIdx["dagChildren"]=1;
+//>>excludeEnd("ctx");
+allNodes=$recv($1)._asSet();
+$recv(self._dagChildren())._do_((function(each){
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+return $core.withContext(function($ctx2) {
+//>>excludeEnd("ctx");
+return $recv(allNodes)._addAll_($recv(each)._allDagChildren());
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+}, function($ctx2) {$ctx2.fillBlock({each:each},$ctx1,1)});
+//>>excludeEnd("ctx");
+}));
+return allNodes;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+}, function($ctx1) {$ctx1.fill(self,"allDagChildren",{allNodes:allNodes},$globals.DagNode)});
+//>>excludeEnd("ctx");
+},
+//>>excludeStart("ide", pragmas.excludeIdeData);
+args: [],
+source: "allDagChildren\x0a\x09| allNodes |\x0a\x09\x0a\x09allNodes := self dagChildren asSet.\x0a\x09self dagChildren do: [ :each | \x0a\x09\x09allNodes addAll: each allDagChildren ].\x0a\x09\x0a\x09^ allNodes",
+referencedClasses: [],
+//>>excludeEnd("ide");
+messageSends: ["asSet", "dagChildren", "do:", "addAll:", "allDagChildren"]
+}),
+$globals.DagNode);
+
+$core.addMethod(
+$core.method({
+selector: "dagChildren",
+protocol: 'accessing',
+fn: function (){
+var self=this;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+return $core.withContext(function($ctx1) {
+//>>excludeEnd("ctx");
+self._subclassResponsibility();
+return self;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+}, function($ctx1) {$ctx1.fill(self,"dagChildren",{},$globals.DagNode)});
+//>>excludeEnd("ctx");
+},
+//>>excludeStart("ide", pragmas.excludeIdeData);
+args: [],
+source: "dagChildren\x0a\x09self subclassResponsibility",
+referencedClasses: [],
+//>>excludeEnd("ide");
+messageSends: ["subclassResponsibility"]
+}),
+$globals.DagNode);
+
+$core.addMethod(
+$core.method({
+selector: "dagChildren:",
+protocol: 'accessing',
+fn: function (aCollection){
+var self=this;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+return $core.withContext(function($ctx1) {
+//>>excludeEnd("ctx");
+self._subclassResponsibility();
+return self;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+}, function($ctx1) {$ctx1.fill(self,"dagChildren:",{aCollection:aCollection},$globals.DagNode)});
+//>>excludeEnd("ctx");
+},
+//>>excludeStart("ide", pragmas.excludeIdeData);
+args: ["aCollection"],
+source: "dagChildren: aCollection\x0a\x09self subclassResponsibility",
+referencedClasses: [],
+//>>excludeEnd("ide");
+messageSends: ["subclassResponsibility"]
+}),
+$globals.DagNode);
+
+$core.addMethod(
+$core.method({
+selector: "isDagNode",
+protocol: 'testing',
+fn: function (){
+var self=this;
+return true;
+
+},
+//>>excludeStart("ide", pragmas.excludeIdeData);
+args: [],
+source: "isDagNode\x0a\x09^ true",
+referencedClasses: [],
+//>>excludeEnd("ide");
+messageSends: []
+}),
+$globals.DagNode);
+
+
+
+$core.addClass('DagParentNode', $globals.DagNode, ['nodes'], 'Kernel-Dag');
+//>>excludeStart("ide", pragmas.excludeIdeData);
+$globals.DagParentNode.comment="I am `DagNode` that stores a collection of its children,\x0alazy initialized to empty array.\x0a\x0aI can `addDagChild:` to add a child.";
+//>>excludeEnd("ide");
+$core.addMethod(
+$core.method({
+selector: "addDagChild:",
+protocol: 'accessing',
+fn: function (aDagNode){
+var self=this;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+return $core.withContext(function($ctx1) {
+//>>excludeEnd("ctx");
+$recv(self._dagChildren())._add_(aDagNode);
+return self;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+}, function($ctx1) {$ctx1.fill(self,"addDagChild:",{aDagNode:aDagNode},$globals.DagParentNode)});
+//>>excludeEnd("ctx");
+},
+//>>excludeStart("ide", pragmas.excludeIdeData);
+args: ["aDagNode"],
+source: "addDagChild: aDagNode\x0a\x09self dagChildren add: aDagNode",
+referencedClasses: [],
+//>>excludeEnd("ide");
+messageSends: ["add:", "dagChildren"]
+}),
+$globals.DagParentNode);
+
+$core.addMethod(
+$core.method({
+selector: "dagChildren",
+protocol: 'accessing',
+fn: function (){
+var self=this;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+return $core.withContext(function($ctx1) {
+//>>excludeEnd("ctx");
+var $1,$receiver;
+$1=self["@nodes"];
+if(($receiver = $1) == null || $receiver.isNil){
+self["@nodes"]=$recv($globals.Array)._new();
+return self["@nodes"];
+} else {
+return $1;
+};
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+}, function($ctx1) {$ctx1.fill(self,"dagChildren",{},$globals.DagParentNode)});
+//>>excludeEnd("ctx");
+},
+//>>excludeStart("ide", pragmas.excludeIdeData);
+args: [],
+source: "dagChildren\x0a\x09^ nodes ifNil: [ nodes := Array new ]",
+referencedClasses: ["Array"],
+//>>excludeEnd("ide");
+messageSends: ["ifNil:", "new"]
+}),
+$globals.DagParentNode);
+
+$core.addMethod(
+$core.method({
+selector: "dagChildren:",
+protocol: 'accessing',
+fn: function (aCollection){
+var self=this;
+self["@nodes"]=aCollection;
+return self;
+
+},
+//>>excludeStart("ide", pragmas.excludeIdeData);
+args: ["aCollection"],
+source: "dagChildren: aCollection\x0a\x09nodes := aCollection",
+referencedClasses: [],
+//>>excludeEnd("ide");
+messageSends: []
+}),
+$globals.DagParentNode);
+
+
+
+$core.addClass('DagSink', $globals.DagNode, ['nodes'], 'Kernel-Dag');
+//>>excludeStart("ide", pragmas.excludeIdeData);
+$globals.DagSink.comment="I am `DagNode` with no direct successors.\x0a\x0aSending `dagChildren:` with empty collection is legal.";
+//>>excludeEnd("ide");
+$core.addMethod(
+$core.method({
+selector: "dagChildren",
+protocol: 'accessing',
+fn: function (){
+var self=this;
+return [];
+
+},
+//>>excludeStart("ide", pragmas.excludeIdeData);
+args: [],
+source: "dagChildren\x0a\x09^ #()",
+referencedClasses: [],
+//>>excludeEnd("ide");
+messageSends: []
+}),
+$globals.DagSink);
+
+$core.addMethod(
+$core.method({
+selector: "dagChildren:",
+protocol: 'accessing',
+fn: function (aCollection){
+var self=this;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+return $core.withContext(function($ctx1) {
+//>>excludeEnd("ctx");
+$recv(aCollection)._ifNotEmpty_((function(){
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+return $core.withContext(function($ctx2) {
+//>>excludeEnd("ctx");
+return self._error_("A DagSink cannot have children.");
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+}, function($ctx2) {$ctx2.fillBlock({},$ctx1,1)});
+//>>excludeEnd("ctx");
+}));
+return self;
+//>>excludeStart("ctx", pragmas.excludeDebugContexts);
+}, function($ctx1) {$ctx1.fill(self,"dagChildren:",{aCollection:aCollection},$globals.DagSink)});
+//>>excludeEnd("ctx");
+},
+//>>excludeStart("ide", pragmas.excludeIdeData);
+args: ["aCollection"],
+source: "dagChildren: aCollection\x0a\x09aCollection ifNotEmpty: [ self error: 'A DagSink cannot have children.' ]",
+referencedClasses: [],
+//>>excludeEnd("ide");
+messageSends: ["ifNotEmpty:", "error:"]
+}),
+$globals.DagSink);
+
+
+$core.addMethod(
+$core.method({
+selector: "isDagNode",
+protocol: '*Kernel-Dag',
+fn: function (){
+var self=this;
+return false;
+
+},
+//>>excludeStart("ide", pragmas.excludeIdeData);
+args: [],
+source: "isDagNode\x0a\x09^ false",
+referencedClasses: [],
+//>>excludeEnd("ide");
+messageSends: []
+}),
+$globals.Object);
+
+});

+ 185 - 0
src/Kernel-Dag.st

@@ -0,0 +1,185 @@
+Smalltalk createPackage: 'Kernel-Dag'!
+Object subclass: #AbstractDagVisitor
+	instanceVariableNames: ''
+	package: 'Kernel-Dag'!
+!AbstractDagVisitor commentStamp!
+I am base class of `DagNode` visitor.
+
+Concrete classes should implement `visitDagNode:`,
+they can reuse possible variants of implementation
+offered directly: `visitDagNodeVariantSimple:`
+and `visitDagNodeVariantRedux:`.!
+
+!AbstractDagVisitor methodsFor: 'visiting'!
+
+visit: aNode
+	^ aNode acceptDagVisitor: self
+!
+
+visitAll: aCollection
+	^ aCollection collect: [ :each | self visit: each ]
+!
+
+visitAllChildren: aDagNode
+	^ self visitAll: aDagNode dagChildren
+!
+
+visitDagNode: aNode
+	self subclassResponsibility
+!
+
+visitDagNodeVariantRedux: aNode
+	"Immutable-guarded implementation of visitDagNode:.
+	Visits all children and checks if there were changes.
+	If not, returns aNode.
+	If yes, returns copy of aNode with new children."
+
+	| newChildren oldChildren |
+	oldChildren := aNode dagChildren.
+	newChildren := self visitAllChildren: aNode.
+	oldChildren size = newChildren size ifTrue: [
+		(1 to: oldChildren size) detect: [ :i |
+			(oldChildren at: i) ~= (newChildren at: i)
+		] ifNone: [ "no change" ^ aNode ] ].
+	^ aNode copy dagChildren: newChildren; yourself
+!
+
+visitDagNodeVariantSimple: aNode
+	"Simple implementation of visitDagNode:.
+	Visits children, then returns aNode"
+
+	self visitAllChildren: aNode.
+	^ aNode
+! !
+
+AbstractDagVisitor subclass: #PathDagVisitor
+	instanceVariableNames: 'path'
+	package: 'Kernel-Dag'!
+!PathDagVisitor commentStamp!
+I am base class of `DagNode` visitor.
+
+I hold the path of ancestors up to actual node
+in `self path`.!
+
+!PathDagVisitor methodsFor: 'accessing'!
+
+path
+	^ path
+! !
+
+!PathDagVisitor methodsFor: 'initialization'!
+
+initialize
+	super initialize.
+
+	path := #()
+! !
+
+!PathDagVisitor methodsFor: 'visiting'!
+
+visit: aNode
+	| oldPath result |
+	result := aNode.
+	oldPath := path.
+	[
+		path := path, {aNode}.
+		result := super visit: aNode
+	] ensure: [ path := oldPath ].
+	^ result
+!
+
+visitDagNodeVariantRedux: aNode
+	| newNode |
+	newNode := super visitDagNodeVariantRedux: aNode.
+	aNode == newNode ifFalse: [ path at: path size put: newNode ].
+	^ newNode
+! !
+
+Object subclass: #DagNode
+	instanceVariableNames: ''
+	package: 'Kernel-Dag'!
+!DagNode commentStamp!
+I am the abstract root class of any directed acyclic graph.
+
+Concrete classes should implement `dagChildren` and `dagChildren:`
+to get / set direct successor nodes (aka child nodes / subnodes).!
+
+!DagNode methodsFor: 'accessing'!
+
+allDagChildren
+	| allNodes |
+	
+	allNodes := self dagChildren asSet.
+	self dagChildren do: [ :each | 
+		allNodes addAll: each allDagChildren ].
+	
+	^ allNodes
+!
+
+dagChildren
+	self subclassResponsibility
+!
+
+dagChildren: aCollection
+	self subclassResponsibility
+! !
+
+!DagNode methodsFor: 'testing'!
+
+isDagNode
+	^ true
+! !
+
+!DagNode methodsFor: 'visiting'!
+
+acceptDagVisitor: aVisitor
+	^ aVisitor visitDagNode: self
+! !
+
+DagNode subclass: #DagParentNode
+	instanceVariableNames: 'nodes'
+	package: 'Kernel-Dag'!
+!DagParentNode commentStamp!
+I am `DagNode` that stores a collection of its children,
+lazy initialized to empty array.
+
+I can `addDagChild:` to add a child.!
+
+!DagParentNode methodsFor: 'accessing'!
+
+addDagChild: aDagNode
+	self dagChildren add: aDagNode
+!
+
+dagChildren
+	^ nodes ifNil: [ nodes := Array new ]
+!
+
+dagChildren: aCollection
+	nodes := aCollection
+! !
+
+DagNode subclass: #DagSink
+	instanceVariableNames: 'nodes'
+	package: 'Kernel-Dag'!
+!DagSink commentStamp!
+I am `DagNode` with no direct successors.
+
+Sending `dagChildren:` with empty collection is legal.!
+
+!DagSink methodsFor: 'accessing'!
+
+dagChildren
+	^ #()
+!
+
+dagChildren: aCollection
+	aCollection ifNotEmpty: [ self error: 'A DagSink cannot have children.' ]
+! !
+
+!Object methodsFor: '*Kernel-Dag'!
+
+isDagNode
+	^ false
+! !
+

+ 1 - 0
support/deploy.js

@@ -7,6 +7,7 @@ define([
     'amber_core/Kernel-Classes',
     'amber_core/Kernel-Methods',
     'amber_core/Kernel-Collections',
+    'amber_core/Kernel-Dag',
     'amber_core/Kernel-Infrastructure',
     'amber_core/Kernel-Promises',
     'amber_core/Kernel-Exceptions',

+ 7 - 7
support/parser.js

@@ -134,7 +134,7 @@ $globals.SmalltalkParser = (function() {
                              return $globals.DynamicArrayNode._new()
                                     ._location_(location())
                                     ._source_(text())
-                                    ._nodes_(expressions || []);
+                                    ._dagChildren_(expressions || []);
                          },
         peg$c66 = "#{",
         peg$c67 = { type: "literal", value: "#{", description: "\"#{\"" },
@@ -142,7 +142,7 @@ $globals.SmalltalkParser = (function() {
                                 return $globals.DynamicDictionaryNode._new()
                                        ._location_(location())
                                        ._source_(text())
-                                       ._nodes_(expressions || []);
+                                       ._dagChildren_(expressions || []);
                             },
         peg$c69 = "true",
         peg$c70 = { type: "literal", value: "true", description: "\"true\"" },
@@ -197,7 +197,7 @@ $globals.SmalltalkParser = (function() {
                              return $globals.ReturnNode._new()
                                     ._location_(location())
                                     ._source_(text())
-                                    ._nodes_([expression]);
+                                    ._dagChildren_([expression]);
                          },
         peg$c95 = "|",
         peg$c96 = { type: "literal", value: "|", description: "\"|\"" },
@@ -220,7 +220,7 @@ $globals.SmalltalkParser = (function() {
                                     ._location_(location())
                                     ._source_(text())
                                     ._temps_(temps || [])
-                                    ._nodes_(statements || []);
+                                    ._dagChildren_(statements || []);
                          },
         peg$c106 = "[",
         peg$c107 = { type: "literal", value: "[", description: "\"[\"" },
@@ -231,7 +231,7 @@ $globals.SmalltalkParser = (function() {
                                     ._location_(location())
                                     ._source_(text())
                                     ._parameters_(params || [])
-                                    ._nodes_([sequence._asBlockSequenceNode()]);
+                                    ._dagChildren_([sequence._asBlockSequenceNode()]);
                          },
         peg$c111 = function(selector) {
                              return $globals.SendNode._new()
@@ -292,7 +292,7 @@ $globals.SmalltalkParser = (function() {
                              return $globals.CascadeNode._new()
                                     ._location_(location())
                                     ._source_(text())
-                                    ._nodes_(messages);
+                                    ._dagChildren_(messages);
                          },
         peg$c122 = "<",
         peg$c123 = { type: "literal", value: "<", description: "\"<\"" },
@@ -322,7 +322,7 @@ $globals.SmalltalkParser = (function() {
                                      ._source_(text())
                                      ._selector_(pattern[0])
                                      ._arguments_(pattern[1])
-                                     ._nodes_([sequence]);
+                                     ._dagChildren_([sequence]);
                          },
         peg$c136 = function(send) { return send._isSendNode() && send._selector() === "->" },
         peg$c137 = function(send) { return [send._receiver(), send._arguments()[0]]; },

+ 7 - 7
support/parser.pegjs

@@ -60,13 +60,13 @@ dynamicArray   = "{" ws expressions:expressions? maybeDotsWs "}" {
                      return $globals.DynamicArrayNode._new()
                             ._location_(location())
                             ._source_(text())
-                            ._nodes_(expressions || []);
+                            ._dagChildren_(expressions || []);
                  }
 dynamicDictionary = "#{" ws expressions:associations? maybeDotsWs  "}" {
                         return $globals.DynamicDictionaryNode._new()
                                ._location_(location())
                                ._source_(text())
-                               ._nodes_(expressions || []);
+                               ._dagChildren_(expressions || []);
                     }
 pseudoVariable = val:(
                    'true' {return true;}
@@ -123,7 +123,7 @@ ret            = '^' ws expression:expression {
                      return $globals.ReturnNode._new()
                             ._location_(location())
                             ._source_(text())
-                            ._nodes_([expression]);
+                            ._dagChildren_([expression]);
                  }
   
 temps          = "|" vars:(ws variable:identifier {return variable;})* ws "|" {return vars;}
@@ -149,7 +149,7 @@ wsStSequenceWs    = ws temps:temps? maybeDotsWs statements:statementsWs? {
                             ._location_(location())
                             ._source_(text())
                             ._temps_(temps || [])
-                            ._nodes_(statements || []);
+                            ._dagChildren_(statements || []);
                  }
 
 jsSequence     = jsStatement
@@ -159,7 +159,7 @@ block          = '[' params:wsBlockParamList? sequence:wsSequenceWs? ']' {
                             ._location_(location())
                             ._source_(text())
                             ._parameters_(params || [])
-                            ._nodes_([sequence._asBlockSequenceNode()]);
+                            ._dagChildren_([sequence._asBlockSequenceNode()]);
                  }
 
 operand        = literal / reference / subexpression
@@ -248,7 +248,7 @@ cascade        = send:keywordSend & { return send._isSendNode(); } messages:(ws
                      return $globals.CascadeNode._new()
                             ._location_(location())
                             ._source_(text())
-                            ._nodes_(messages);
+                            ._dagChildren_(messages);
                  }
 
 jsStatement    = pragmaJsStatement / legacyJsStatement
@@ -273,7 +273,7 @@ method         = pattern:(wsKeywordPattern / wsBinaryPattern / wsUnaryPattern) s
                              ._source_(text())
                              ._selector_(pattern[0])
                              ._arguments_(pattern[1])
-                             ._nodes_([sequence]);
+                             ._dagChildren_([sequence]);
                  }
 
 

Some files were not shown because too many files changed in this diff