Syntax node code cleanups.
[cslatevm.git] / src / syntax / node.slate
blob9f87ccf9963978657d69307212add5314fdf0cba
1 ensureNamespace: #nodes &delegate: True.
3 nodes define: #Node &parents: {Cloneable} &slots:
4 {#type -> Types Any. "The annotated type, by the inferencer or manually."
5  #source -> Nil. "The source of the lexer stream"
6  #lineNumber -> Nil "The line number in the source code at which the node was read."}.
7 "The general syntax object for expressions."
9 node@(nodes Node traits) new
10 [resend `setting: #{#type. #lineNumber} to: {Types Any. Nil}].
12 node@(nodes Node traits) evaluate
13 [node evaluateIn: lobby].
15 node@(nodes Node traits) evaluateIn: namespace
16 [overrideThis].
18 node@(nodes Node traits) walk: block
19 "A depth-first do:-style iteration through Nodes; a code/tree-walker."
21   block applyWith: node.
24 node@(nodes Node traits) transformBy: block
25 "Transforms the tree's nodes in-place by the block closure.
26 Only transformChildren: needs to be overridden."
28   (block applyWith: node) transformChildren: block
31 node@(nodes Node traits) transformChildren: block
32 "Act on each of a node's children in-place.
33 This gets overridden for the various compound node types."
35   node
38 node@(nodes Node traits) deepCopy: scope
39 "Copies the entire syntax tree, with the given scope as the lexical reference.
40 This gets overridden for each type that is compound or relates to the scope."
42   node
45 node@(nodes Node traits) deepCopy
46 "Copies the entire syntax tree with the (default) scope being the lobby."
48   node deepCopy: nodes Ground
51 node@(nodes Node traits) definitionLocation
53   (node source hasSlotNamed: #resource)
54     ifTrue: [node source resource locator
55                ifNil: ['stdin:' ; (node lineNumber - 2) printString]
56                ifNotNilDo: [| :loc | (loc as: String) ; ':' ; node lineNumber printString]]
57     ifFalse: [node source
58                 ifNil: ['Nil']
59                 ifNotNil: [node source printString ; ':' ; node lineNumber printString]]
62 nodes define: #Annotation &parents: {nodes Node}
63   &slots: {#value "The annotated node."}.
64 "A wrapper for other Nodes that adds an annotative object."
66 x@(nodes Annotation traits) = y@(nodes Annotation traits)
67 [x value = y value].
69 ann@(nodes Annotation traits) walk: block
71   block applyWith: ann.
72   ann value walk: block
75 ann@(nodes Annotation traits) transformChildren: block
77   ann value: (ann value transformBy: block).
78   ann
81 ann@(nodes Annotation traits) deepCopy: scope
82 [ann clone `setting: #{#value} to: {ann value deepCopy: scope}].
84 ann@(nodes Annotation traits) evaluateIn: namespace
85 [ann value evaluateIn: namespace].
87 nodes define: #Comment &parents: {nodes Annotation}
88 &slots: {#comment -> '' "The comment object, an empty String by default."}.
89 "Comments are nodes that contain the expression that they annotate."
91 x@(nodes Comment traits) = y@(nodes Comment traits)
92 [x value = y value /\ [x comment = y comment]].
94 node@(nodes Node traits) comment: comment
95 "Returns a new Comment with the given comment wrapping the original
96 Node. Usable as a macro."
97 [nodes Comment clone `setting: #{#comment. #value} to: {comment evaluate. node}].
99 nodes define: #ImplicitArgument &parents: {nodes Node}.
100 "Implicit arguments include anything sent to the local context, as well as
101 the lobby."
103 node1@(nodes ImplicitArgument traits) = node2@(nodes ImplicitArgument traits)
104 [True].
106 node@(nodes ImplicitArgument traits) evaluateIn: namespace
107 "The default is to simply return the namespace as the result."
108 [namespace].
110 nodes define: #Message &parents: {nodes Node}
111   &slots: {#selector -> #'' . #arguments -> #{}}.
112 "Represents a message send."
114 m@(nodes Message traits) prototypeFor: selector
116   `conditions: (
117     [Syntax isUnarySelector: selector] -> [nodes UnaryMessage].
118     [Syntax isBinarySelector: selector] -> [nodes BinaryMessage]
119   ) otherwise: [nodes KeywordMessage]
122 message@(nodes Message traits) sending: selector to: arguments
123 [(message prototypeFor: selector) clone `setting: #{#selector. #arguments} to:
124   {selector intern. arguments}].
126 x@(nodes Message traits) as: y@(nodes Message traits)
127 [y sending: x selector to: x arguments].
129 node1@(nodes Message traits) = node2@(nodes Message traits)
131   node1 selector = node2 selector
132    /\ [node1 isSameAs: node2]
133    /\ [node1 arguments = node2 arguments]
136 message@(nodes Message traits) walk: block
138   resend.
139   message arguments do: #(_ walk: block) `er
142 message@(nodes Message traits) transformChildren: block
144   message arguments infect: #(_ transformBy: block) `er.
145   message
148 message@(nodes Message traits) deepCopy: scope
150   message clone `>> [arguments := message arguments collect: #(deepCopy: scope) `er. ]
153 message@(nodes Message traits) evaluateIn: namespace &optionals: opts
154 "Overridden to support the evaluateIn: for ImplicitArgument."
156   message selector sendTo:
157     (message arguments collect: #(evaluateIn: namespace) `er)
158     &optionals: opts
161 nodes define: #UnaryMessage &parents: {nodes Message}.
163 message@(nodes UnaryMessage traits) sending: selector
164 "Send the selector to the implicit context."
165 [message sending: selector to: {nodes ImplicitArgument}].
167 node@(nodes UnaryMessage traits) argument
168 [node arguments first].
170 nodes define: #BinaryMessage &parents: {nodes Message}.
171 nodes define: #KeywordMessage &parents: {nodes Message}.
173 nodes define: #Macro &parents: {nodes Message}.
174 "Macro nodes are just like regular message-sends, except being applied at
175 compile-time to the Node trees for the expressions."
177 macro@(nodes Macro traits) evaluateIn: namespace &optionals: opts
178 "Evaluate the expansion. Should this be relied on? (I.e. should this throw a
179 condition which is resumable via macro-expansion?)"
181   (macro macroExpand &optionals:
182     (opts
183       ifNotNil:
184         [nodes OptionalKeywords new `>>
185            [message := macro.
186             keywords := opts atAll: (0 below: opts size by: 2).
187             arguments := opts atAll: (1 below: opts size by: 2). ]]))
188     evaluateIn: namespace
191 m@(nodes Macro traits) prototypeFor: selector
193   `conditions: (
194     [Syntax isUnarySelector: selector] -> [nodes UnaryMacro].
195     [Syntax isBinarySelector: selector] -> [nodes BinaryMacro]
196   ) otherwise: [nodes KeywordMacro]
199 nodes define: #UnaryMacro &parents: {nodes Macro}.
200 nodes define: #BinaryMacro &parents: {nodes Macro}.
201 nodes define: #KeywordMacro &parents: {nodes Macro}.
203 nodes define: #Deferred &parents: {nodes Message}.
204 "Deferred nodes are just like regular message-sends, except being applied
205 only when all argument promises are entirely resolved."
207 message@(nodes Message traits) deferred
208 [message as: nodes Deferred].
210 message@(nodes Deferred traits) evaluateIn: namespace &optionals: opts
212   (message arguments collect: #(evaluateIn: namespace) `er)
213     whenFulfilled: [| *args |
214       message selector sendTo: args &optionals: opts]
217 m@(nodes Deferred traits) prototypeFor: selector
219   `conditions: (
220     [Syntax isUnarySelector: selector] -> [nodes UnaryDeferred].
221     [Syntax isBinarySelector: selector] -> [nodes BinaryDeferred]
222   ) otherwise: [nodes KeywordDeferred]
225 nodes define: #UnaryDeferred &parents: {nodes Deferred}.
226 nodes define: #BinaryDeferred &parents: {nodes Deferred}.
227 nodes define: #KeywordDeferred &parents: {nodes Deferred}.
229 nodes define: #MessageWrapper &parents: {nodes Node}
230   &slots: {#message}.
232 w@(nodes MessageWrapper traits) for: message
233 [w new `setting: #{#message} to: {message}].
235 w@(nodes MessageWrapper traits) selector
236 [w message selector].
238 w@(nodes MessageWrapper traits) transformChildren: block
240   w message := w message transformBy: block.
241   w
244 w@(nodes MessageWrapper traits) walk: block
246   block applyWith: w.
247   w message walk: block.
250 w@(nodes MessageWrapper traits) deepCopy: scope
252   w clone `>> [message := w message deepCopy: scope. ]
255 nodes define: #OptionalKeywords &parents: {nodes MessageWrapper}
256   &slots: {#keywords -> {}. #arguments -> {}}.
257 "Annotates a Message with optional keywords and values given."
259 x@(nodes OptionalKeywords traits) = y@(nodes OptionalKeywords traits)
260 [x message = y message /\ [x keywords = y keywords] /\ [x arguments = y arguments]].
262 opts@(nodes OptionalKeywords traits) new
263 [resend clone `setting: #{#keywords. #arguments} to: #{{}. {}}].
265 opts@(nodes OptionalKeywords traits) walk: block
267   resend.
268   opts arguments
269     do: #(walk: block) `er
272 opts@(nodes OptionalKeywords traits) transformChildren: block
274   resend.
275   opts arguments infect: #(_ transformBy: block) `er.
276   opts
279 opts@(nodes OptionalKeywords traits) deepCopy: scope
281   resend `>> [arguments := opts arguments collect: #(deepCopy: scope) `er. ]
284 opts@(nodes OptionalKeywords traits) evaluateIn: namespace
286   opts message evaluateIn: namespace &optionals:
287     ([| :result |
288        opts keywords with: opts arguments
289          do: [| :key :arg | result nextPutAll: {key intern. arg evaluateIn: namespace}]
290      ] writingAs: #{})
293 nodes define: #RestArguments &parents: {nodes MessageWrapper}
294   &slots: {#arguments}.
296 x@(nodes RestArguments traits) = y@(nodes RestArguments traits)
297 [x message = y message /\ [x arguments = y arguments]].
299 rest@(nodes RestArguments traits) new
300 [resend clone `setting: #{#arguments} to: #{{}}].
302 rest@(nodes RestArguments traits) walk: block
304   resend.
305   rest arguments do: #(_ walk: block) `er
308 rest@(nodes RestArguments traits) transformChildren: block
310   resend.
311   rest arguments infect: #(_ transformBy: block) `er.
312   rest
315 rest@(nodes RestArguments traits) deepCopy: scope
317   resend `>> [arguments := rest arguments collect: #(deepCopy: scope) `er. ]
320 rest@(nodes RestArguments traits) allArguments
322   rest message arguments ; rest arguments
325 rest@(nodes RestArguments traits) evaluateIn: namespace &optionals: opts
327   rest selector sendTo:
328     (rest allArguments collect: #(evaluateIn: namespace) `er)
329     &optionals: opts
332 nodes define: #Placeholder &parents: {nodes Node}.
334 node@(nodes Node traits) as: _@(nodes Placeholder traits)
336   node
339 node@(nodes UnaryMessage traits) as: ph@(nodes Placeholder traits)
341   node selector = #_ /\ [node arguments first == nodes ImplicitArgument]
342     ifTrue: [ph] ifFalse: [node]
345 ph@(nodes Placeholder traits) evaluateIn: namespace &optionals: opts
347   ph
350 nodes define: #Pattern &parents: {nodes MessageWrapper}.
351 "Pattern nodes are just like regular message-sends, except having only
352 some arguments filled initially at parse-time. They may be treated as
353 records or curry-able message-sends."
355 pattern@(nodes Pattern traits) keywords
356 [pattern selector keywords].
358 pattern@(nodes Pattern traits) values
359 [pattern message arguments].
361 nodes Pattern traits define: #BlankTokens &builder:
362   [{nodes Placeholder. nodes ImplicitArgument}].
364 pattern@(nodes Pattern traits) isPlaceholder: node
366   pattern BlankTokens includes: node
369 pattern@(nodes Pattern traits) arity
370 [| count countedImplicit |
371   count := 0.
372   pattern walk:
373     [| :node |
374      `conditions: (
375         [node == nodes Placeholder]
376           -> [count += 1].
377         [node == nodes ImplicitArgument /\ [countedImplicit isNil]]
378           -> [countedImplicit := node. count += 1]
379     )].
380   count
383 pattern@(nodes Pattern traits) isComplete
384 "Answers whether it can be evaluated successfully."
386   pattern walk: [| :node | node == nodes Placeholder ifTrue: [^ False]].
387   True
390 pattern@(nodes Pattern traits) completeWith: values
391 [| valuesIn countedImplicit |
392   valuesIn := values reader.
393   pattern transformBy:
394     [| :node |
395      valuesIn isAtEnd
396        ifTrue: [node]
397        ifFalse:
398          [`conditions: (
399             [node == nodes ImplicitArgument /\ [countedImplicit isNil]]
400               -> [countedImplicit := node. valuesIn next].
401             [node == nodes Placeholder]
402               -> [valuesIn next]
403           ) otherwise: [node]]]
406 pattern@(nodes Pattern traits) deepCopy: scope
408   pattern for: (pattern message deepCopy: scope)
411 pattern@(nodes Pattern traits) evaluateIn: namespace &optionals: opts
412 "Patterns are auto-quasiquoting, in that their arguments get evaluated,
413 but the message is not sent."
415   pattern for: pattern message clone `>>
416     [arguments := pattern message arguments collect: #(evaluateIn: namespace) `er. ]
419 nodes define: #Literal &parents: {nodes Node} &slots: {#value}.
420 "The syntax for a literal Slate object, i.e. something the Lexer can create
421 directly."
423 nodes Literal traits define: #ReusableValues &builder: [Dictionary new].
424 nodes Literal traits define: #Nil &builder: [nodes Literal clone].
426 l@(nodes Literal traits) noteReusable: obj
427 [l ReusableValues at: obj ifAbsentPut:
428   [l new `setting: #{#value} to: {obj}]].
430 [| :each | nodes Literal noteReusable: each] for:
431   {Array new. ByteArray new. #''. ''}.
433 node@(nodes Literal traits) for: obj
434 [node ReusableValues at: obj ifAbsent: [node new `setting: #{#value} to: {obj}]].
436 node@(nodes Literal traits) for: _@Nil [node Nil].
438 x@(nodes Literal traits) = y@(nodes Literal traits)
439 [x value = y value].
441 node@(nodes Literal traits) evaluateIn: namespace
442 "A literal just evaluates to its expression-value."
443 [node value].
445 b@(nodes Node traits) allLiterals
446 "Answer an Array of all literal values from the source."
448   [| :result |
449    b walk: [| :node | (node is: nodes Literal) ifTrue:
450      [result nextPut: node value]]] writingAs: #{}
453 nodes define: #CompoundStatement &parents: {nodes Node}
454   &slots: {#statements -> #{}}.
456 array@(Sequence traits) as: group@(nodes CompoundStatement traits)
457 [group new `setting: #{#statements} to: {array as: group statements}].
459 group@(nodes CompoundStatement traits) size
460 "The number of statements/elements in the expression."
461 [group statements size].
463 node1@(nodes CompoundStatement traits) = node2@(nodes CompoundStatement traits)
464 [(node1 isSameAs: node2) /\ [node1 statements = node2 statements]].
466 group@(nodes CompoundStatement traits) walk: block
468   resend.
469   group statements do: #(_ walk: block) `er
472 group@(nodes CompoundStatement traits) transformChildren: block
474   group statements infect: #(_ transformBy: block) `er.
475   group
478 group@(nodes CompoundStatement traits) deepCopy: scope
480   (group statements collect:
481     #(_ deepCopy: scope) `er) as: group
484 nodes define: #Array &parents: {nodes CompoundStatement}.
486 group@(nodes Array traits) evaluateIn: namespace
488   group statements collect: #(evaluateIn: namespace) `er
491 nodes define: #Parenthesis &parents: {nodes CompoundStatement}.
493 group@(nodes Parenthesis traits) evaluateIn: namespace
495   group statements isEmpty
496     ifTrue: [Nil]
497     ifFalse:
498       [group statements allButLastDo: #(_ evaluateIn: namespace) `er.
499        group statements last evaluateIn: namespace]
502 group@(nodes Parenthesis traits) parenthesize
504   group
507 node@(nodes Node traits) parenthesize
509   {node} parenthesize
512 seq@(Sequence traits) parenthesize
514   seq size = 1 ifTrue: [seq first] ifFalse: [seq as: nodes Parenthesis]
517 nodes define: #Namespace &parents: {nodes Node} &slots: {#namespace -> lobby}.
519 node@(nodes Namespace traits) for: namespace
520 [node new `setting: #{#namespace} to: {namespace}].
522 node1@(nodes Namespace traits) = node2@(nodes Namespace traits)
523 [node1 namespace = node2 namespace].
525 _@(nodes Namespace traits) evaluateIn: namespace
526 [shouldNotImplement].
528 _@(nodes Namespace traits) parentScope
530   error: 'The top-level namespace has no parent scope.'
533 node@(nodes Namespace traits) topLevel
535   node
538 _@(nodes Namespace traits) findVariable: _
539 "Present for compatibility with Block findVariable:."
540 [Nil].
542 namespace@(nodes Namespace traits) includesScope: scope
543 [namespace == scope].
545 nodes define: #Ground &builder: [nodes Namespace for: lobby].
547 nodes define: #Block &parents: {nodes CompoundStatement} &slots:
548 {#parentScope -> nodes Ground.
549  #inputVariables -> #{}.
550 "Holds Variable nodes representing the block's inputs in order."
551  #restVariable -> Nil.
552 "Holds a Variable node representing the block's rest parameter if it
553 accepts one."
554  #optionalKeywords -> #{}.
555  #optionalVariables -> #{}.
556 "Holds Variable nodes representing the block's optional local slots."
557  #localVariables -> #{}
558 "Holds Variable nodes representing the block's local slots (including
559 inputs in order and optionals)."}.
561 node1@(nodes Block traits) = node2@(nodes Block traits)
562 "TODO: ensure this is correct and that local variable order is ignored."
564   resend
565    /\ [node1 inputVariables = node2 inputVariables]
566    /\ [node1 parentScope = node2 parentScope]
567    /\ [node1 localVariables = node2 localVariables]
570 block@(nodes Block traits) compile
571 "Invoke the VM ByteCompiler."
573   VM SSACompiler new generate: block result: Nil
576 block@(nodes Block traits) compileAndRun
577 "Compile the block using the VM ByteCompiler and then run it."
579   block compile do
582 block@(nodes Block traits) evaluateIn: namespace
583 "Compile the block and return it."
584 [block compile].
586 b@(nodes Block traits) new
588   resend `>>
589    [inputVariables := b inputVariables new.
590     localVariables := b localVariables new.
591     optionalKeywords := b optionalKeywords new.
592     optionalVariables := b optionalVariables new.
593     restVariable := Nil. ]
596 b@(nodes Block traits) body: body@(nodes Node traits)
597 "Makes a given Node the body."
598 [b statements := {body}].
600 b@(nodes Block traits) body: body@(nodes Parenthesis traits)
601 "Takes the statements as the body of the block."
602 [b statements := body statements].
604 b@(nodes Block traits) newFor: body@(nodes Node traits)
605 "Creates a new Block with the given node as the body."
606 [b new `>> [body := body. ]].
608 block@(nodes Block traits) addVariable: var
609 "Adds the Variable node to the block's locals and sets it as the
610 variable's scope (used to compile closures properly), and answers it."
612   (block localVariables anySatisfy: [| :other | other name = var name])
613     ifTrue:
614       [var name := block uniqueVariableName].
615   var scope := block.
616   block localVariables := block localVariables copyWith: var.
617   var
620 block@(nodes Block traits) addVariableNamed: name &varType: varType
621 "Creates a new Variable with the given name and adds it as a local,
622 then returning it."
624   varType `defaultsTo: nodes Variable.
625   block localVariables
626     detect: [| :var | var name = name /\ [var isSameAs: varType]]
627     ifNone: [block addVariable: (varType named: name)]
630 block@(nodes Block traits) uniqueVariableName &prefix: prefix
631 [| nameIndex |
632   prefix `defaultsTo: '_'.
633   nameIndex := 0.
634   [nameIndex < 100 /\
635      [(block findVariable: (prefix ; nameIndex printString) intern) isNotNil]]
636     whileTrue:
637       [nameIndex += 1].
638   nameIndex < 100
639     ifFalse:
640       [error: 'Could not generate a unique variable name.'].
641   (prefix ; nameIndex printString) intern
644 block@(nodes Block traits) addVariable &name: name &prefix: prefix
645 "Calls addVariable: with a name guaranteed not to clash with other such names."
647   name `defaultsTo: (block uniqueVariableName &prefix: prefix).
648   block addVariableNamed: name
651 block@(nodes Block traits) addInputVariableNamed: name
652 "Creates a new Variable with the given name and adds it as an input,
653 then returning it."
654 [| var |
655   var := block addVariableNamed: name.
656   block inputVariables := block inputVariables copyWith: var.
657   var
660 block@(nodes Block traits) addInputVariable &name: name &prefix: prefix
661 "Calls addInputVariable: with a name guaranteed not to clash with other such
662 names."
664   name `defaultsTo: (block uniqueVariableName &prefix: prefix).
665   block addInputVariableNamed: name
668 block@(nodes Block traits) addOptionalKeyword: key named: name
669 "Creates a new Variable with the given name and adds it as an optional,
670 then returning it."
671 [| var |
672   var := block addVariableNamed: name.
673   block optionalKeywords := block optionalKeywords copyWith: key intern.
674   block optionalVariables := block optionalVariables copyWith: var.
675   var
678 block@(nodes Block traits) topLevel
679 "Recurses up the scope to find the top-level scope."
681   block parentScope topLevel
684 block@(nodes Block traits) outermostBlock
685 "Answers the outermost scope that is still a Block or MethodDefinition and not
686 a Namespace."
687 [| scope |
688   scope := block.
689   [scope parentScope isSameAs: nodes Namespace]
690     whileFalse: [scope := scope parentScope].
691   scope
694 block@(nodes Block traits) hasVariableNamed: name
696   block localVariables anySatisfy: [| :var | name =~ var name]
699 block@(nodes Block traits) outermostScopeNotBinding: name
700 "Answers the outermost scope that does not have a given binding or slot."
701 [| scope |
702   (block hasVariableNamed: name) ifFalse:
703     [scope := block.
704      [(scope hasVariableNamed: name) \/ [scope parentScope isSameAs: nodes Namespace]]
705        whileFalse: [scope := scope parentScope]].
706   scope
709 block@(nodes Block traits) findVariable: name
710 "Searches through the current scope, and then upward, for the entry
711 corresponding to the given name, and answers what it can find, or Nil if none."
713   block localVariables
714     detect: [| :var | name =~ var name]
715     ifNone: [block parentScope findVariable: name]
718 block@(nodes Block traits) includesScope: scope
719 [block == scope \/ [block parentScope includesScope: scope]].
721 block@(nodes Block traits) from: varNames to: codeBlock &locals: localNames &linkVariables: linkVariables
722 "Takes an Array of symbol names or Nil's for unnamed variables, and runs the
723 code block with corresponding VariableNodes as inputs. The code block is
724 expected to return the method body expression. The method then answers a new
725 Block with that method body and those input variables."
726 [| result |
727   result := block new.
728   varNames do: [| :var | result addInputVariable &name: var].
729   localNames ifNotNil: [localNames do: [| :var | result addVariable &name: var]].
730   "ASSUME: newFor: does not clear inputs."
731   result body := codeBlock applyTo: result localVariables.
732   linkVariables ifNotNil: [result linkVariables].
733   result
736 b@(nodes Block traits) deepCopy: scope &into: target
737 "Copies up to the level of the given scope, and sets the scope to that one."
739   (target ifNil: [b]) clone `>>
740    [| :newBlock |
741     parentScope := scope.
742     localVariables :=
743       b localVariables collect:
744         [| :var newVar | var clone `>> [scope := newBlock. ]].
745     inputVariables :=
746       b inputVariables collect: [| :var | newBlock findVariable: var name].
747     optionalVariables :=
748       b optionalVariables collect: [| :var | newBlock findVariable: var name].
749     restVariable :=
750       b restVariable ifNotNil: [newBlock findVariable: b restVariable name].
751     statements :=
752       b statements collect: #(deepCopy: newBlock) `er.
753   ]
756 block@(nodes Block traits) deepCopy &into: target
757 "Copies the entire syntax tree with the (default) scope being the block's parent."
759   block deepCopy: block parentScope
762 block@(nodes Block traits) as: target@(nodes Block traits)
763 "This should allow Block and MethodDefinition objects to be converted (with
764 loss of Signature information, of course."
765 [block deepCopy &into: target new].
767 block@(nodes Block traits) arity
768 [block inputVariables size].
770 dst@(nodes Block traits) addVariablesFrom: src@(nodes Block traits)
771 "Copies over the local variable entries from the source block to the
772 destination. Answers the locals found."
774   src localVariables do: #(dst addVariable: _) `er
777 block@(nodes Block traits) modifiesOwnVariables
778 "Answers whether there are any direct variable stores."
779 "TODO: Avoid re-implementing detect:!"
781   block walk: [| :node | (node is: nodes StoreVariable) ifTrue: [^ True]].
782   False
785 block@(nodes Block traits) modifiesInputVariables
786 "Answers whether there are any direct variable stores to inputs."
788   block walk: [| :node | (node is: nodes StoreVariable) /\
789              [block inputVariables includes: node variable] ifTrue: [^ True]].
790   False
793 block@(nodes Block traits) allSelectorsSent
795   [| :result |
796    block walk:
797      [| :node |
798       (node isSameAs: nodes LoadVariable) \/
799         [node isSameAs: nodes StoreVariable]
800       ifTrue: [result nextPut: node variable name]
801       ifFalse: [(node is: nodes Message)
802                 ifTrue: [result nextPut: node selector]]].
803    ] writingAs: Set
806 block@(nodes Block traits) allSelectorsSentTo: var
807 "Answers the Set of all selectors called in this method on the Variable object."
808 [| loadExpr |
809   loadExpr := var load.
810   [| :result |
811    block statements do:
812      [| :statement | statement walk:
813         [| :expr | (expr is: nodes Message) /\ [expr arguments includes: loadExpr]
814            ifTrue: [result nextPut: expr selector]]]] writingAs: Set
817 block@(nodes Block traits) allSelectorsSentToInputAt: argIndex
818 "Answers the Set of all selectors called in this method on the argument object."
820   (block inputVariables acceptsKey: argIndex)
821     ifTrue: [block allSelectorsSentTo: (block inputVariables at: argIndex)]
822     ifFalse: [error: 'No such input argument.']
825 block@(nodes Block traits) allSelectorsSentToInputs
827   [| :result |
828    block inputVariables keysDo:
829      [| :index | result ; (block allSelectorsSentToInputAt: index)]
830   ] writingAs: Set
833 block@(nodes Block traits) bodyIncludesImplicitSends
835   block statements do:
836     [| :statement | statement walk:
837        [| :node | (node is: nodes Message) /\
838           [node arguments includes: nodes ImplicitArgument]
839           ifTrue: [^ True]]].
840   False
843 block@(nodes Block traits) allSelectorsSentImplicitly
845   [| :result |
846    block statements do:
847      [| :statement | statement walk:
848         [| :node | (node is: nodes Message) ifTrue:
849            [node arguments do:
850               [| :arg |
851                arg = nodes ImplicitArgument
852                  \/ [(arg is: nodes LoadVariable)
853                        /\ [arg variable = nodes ImplicitArgument]]
854                  ifTrue: [result nextPut: node selector]]]]]] writingAs: Set
857 nodes define: #MethodDefinition &parents: {nodes Block}
858   &slots: {#selector. #roles -> #{}}.
859 "The object representing the definition of a Method."
861 method@(nodes MethodDefinition traits) new
862 [resend `>> [selector := Nil. roles := method roles new. ]].
864 method@(nodes MethodDefinition traits) of: selector on: roles
865   from: varNames to: codeBlock &locals: localNames &linkVariables: linkVariables
867   (method from: varNames to: codeBlock &locals: localNames &linkVariables: linkVariables) `>>
868     [selector := selector. roles := roles. ]
871 node1@(nodes MethodDefinition traits) = node2@(nodes MethodDefinition traits)
872 [resend /\ [node1 selector = node2 selector] /\ [node1 roles = node2 roles]].
874 method@(nodes MethodDefinition traits) walk: block
876   resend.
877   method roles do: [| :role | role ifNotNil: [role walk: block]]
880 method@(nodes MethodDefinition traits) transformChildren: block
882   method roles infect: [| :role | role ifNotNil: [role transformBy: block]].
883   resend
886 method@(nodes MethodDefinition traits) deepCopy: scope &into: target
888   resend `>>
889     [roles := method roles
890        collect: [| :role | role ifNotNil: [role deepCopy: scope]]. ]
893 method@(nodes MethodDefinition traits) evaluateIn: namespace
895   resend
896     asMethod: method selector
897     on: (method roles collect: #(evaluateIn: namespace) `er)
900 nodes define: #Signature &parents: {nodes Node} &slots: {
901   #selector.
902   #roles -> #{}.
903   #inputVariables -> #{}.
904   #restVariable -> Nil.
905   #optionalKeywords -> #{}.
906   #optionalVariables -> #{}
908 "The object representing the definition of a Method without the body."
910 sig@(nodes Signature traits) new
912   resend `>>
913     [selector := Nil.
914      roles := sig roles new.
915      inputVariables := sig inputVariables new.
916      restVariable := Nil.
917      optionalKeywords := sig optionalKeywords new.
918      optionalVariables := sig optionalVariables new. ]
921 method@(nodes MethodDefinition traits) as: sig@(nodes Signature traits)
923   sig new `>>
924     [selector := method selector.
925      roles := method roles.
926      inputVariables := method inputVariables.
927      inputVariables do: [| :var | var scope := sig].
928      restVariable := method restVariable.
929      optionalKeywords := method optionalKeywords.
930      optionalVariables := method optionalVariables. ]
933 sig@(nodes Signature traits) as: method@(nodes MethodDefinition traits)
935   method new `>>
936     [| :result |
937      selector := sig selector.
938      roles := sig roles.
939      inputVariables := sig inputVariables copy.
940      inputVariables do: [| :var | var scope := result].
941      localVariables := result inputVariables copy.
942      restVariable := sig restVariable.
943      optionalKeywords := sig optionalKeywords.
944      optionalVariables := sig optionalVariables.
945      optionalVariables do: [| :var | var scope := result]. ]
948 node1@(nodes Signature traits) = node2@(nodes Signature traits)
949 [node1 selector = node2 selector /\ [node1 roles = node2 roles]].
951 sig@(nodes Signature traits) walk: block
953   sig roles do: [| :role | role ifNotNil: [role walk: block]]
956 sig@(nodes Signature traits) transformChildren: block
958   sig roles infect: [| :role | role ifNotNil: [role transformBy: block]].
961 sig@(nodes Signature traits) deepCopy: scope &into: target
963   resend `>>
964     [roles := sig roles
965        collect: [| :role | role ifNotNil: [role deepCopy: scope]]. ]
968 sig@(nodes Signature traits) evaluateIn: namespace
970   sig
973 nodes define: #Variable &parents: {nodes Node} &slots: {
974   #name -> #''.
975   #scope -> nodes Ground
978 node1@(nodes Variable traits) = node2@(nodes Variable traits)
979 [node1 name = node2 name /\ [node1 scope = node2 scope]].
981 var@(nodes Variable traits) named: name
983   var clone `>> [name := name. ]
986 var@(nodes Variable traits) deepCopy: scope
988   scope findVariable: var name
991 var@(nodes Variable traits) isImmutable [False].
993 nodes define: #Binding &parents: {nodes Variable}.
995 var@(nodes Binding traits) isImmutable [True].
997 nodes define: #RestVariable &parents: {nodes Variable}.
999 nodes define: #VariableOperation &parents: {nodes Node} &slots: {#variable}.
1001 nodes define: #LoadVariable &parents: {nodes VariableOperation} &slots: {}.
1003 load@(nodes LoadVariable traits) from: variable
1004 [load new `setting: #{#variable} to: {variable}].
1006 var@(nodes Variable traits) load
1007 [nodes LoadVariable from: var].
1009 node1@(nodes LoadVariable traits) = node2@(nodes LoadVariable traits)
1010 [node1 variable = node2 variable].
1012 load@(nodes LoadVariable traits) deepCopy: scope
1014   (scope findVariable: load variable name)
1015     ifNil: [nodes UnaryMessage
1016               sending: load variable name
1017               to: {nodes ImplicitArgument}]
1018     ifNotNilDo: #(load from: _) `er
1021 load@(nodes LoadVariable traits) evaluateIn: namespace &optionals: opts
1023   load variable name sendTo: {namespace} &optionals: opts
1026 nodes define: #LoadRestVariable &parents: {nodes LoadVariable}.
1028 nodes define: #StoreVariable &parents: {nodes VariableOperation}
1029   &slots: {#value}.
1031 store@(nodes StoreVariable traits) of: value into: variable
1032 [store new `setting: #{#value. #variable} to: {value. variable}].
1034 var@(nodes Variable traits) store: value
1035 [nodes StoreVariable of: value into: var].
1037 var@(nodes Binding traits) store: value
1038 [error: 'Cannot rebind'].
1040 load@(nodes LoadVariable traits) store: value
1041 [load variable store: value].
1043 store@(nodes StoreVariable traits) load
1044 [store variable load].
1046 node1@(nodes StoreVariable traits) = node2@(nodes StoreVariable traits)
1047 [node1 variable = node2 variable /\ [node1 value = node2 value]].
1049 store@(nodes StoreVariable traits) walk: block
1051   resend.
1052   store value walk: block
1055 store@(nodes StoreVariable traits) transformChildren: block
1057   store value := store value transformBy: block.
1058   store
1061 store@(nodes StoreVariable traits) deepCopy: scope
1063   (scope findVariable: store variable name)
1064     ifNil:
1065       [nodes KeywordMessage
1066         sending: store variable name name ; ':'
1067         to: {nodes ImplicitArgument. store value deepCopy: scope}]
1068     ifNotNilDo:
1069       [| :var | store of: (store value deepCopy: scope) into: var]
1072 store@(nodes StoreVariable traits) evaluateIn: namespace &optionals: opts
1074   (store variable name name ; ':') intern
1075     sendTo: {namespace. store value evaluateIn: namespace}
1076     &optionals: opts
1079 nodes define: #Return &parents: {nodes Node} &slots: {#value}.
1081 ret@(nodes Return traits) of: value
1082 [ret new `setting: #{#value} to: {value}].
1084 node1@(nodes Return traits) = node2@(nodes Return traits)
1085 [node1 value = node2 value /\ [node1 isSameAs: node2]].
1087 ret@(nodes Return traits) walk: block
1089   resend.
1090   ret value walk: block
1093 ret@(nodes Return traits) deepCopy: scope
1095   ret of: (ret value deepCopy: scope)
1098 ret@(nodes Return traits) transformChildren: block
1100   ret value := ret value transformBy: block.
1101   ret
1104 nodes define: #ReturnClose &parents: {nodes Return}.
1106 ret@(nodes ReturnClose traits) selector [#^].
1108 nodes define: #ReturnFar &parents: {nodes Return}.
1110 ret@(nodes ReturnFar traits) selector [#^^].
1112 nodes define: #ReturnLevel &parents: {nodes Return} &slots: {#level -> 1}.
1114 ret@(nodes ReturnLevel traits) selector [('^' ; ret level printString) intern].
1116 ret@(nodes ReturnLevel traits) by: offset
1117 [ret new `setting: #{#level} to: {offset}].
1119 nodes define: #Resend &parents: {nodes Node}.
1121 _@(nodes Resend traits) selector [ #resend ].
1123 node1@(nodes Resend traits) = node2@(nodes Resend traits)
1124 [True].
1126 "Non-core utilities follow."
1128 b@(nodes Node traits) allSelectorsSent
1129 "Answer a Set of all selectors sent in the source."
1131   [| :result |
1132    b walk: [| :node | (node is: nodes Message) ifTrue:
1133      [result nextPut: node selector.
1134       ({#sendTo:. #sendTo:through:} includes: result selector)
1135         /\ [node arguments first is: Symbol]
1136         ifTrue: [result nextPut: node arguments first]]]]
1137     writingAs: IdentitySet
1140 n@(nodes Node traits) allMacroSelectorsSent
1141 "Answer a Set of selectors for the macro-messages sent in this parse tree."
1143   [| :calls |
1144    n walk: [| :node | (node is: nodes Macro)
1145                         ifTrue: [calls nextPut: node selector]]]
1146     writingAs: IdentitySet
1149 n@(nodes Node traits) nodeCount
1150 "Answer the number of nodes in this tree, analogous to the size of the tree."
1151 [| count |
1152   count := 0.
1153   n walk: [| :_ | count += 1].
1154   count
1157 n@(nodes Node traits) hasExplicitReturn
1158 "Answer whether there is an explicit/early return call."
1160   n walk: [| :node | (node is: nodes Return) ifTrue: [^ True]].
1161   False