Browse Source

AST Node / Visitor as Dag Node / Visitor.

Herbert Vojčík 7 years ago
parent
commit
155c1ab8d3

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


+ 53 - 113
src/Compiler-AST.st

@@ -1,6 +1,6 @@
 Smalltalk createPackage: 'Compiler-AST'!
-Object subclass: #Node
-	instanceVariableNames: 'parent position source nodes shouldBeInlined shouldBeAliased'
+DagParentNode subclass: #Node
+	instanceVariableNames: 'parent position source shouldBeInlined shouldBeAliased'
 	package: 'Compiler-AST'!
 !Node commentStamp!
 I am the abstract root class of the abstract syntax tree.
@@ -11,21 +11,6 @@ Concrete classes should implement `#accept:` to allow visiting.
 
 !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
-!
-
 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
 !
@@ -111,20 +92,6 @@ 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'!
 
 inPosition: aPoint
@@ -157,7 +124,7 @@ isJSStatementNode
 !
 
 isLastChild
-	^ self parent nodes last = self
+	^ self parent dagChildren last = self
 !
 
 isNavigationNode
@@ -209,20 +176,14 @@ 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
 !
 
 subtreeNeedsAliasing
 	^ (self shouldBeAliased or: [ self shouldBeInlined ]) or: [
-		self nodes anySatisfy: [ :each | each subtreeNeedsAliasing ] ]
-! !
-
-!Node methodsFor: 'visiting'!
-
-accept: aVisitor
-	^ aVisitor visitNode: self
+		self dagChildren anySatisfy: [ :each | each subtreeNeedsAliasing ] ]
 ! !
 
 Node subclass: #AssignmentNode
@@ -233,17 +194,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
@@ -251,8 +211,7 @@ right
 !
 
 right: aNode
-	right := aNode.
-	aNode parent: self
+	right := aNode
 ! !
 
 !AssignmentNode methodsFor: 'testing'!
@@ -267,7 +226,7 @@ shouldBeAliased
 
 !AssignmentNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitAssignmentNode: self
 ! !
 
@@ -307,7 +266,7 @@ subtreeNeedsAliasing
 
 !BlockNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitBlockNode: self
 ! !
 
@@ -339,7 +298,7 @@ subtreeNeedsAliasing
 
 !CascadeNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitCascadeNode: self
 ! !
 
@@ -351,7 +310,7 @@ I represent an dynamic array node.!
 
 !DynamicArrayNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitDynamicArrayNode: self
 ! !
 
@@ -363,7 +322,7 @@ I represent an dynamic dictionary node.!
 
 !DynamicDictionaryNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitDynamicDictionaryNode: self
 ! !
 
@@ -385,7 +344,7 @@ requiresSmalltalkContext
 
 !JSStatementNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitJSStatementNode: self
 ! !
 
@@ -448,7 +407,7 @@ sendIndexes: aDictionary
 !
 
 sequenceNode
-	self nodes do: [ :each |
+	self dagChildren do: [ :each |
 		each isSequenceNode ifTrue: [ ^ each ] ].
 		
 	^ nil
@@ -464,7 +423,7 @@ source: aString
 
 !MethodNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitMethodNode: self
 ! !
 
@@ -496,7 +455,7 @@ nonLocalReturn
 
 !ReturnNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitReturnNode: self
 ! !
 
@@ -513,19 +472,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
 !
 
@@ -541,22 +495,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
@@ -619,7 +563,7 @@ shouldBeAliased
 
 !SendNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitSendNode: self
 ! !
 
@@ -653,7 +597,7 @@ asBlockSequenceNode
 	^ BlockSequenceNode new
 		position: self position;
 		source: self source;
-		nodes: self nodes;
+		dagChildren: self dagChildren;
 		temps: self temps;
 		yourself
 ! !
@@ -666,7 +610,7 @@ isSequenceNode
 
 !SequenceNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitSequenceNode: self
 ! !
 
@@ -684,7 +628,7 @@ isBlockSequenceNode
 
 !BlockSequenceNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitBlockSequenceNode: self
 ! !
 
@@ -716,7 +660,7 @@ isValueNode
 
 !ValueNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitValueNode: self
 ! !
 
@@ -781,11 +725,11 @@ isVariableNode
 
 !VariableNode methodsFor: 'visiting'!
 
-accept: aVisitor
+acceptDagVisitor: aVisitor
 	^ aVisitor visitVariableNode: self
 ! !
 
-Object subclass: #NodeVisitor
+PathDagVisitor subclass: #NodeVisitor
 	instanceVariableNames: ''
 	package: 'Compiler-AST'!
 !NodeVisitor commentStamp!
@@ -794,19 +738,16 @@ 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 ]
+	self path ifNotEmpty: [ :p | aNode parent: p last ].
+	^ super visit: aNode
 !
 
 visitAssignmentNode: aNode
-	^ self visitNode: aNode
+	^ self visitDagNode: aNode
 !
 
 visitBlockNode: aNode
-	^ self visitNode: aNode
+	^ self visitDagNode: aNode
 !
 
 visitBlockSequenceNode: aNode
@@ -814,48 +755,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'!

+ 39 - 39
src/Compiler-IR.js

@@ -410,7 +410,7 @@ $ctx2.sendIdx["add:"]=1;
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx1.sendIdx["do:"]=1;
 //>>excludeEnd("ctx");
-$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");
@@ -426,10 +426,10 @@ return closure;
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["aNode"],
-source: "visitBlockNode: aNode\x0a\x09| closure |\x0a\x09closure := IRClosure new\x0a\x09\x09arguments: aNode parameters;\x0a\x09\x09requiresSmalltalkContext: aNode requiresSmalltalkContext;\x0a\x09\x09scope: aNode scope;\x0a\x09\x09yourself.\x0a\x09aNode scope temps do: [ :each |\x0a\x09\x09closure add: (IRTempDeclaration new\x0a\x09\x09\x09name: each name;\x0a\x09\x09\x09scope: aNode scope;\x0a\x09\x09\x09yourself) ].\x0a\x09aNode nodes do: [ :each | closure add: (self visit: each) ].\x0a\x09^ closure",
+source: "visitBlockNode: aNode\x0a\x09| closure |\x0a\x09closure := IRClosure new\x0a\x09\x09arguments: aNode parameters;\x0a\x09\x09requiresSmalltalkContext: aNode requiresSmalltalkContext;\x0a\x09\x09scope: aNode scope;\x0a\x09\x09yourself.\x0a\x09aNode scope temps do: [ :each |\x0a\x09\x09closure add: (IRTempDeclaration new\x0a\x09\x09\x09name: each name;\x0a\x09\x09\x09scope: aNode scope;\x0a\x09\x09\x09yourself) ].\x0a\x09aNode dagChildren do: [ :each | closure add: (self visit: each) ].\x0a\x09^ closure",
 referencedClasses: ["IRClosure", "IRTempDeclaration"],
 //>>excludeEnd("ide");
-messageSends: ["arguments:", "new", "parameters", "requiresSmalltalkContext:", "requiresSmalltalkContext", "scope:", "scope", "yourself", "do:", "temps", "add:", "name:", "name", "nodes", "visit:"]
+messageSends: ["arguments:", "new", "parameters", "requiresSmalltalkContext:", "requiresSmalltalkContext", "scope:", "scope", "yourself", "do:", "temps", "add:", "name:", "name", "dagChildren", "visit:"]
 }),
 $globals.IRASTTranslator);
 
@@ -451,17 +451,17 @@ return self._withSequence_do_($1,(function(){
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 return $core.withContext(function($ctx2) {
 //>>excludeEnd("ctx");
-$2=$recv(aNode)._nodes();
+$2=$recv(aNode)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx2.sendIdx["nodes"]=1;
+$ctx2.sendIdx["dagChildren"]=1;
 //>>excludeEnd("ctx");
 return $recv($2)._ifNotEmpty_((function(){
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 return $core.withContext(function($ctx3) {
 //>>excludeEnd("ctx");
-$4=$recv(aNode)._nodes();
+$4=$recv(aNode)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx3.sendIdx["nodes"]=2;
+$ctx3.sendIdx["dagChildren"]=2;
 //>>excludeEnd("ctx");
 $3=$recv($4)._allButLast();
 $recv($3)._do_((function(each){
@@ -484,9 +484,9 @@ $ctx4.sendIdx["add:"]=1;
 }, function($ctx4) {$ctx4.fillBlock({each:each},$ctx3,3)});
 //>>excludeEnd("ctx");
 }));
-$9=$recv(aNode)._nodes();
+$9=$recv(aNode)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx3.sendIdx["nodes"]=3;
+$ctx3.sendIdx["dagChildren"]=3;
 //>>excludeEnd("ctx");
 $8=$recv($9)._last();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
@@ -494,16 +494,16 @@ $ctx3.sendIdx["last"]=1;
 //>>excludeEnd("ctx");
 $7=$recv($8)._isReturnNode();
 if($core.assert($7)){
-return $recv(self._sequence())._add_(self._visitOrAlias_($recv($recv(aNode)._nodes())._last()));
+return $recv(self._sequence())._add_(self._visitOrAlias_($recv($recv(aNode)._dagChildren())._last()));
 } else {
 $10=self._sequence();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx3.sendIdx["sequence"]=2;
 //>>excludeEnd("ctx");
 $12=$recv($globals.IRBlockReturn)._new();
-$15=$recv(aNode)._nodes();
+$15=$recv(aNode)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx3.sendIdx["nodes"]=4;
+$ctx3.sendIdx["dagChildren"]=4;
 //>>excludeEnd("ctx");
 $14=$recv($15)._last();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
@@ -537,10 +537,10 @@ $ctx3.sendIdx["add:"]=2;
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["aNode"],
-source: "visitBlockSequenceNode: aNode\x0a\x09^ self\x0a\x09\x09withSequence: IRBlockSequence new\x0a\x09\x09do: [\x0a\x09\x09\x09aNode nodes ifNotEmpty: [\x0a\x09\x09\x09\x09aNode nodes allButLast do: [ :each |\x0a\x09\x09\x09\x09\x09self sequence add: (self visitOrAlias: each) ].\x0a\x09\x09\x09\x09aNode nodes last isReturnNode\x0a\x09\x09\x09\x09\x09ifFalse: [ self sequence add: (IRBlockReturn new add: (self visitOrAlias: aNode nodes last); yourself) ]\x0a\x09\x09\x09\x09\x09ifTrue: [ self sequence add: (self visitOrAlias: aNode nodes last) ] ]]",
+source: "visitBlockSequenceNode: aNode\x0a\x09^ self\x0a\x09\x09withSequence: IRBlockSequence new\x0a\x09\x09do: [\x0a\x09\x09\x09aNode dagChildren ifNotEmpty: [\x0a\x09\x09\x09\x09aNode dagChildren allButLast do: [ :each |\x0a\x09\x09\x09\x09\x09self sequence add: (self visitOrAlias: each) ].\x0a\x09\x09\x09\x09aNode dagChildren last isReturnNode\x0a\x09\x09\x09\x09\x09ifFalse: [ self sequence add: (IRBlockReturn new add: (self visitOrAlias: aNode dagChildren last); yourself) ]\x0a\x09\x09\x09\x09\x09ifTrue: [ self sequence add: (self visitOrAlias: aNode dagChildren last) ] ]]",
 referencedClasses: ["IRBlockSequence", "IRBlockReturn"],
 //>>excludeEnd("ide");
-messageSends: ["withSequence:do:", "new", "ifNotEmpty:", "nodes", "do:", "allButLast", "add:", "sequence", "visitOrAlias:", "ifFalse:ifTrue:", "isReturnNode", "last", "yourself"]
+messageSends: ["withSequence:do:", "new", "ifNotEmpty:", "dagChildren", "do:", "allButLast", "add:", "sequence", "visitOrAlias:", "ifFalse:ifTrue:", "isReturnNode", "last", "yourself"]
 }),
 $globals.IRASTTranslator);
 
@@ -564,9 +564,9 @@ alias;
 receiver=$recv($recv($globals.VariableNode)._new())._binding_($recv(alias)._variable());
 receiver;
 };
-$2=$recv(aNode)._nodes();
+$2=$recv(aNode)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["nodes"]=1;
+$ctx1.sendIdx["dagChildren"]=1;
 //>>excludeEnd("ctx");
 $recv($2)._do_((function(each){
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
@@ -580,9 +580,9 @@ return $recv(each)._receiver_(receiver);
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx1.sendIdx["do:"]=1;
 //>>excludeEnd("ctx");
-$4=$recv(aNode)._nodes();
+$4=$recv(aNode)._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["nodes"]=2;
+$ctx1.sendIdx["dagChildren"]=2;
 //>>excludeEnd("ctx");
 $3=$recv($4)._allButLast();
 $recv($3)._do_((function(each){
@@ -594,17 +594,17 @@ return $recv(self._sequence())._add_(self._visit_(each));
 }, function($ctx2) {$ctx2.fillBlock({each:each},$ctx1,3)});
 //>>excludeEnd("ctx");
 }));
-return self._visitOrAlias_($recv($recv(aNode)._nodes())._last());
+return self._visitOrAlias_($recv($recv(aNode)._dagChildren())._last());
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 }, function($ctx1) {$ctx1.fill(self,"visitCascadeNode:",{aNode:aNode,receiver:receiver},$globals.IRASTTranslator)});
 //>>excludeEnd("ctx");
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["aNode"],
-source: "visitCascadeNode: aNode\x0a\x09| receiver |\x0a\x09receiver := aNode receiver.\x0a\x09receiver isImmutable ifFalse: [\x0a\x09\x09| alias |\x0a\x09\x09alias := self alias: receiver.\x0a\x09\x09receiver := VariableNode new binding: alias variable ].\x0a\x09aNode nodes do: [ :each | each receiver: receiver ].\x0a\x0a\x09aNode nodes allButLast do: [ :each |\x0a\x09\x09self sequence add: (self visit: each) ].\x0a\x0a\x09^ self visitOrAlias: aNode nodes last",
+source: "visitCascadeNode: aNode\x0a\x09| receiver |\x0a\x09receiver := aNode receiver.\x0a\x09receiver isImmutable ifFalse: [\x0a\x09\x09| alias |\x0a\x09\x09alias := self alias: receiver.\x0a\x09\x09receiver := VariableNode new binding: alias variable ].\x0a\x09aNode dagChildren do: [ :each | each receiver: receiver ].\x0a\x0a\x09aNode dagChildren allButLast do: [ :each |\x0a\x09\x09self sequence add: (self visit: each) ].\x0a\x0a\x09^ self visitOrAlias: aNode dagChildren last",
 referencedClasses: ["VariableNode"],
 //>>excludeEnd("ide");
-messageSends: ["receiver", "ifFalse:", "isImmutable", "alias:", "binding:", "new", "variable", "do:", "nodes", "receiver:", "allButLast", "add:", "sequence", "visit:", "visitOrAlias:", "last"]
+messageSends: ["receiver", "ifFalse:", "isImmutable", "alias:", "binding:", "new", "variable", "do:", "dagChildren", "receiver:", "allButLast", "add:", "sequence", "visit:", "visitOrAlias:", "last"]
 }),
 $globals.IRASTTranslator);
 
@@ -619,7 +619,7 @@ var array;
 return $core.withContext(function($ctx1) {
 //>>excludeEnd("ctx");
 array=$recv($globals.IRDynamicArray)._new();
-$recv(self._aliasTemporally_($recv(aNode)._nodes()))._do_((function(each){
+$recv(self._aliasTemporally_($recv(aNode)._dagChildren()))._do_((function(each){
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 return $core.withContext(function($ctx2) {
 //>>excludeEnd("ctx");
@@ -635,10 +635,10 @@ return array;
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["aNode"],
-source: "visitDynamicArrayNode: aNode\x0a\x09| array |\x0a\x09array := IRDynamicArray new.\x0a\x09(self aliasTemporally: aNode nodes) do: [ :each | array add: each ].\x0a\x09^ array",
+source: "visitDynamicArrayNode: aNode\x0a\x09| array |\x0a\x09array := IRDynamicArray new.\x0a\x09(self aliasTemporally: aNode dagChildren) do: [ :each | array add: each ].\x0a\x09^ array",
 referencedClasses: ["IRDynamicArray"],
 //>>excludeEnd("ide");
-messageSends: ["new", "do:", "aliasTemporally:", "nodes", "add:"]
+messageSends: ["new", "do:", "aliasTemporally:", "dagChildren", "add:"]
 }),
 $globals.IRASTTranslator);
 
@@ -653,7 +653,7 @@ var dictionary;
 return $core.withContext(function($ctx1) {
 //>>excludeEnd("ctx");
 dictionary=$recv($globals.IRDynamicDictionary)._new();
-$recv(self._aliasTemporally_($recv(aNode)._nodes()))._do_((function(each){
+$recv(self._aliasTemporally_($recv(aNode)._dagChildren()))._do_((function(each){
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 return $core.withContext(function($ctx2) {
 //>>excludeEnd("ctx");
@@ -669,10 +669,10 @@ return dictionary;
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["aNode"],
-source: "visitDynamicDictionaryNode: aNode\x0a\x09| dictionary |\x0a\x09dictionary := IRDynamicDictionary new.\x0a\x09(self aliasTemporally: aNode nodes) do: [ :each | dictionary add: each ].\x0a\x09^ dictionary",
+source: "visitDynamicDictionaryNode: aNode\x0a\x09| dictionary |\x0a\x09dictionary := IRDynamicDictionary new.\x0a\x09(self aliasTemporally: aNode dagChildren) do: [ :each | dictionary add: each ].\x0a\x09^ dictionary",
 referencedClasses: ["IRDynamicDictionary"],
 //>>excludeEnd("ide");
-messageSends: ["new", "do:", "aliasTemporally:", "nodes", "add:"]
+messageSends: ["new", "do:", "aliasTemporally:", "dagChildren", "add:"]
 }),
 $globals.IRASTTranslator);
 
@@ -779,7 +779,7 @@ $ctx2.sendIdx["add:"]=1;
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 $ctx1.sendIdx["do:"]=1;
 //>>excludeEnd("ctx");
-$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");
@@ -844,10 +844,10 @@ return self._method();
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["aNode"],
-source: "visitMethodNode: aNode\x0a\x0a\x09self method: (IRMethod new\x0a\x09\x09source: self source crlfSanitized;\x0a\x09\x09theClass: self theClass;\x0a\x09\x09arguments: aNode arguments;\x0a\x09\x09selector: aNode selector;\x0a\x09\x09sendIndexes: aNode sendIndexes;\x0a\x09\x09requiresSmalltalkContext: aNode requiresSmalltalkContext;\x0a\x09\x09classReferences: aNode classReferences;\x0a\x09\x09scope: aNode scope;\x0a\x09\x09yourself).\x0a\x0a\x09aNode scope temps do: [ :each |\x0a\x09\x09self method add: (IRTempDeclaration new\x0a\x09\x09\x09name: each name;\x0a\x09\x09\x09scope: aNode scope;\x0a\x09\x09\x09yourself) ].\x0a\x0a\x09aNode nodes do: [ :each | self method add: (self visit: each) ].\x0a\x0a\x09aNode scope hasLocalReturn ifFalse: [self method\x0a\x09\x09add: (IRReturn new\x0a\x09\x09\x09add: (IRVariable new\x0a\x09\x09\x09\x09variable: (aNode scope pseudoVars at: 'self');\x0a\x09\x09\x09\x09yourself);\x0a\x09\x09\x09yourself);\x0a\x09\x09add: (IRVerbatim new source: ''; yourself) ].\x0a\x0a\x09^ self method",
+source: "visitMethodNode: aNode\x0a\x0a\x09self method: (IRMethod new\x0a\x09\x09source: self source crlfSanitized;\x0a\x09\x09theClass: self theClass;\x0a\x09\x09arguments: aNode arguments;\x0a\x09\x09selector: aNode selector;\x0a\x09\x09sendIndexes: aNode sendIndexes;\x0a\x09\x09requiresSmalltalkContext: aNode requiresSmalltalkContext;\x0a\x09\x09classReferences: aNode classReferences;\x0a\x09\x09scope: aNode scope;\x0a\x09\x09yourself).\x0a\x0a\x09aNode scope temps do: [ :each |\x0a\x09\x09self method add: (IRTempDeclaration new\x0a\x09\x09\x09name: each name;\x0a\x09\x09\x09scope: aNode scope;\x0a\x09\x09\x09yourself) ].\x0a\x0a\x09aNode dagChildren do: [ :each | self method add: (self visit: each) ].\x0a\x0a\x09aNode scope hasLocalReturn ifFalse: [self method\x0a\x09\x09add: (IRReturn new\x0a\x09\x09\x09add: (IRVariable new\x0a\x09\x09\x09\x09variable: (aNode scope pseudoVars at: 'self');\x0a\x09\x09\x09\x09yourself);\x0a\x09\x09\x09yourself);\x0a\x09\x09add: (IRVerbatim new source: ''; yourself) ].\x0a\x0a\x09^ self method",
 referencedClasses: ["IRMethod", "IRTempDeclaration", "IRReturn", "IRVariable", "IRVerbatim"],
 //>>excludeEnd("ide");
-messageSends: ["method:", "source:", "new", "crlfSanitized", "source", "theClass:", "theClass", "arguments:", "arguments", "selector:", "selector", "sendIndexes:", "sendIndexes", "requiresSmalltalkContext:", "requiresSmalltalkContext", "classReferences:", "classReferences", "scope:", "scope", "yourself", "do:", "temps", "add:", "method", "name:", "name", "nodes", "visit:", "ifFalse:", "hasLocalReturn", "variable:", "at:", "pseudoVars"]
+messageSends: ["method:", "source:", "new", "crlfSanitized", "source", "theClass:", "theClass", "arguments:", "arguments", "selector:", "selector", "sendIndexes:", "sendIndexes", "requiresSmalltalkContext:", "requiresSmalltalkContext", "classReferences:", "classReferences", "scope:", "scope", "yourself", "do:", "temps", "add:", "method", "name:", "name", "dagChildren", "visit:", "ifFalse:", "hasLocalReturn", "variable:", "at:", "pseudoVars"]
 }),
 $globals.IRASTTranslator);
 
@@ -901,7 +901,7 @@ $ctx1.sendIdx["new"]=1;
 return_=$recv($globals.IRReturn)._new();
 };
 $recv(return_)._scope_($recv(aNode)._scope());
-$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");
@@ -917,10 +917,10 @@ return return_;
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["aNode"],
-source: "visitReturnNode: aNode\x0a\x09| return |\x0a\x09return := aNode nonLocalReturn\x0a\x09\x09ifTrue: [ IRNonLocalReturn new ]\x0a\x09\x09ifFalse: [ IRReturn new ].\x0a\x09return scope: aNode scope.\x0a\x09aNode nodes do: [ :each |\x0a\x09\x09return add: (self visitOrAlias: each) ].\x0a\x09^ return",
+source: "visitReturnNode: aNode\x0a\x09| return |\x0a\x09return := aNode nonLocalReturn\x0a\x09\x09ifTrue: [ IRNonLocalReturn new ]\x0a\x09\x09ifFalse: [ IRReturn new ].\x0a\x09return scope: aNode scope.\x0a\x09aNode dagChildren do: [ :each |\x0a\x09\x09return add: (self visitOrAlias: each) ].\x0a\x09^ return",
 referencedClasses: ["IRNonLocalReturn", "IRReturn"],
 //>>excludeEnd("ide");
-messageSends: ["ifTrue:ifFalse:", "nonLocalReturn", "new", "scope:", "scope", "do:", "nodes", "add:", "visitOrAlias:"]
+messageSends: ["ifTrue:ifFalse:", "nonLocalReturn", "new", "scope:", "scope", "do:", "dagChildren", "add:", "visitOrAlias:"]
 }),
 $globals.IRASTTranslator);
 
@@ -939,7 +939,7 @@ send=$recv($globals.IRSend)._new();
 $1=send;
 $recv($1)._selector_($recv(aNode)._selector());
 $recv($1)._index_($recv(aNode)._index());
-$recv(self._aliasTemporally_($recv(aNode)._nodes()))._do_((function(each){
+$recv(self._aliasTemporally_($recv(aNode)._dagChildren()))._do_((function(each){
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 return $core.withContext(function($ctx2) {
 //>>excludeEnd("ctx");
@@ -955,10 +955,10 @@ return send;
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["aNode"],
-source: "visitSendNode: aNode\x0a\x09| send |\x0a\x09send := IRSend new.\x0a\x09send\x0a\x09\x09selector: aNode selector;\x0a\x09\x09index: aNode index.\x0a\x09\x0a\x09(self aliasTemporally: aNode nodes) do: [ :each | send add: each ].\x0a\x0a\x09^ send",
+source: "visitSendNode: aNode\x0a\x09| send |\x0a\x09send := IRSend new.\x0a\x09send\x0a\x09\x09selector: aNode selector;\x0a\x09\x09index: aNode index.\x0a\x09\x0a\x09(self aliasTemporally: aNode dagChildren) do: [ :each | send add: each ].\x0a\x0a\x09^ send",
 referencedClasses: ["IRSend"],
 //>>excludeEnd("ide");
-messageSends: ["new", "selector:", "selector", "index:", "index", "do:", "aliasTemporally:", "nodes", "add:"]
+messageSends: ["new", "selector:", "selector", "index:", "index", "do:", "aliasTemporally:", "dagChildren", "add:"]
 }),
 $globals.IRASTTranslator);
 
@@ -976,7 +976,7 @@ return self._withSequence_do_($recv($globals.IRSequence)._new(),(function(){
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 return $core.withContext(function($ctx2) {
 //>>excludeEnd("ctx");
-return $recv($recv(aNode)._nodes())._do_((function(each){
+return $recv($recv(aNode)._dagChildren())._do_((function(each){
 var instruction;
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
 return $core.withContext(function($ctx3) {
@@ -1001,10 +1001,10 @@ return $recv(self._sequence())._add_(instruction);
 },
 //>>excludeStart("ide", pragmas.excludeIdeData);
 args: ["aNode"],
-source: "visitSequenceNode: aNode\x0a\x09^ self\x0a\x09\x09withSequence: IRSequence new\x0a\x09\x09do: [\x0a\x09\x09\x09aNode nodes do: [ :each | | instruction |\x0a\x09\x09\x09\x09instruction := self visitOrAlias: each.\x0a\x09\x09\x09\x09instruction isVariable ifFalse: [\x0a\x09\x09\x09\x09\x09self sequence add: instruction ] ]]",
+source: "visitSequenceNode: aNode\x0a\x09^ self\x0a\x09\x09withSequence: IRSequence new\x0a\x09\x09do: [\x0a\x09\x09\x09aNode dagChildren do: [ :each | | instruction |\x0a\x09\x09\x09\x09instruction := self visitOrAlias: each.\x0a\x09\x09\x09\x09instruction isVariable ifFalse: [\x0a\x09\x09\x09\x09\x09self sequence add: instruction ] ]]",
 referencedClasses: ["IRSequence"],
 //>>excludeEnd("ide");
-messageSends: ["withSequence:do:", "new", "do:", "nodes", "visitOrAlias:", "ifFalse:", "isVariable", "add:", "sequence"]
+messageSends: ["withSequence:do:", "new", "do:", "dagChildren", "visitOrAlias:", "ifFalse:", "isVariable", "add:", "sequence"]
 }),
 $globals.IRASTTranslator);
 

+ 15 - 15
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 ] ]]

+ 37 - 37
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);
 
@@ -2096,7 +2096,7 @@ $globals.ASTEnterNode);
 
 $core.addMethod(
 $core.method({
-selector: "visitNode:",
+selector: "visitDagNode:",
 protocol: 'visiting',
 fn: function (aNode){
 var self=this;
@@ -2105,7 +2105,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){
@@ -2121,15 +2121,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);
 
@@ -3209,6 +3209,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:",
@@ -3220,7 +3238,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");
@@ -3237,10 +3255,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);
 
@@ -3255,7 +3273,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");
@@ -3272,10 +3290,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);
 
@@ -3304,24 +3322,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:",
@@ -3903,11 +3903,11 @@ return $core.withContext(function($ctx1) {
 var $1;
 var $early={};
 try {
-$1=self._nodes();
+$1=self._dagChildren();
 //>>excludeStart("ctx", pragmas.excludeDebugContexts);
-$ctx1.sendIdx["nodes"]=1;
+$ctx1.sendIdx["dagChildren"]=1;
 //>>excludeEnd("ctx");
-return $recv($1)._at_ifAbsent_($recv($recv(self._nodes())._indexOf_(aNode)).__plus((1)),(function(){
+return $recv($1)._at_ifAbsent_($recv($recv(self._dagChildren())._indexOf_(aNode)).__plus((1)),(function(){
 throw $early=[nil];
 
 }));
@@ -3919,10 +3919,10 @@ catch(e) {if(e===$early)return e[0]; throw e}
 },
 //>>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 ]",
+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: ["at:ifAbsent:", "nodes", "+", "indexOf:"]
+messageSends: ["at:ifAbsent:", "dagChildren", "+", "indexOf:"]
 }),
 $globals.Node);
 

+ 11 - 11
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
@@ -1021,8 +1021,8 @@ isSteppingNode
 nextSiblingNode: aNode
 	"Answer the next node after aNode or nil"
 	
-	^ self nodes 
-		at: (self nodes indexOf: aNode) + 1
+	^ self dagChildren 
+		at: (self dagChildren indexOf: aNode) + 1
 		ifAbsent: [ ^ nil ]
 ! !
 

+ 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

@@ -2425,9 +2425,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();
@@ -2443,10 +2443,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);
 
@@ -2464,22 +2464,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);
@@ -2498,10 +2498,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);
 
@@ -2531,22 +2531,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);
@@ -2562,10 +2562,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);
 
@@ -2804,17 +2804,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);
@@ -2836,17 +2836,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);
@@ -2873,33 +2873,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);
@@ -2918,33 +2918,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);
@@ -2956,9 +2956,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();
@@ -2971,10 +2971,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

@@ -683,7 +683,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
@@ -693,7 +693,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
@@ -704,7 +704,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
@@ -768,12 +768,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

+ 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: "\"<\"" },
@@ -314,7 +314,7 @@ $globals.SmalltalkParser = (function() {
                                      ._source_(text())
                                      ._selector_(pattern[0])
                                      ._arguments_(pattern[1])
-                                     ._nodes_([sequence]);
+                                     ._dagChildren_([sequence]);
                          },
         peg$c133 = function(send) { return send._isSendNode() && send._selector() === "->" },
         peg$c134 = 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    = "<" val:((">>" {return ">";} / [^>])*) ">" {
@@ -264,7 +264,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