Fixed a bug where two code branches with Bindings would never "unify" to one variable.
[cslatevm.git] / src / syntax / node.slate
blobae5f8faa0e8ed82fcd30a9b83ac3961f84e2285b
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 b@(nodes Node traits) allSelectorsSent
162 "Answer a Set of all selectors sent in the source."
164   [| :result |
165    b walk: [| :node | (node is: nodes Message) ifTrue:
166      [result nextPut: node selector.
167       ({#sendTo:. #sendTo:through:} includes: result selector)
168         /\ [node arguments first is: Symbol]
169         ifTrue: [result nextPut: node arguments first]]]]
170     writingAs: IdentitySet
173 nodes define: #UnaryMessage &parents: {nodes Message}.
175 message@(nodes UnaryMessage traits) sending: selector
176 "Send the selector to the implicit context."
177 [message sending: selector to: {nodes ImplicitArgument}].
179 node@(nodes UnaryMessage traits) argument
180 [node arguments first].
182 nodes define: #BinaryMessage &parents: {nodes Message}.
183 nodes define: #KeywordMessage &parents: {nodes Message}.
185 nodes define: #Macro &parents: {nodes Message}.
186 "Macro nodes are just like regular message-sends, except being applied at
187 compile-time to the Node trees for the expressions."
189 macro@(nodes Macro traits) evaluateIn: namespace &optionals: opts
190 "Evaluate the expansion. Should this be relied on? (I.e. should this throw a
191 condition which is resumable via macro-expansion?)"
193   (macro macroExpand &optionals:
194     (opts
195       ifNotNil:
196         [nodes OptionalKeywords new `>>
197            [message := macro.
198             keywords := opts atAll: (0 below: opts size by: 2).
199             arguments := opts atAll: (1 below: opts size by: 2). ]]))
200     evaluateIn: namespace
203 m@(nodes Macro traits) prototypeFor: selector
205   `conditions: (
206     [Syntax isUnarySelector: selector] -> [nodes UnaryMacro].
207     [Syntax isBinarySelector: selector] -> [nodes BinaryMacro]
208   ) otherwise: [nodes KeywordMacro]
211 nodes define: #UnaryMacro &parents: {nodes Macro}.
212 nodes define: #BinaryMacro &parents: {nodes Macro}.
213 nodes define: #KeywordMacro &parents: {nodes Macro}.
215 nodes define: #Deferred &parents: {nodes Message}.
216 "Deferred nodes are just like regular message-sends, except being applied
217 only when all argument promises are entirely resolved."
219 message@(nodes Message traits) deferred
220 [message as: nodes Deferred].
222 message@(nodes Deferred traits) evaluateIn: namespace &optionals: opts
224   (message arguments collect: #(evaluateIn: namespace) `er)
225     whenFulfilled: [| *args |
226       message selector sendTo: args &optionals: opts]
229 m@(nodes Deferred traits) prototypeFor: selector
231   `conditions: (
232     [Syntax isUnarySelector: selector] -> [nodes UnaryDeferred].
233     [Syntax isBinarySelector: selector] -> [nodes BinaryDeferred]
234   ) otherwise: [nodes KeywordDeferred]
237 nodes define: #UnaryDeferred &parents: {nodes Deferred}.
238 nodes define: #BinaryDeferred &parents: {nodes Deferred}.
239 nodes define: #KeywordDeferred &parents: {nodes Deferred}.
241 nodes define: #MessageWrapper &parents: {nodes Node}
242   &slots: {#message}.
244 w@(nodes MessageWrapper traits) for: message
245 [w new `setting: #{#message} to: {message}].
247 w@(nodes MessageWrapper traits) selector
248 [w message selector].
250 w@(nodes MessageWrapper traits) transformChildren: block
252   w message := w message transformBy: block.
253   w
256 w@(nodes MessageWrapper traits) walk: block
258   block applyWith: w.
259   w message walk: block.
262 w@(nodes MessageWrapper traits) deepCopy: scope
264   w clone `>> [message := w message deepCopy: scope. ]
267 nodes define: #OptionalKeywords &parents: {nodes MessageWrapper}
268   &slots: {#keywords -> {}. #arguments -> {}}.
269 "Annotates a Message with optional keywords and values given."
271 x@(nodes OptionalKeywords traits) = y@(nodes OptionalKeywords traits)
272 [x message = y message /\ [x keywords = y keywords] /\ [x arguments = y arguments]].
274 opts@(nodes OptionalKeywords traits) new
275 [resend clone `setting: #{#keywords. #arguments} to: #{{}. {}}].
277 opts@(nodes OptionalKeywords traits) walk: block
279   resend.
280   opts arguments
281     do: #(walk: block) `er
284 opts@(nodes OptionalKeywords traits) transformChildren: block
286   resend.
287   opts arguments infect: #(_ transformBy: block) `er.
288   opts
291 opts@(nodes OptionalKeywords traits) deepCopy: scope
293   resend `>> [arguments := opts arguments collect: #(deepCopy: scope) `er. ]
296 opts@(nodes OptionalKeywords traits) evaluateIn: namespace
298   opts message evaluateIn: namespace &optionals:
299     ([| :result |
300        opts keywords with: opts arguments
301          do: [| :key :arg | result nextPutAll: {key intern. arg evaluateIn: namespace}]
302      ] writingAs: #{})
305 nodes define: #RestArguments &parents: {nodes MessageWrapper}
306   &slots: {#arguments}.
308 x@(nodes RestArguments traits) = y@(nodes RestArguments traits)
309 [x message = y message /\ [x arguments = y arguments]].
311 rest@(nodes RestArguments traits) new
312 [resend clone `setting: #{#arguments} to: #{{}}].
314 rest@(nodes RestArguments traits) walk: block
316   resend.
317   rest arguments do: #(_ walk: block) `er
320 rest@(nodes RestArguments traits) transformChildren: block
322   resend.
323   rest arguments infect: #(_ transformBy: block) `er.
324   rest
327 rest@(nodes RestArguments traits) deepCopy: scope
329   resend `>> [arguments := rest arguments collect: #(deepCopy: scope) `er. ]
332 rest@(nodes RestArguments traits) allArguments
334   rest message arguments ; rest arguments
337 rest@(nodes RestArguments traits) evaluateIn: namespace &optionals: opts
339   rest selector sendTo:
340     (rest allArguments collect: #(evaluateIn: namespace) `er)
341     &optionals: opts
344 nodes define: #Placeholder &parents: {nodes Node}.
346 node@(nodes Node traits) as: _@(nodes Placeholder traits)
348   node
351 node@(nodes UnaryMessage traits) as: ph@(nodes Placeholder traits)
353   node selector = #_ /\ [node arguments first == nodes ImplicitArgument]
354     ifTrue: [ph] ifFalse: [node]
357 ph@(nodes Placeholder traits) evaluateIn: namespace &optionals: opts
359   ph
362 nodes define: #Pattern &parents: {nodes MessageWrapper}.
363 "Pattern nodes are just like regular message-sends, except having only
364 some arguments filled initially at parse-time. They may be treated as
365 records or curry-able message-sends."
367 pattern@(nodes Pattern traits) keywords
368 [pattern selector keywords].
370 pattern@(nodes Pattern traits) values
371 [pattern message arguments].
373 nodes Pattern traits define: #BlankTokens &builder:
374   [{nodes Placeholder. nodes ImplicitArgument}].
376 pattern@(nodes Pattern traits) isPlaceholder: node
378   pattern BlankTokens includes: node
381 pattern@(nodes Pattern traits) arity
382 [| count countedImplicit |
383   count := 0.
384   pattern walk:
385     [| :node |
386      `conditions: (
387         [node == nodes Placeholder]
388           -> [count += 1].
389         [node == nodes ImplicitArgument /\ [countedImplicit isNil]]
390           -> [countedImplicit := node. count += 1]
391     )].
392   count
395 pattern@(nodes Pattern traits) isComplete
396 "Answers whether it can be evaluated successfully."
398   pattern walk: [| :node | node == nodes Placeholder ifTrue: [^ False]].
399   True
402 pattern@(nodes Pattern traits) completeWith: values
403 [| valuesIn countedImplicit |
404   valuesIn := values reader.
405   pattern transformBy:
406     [| :node |
407      valuesIn isAtEnd
408        ifTrue: [node]
409        ifFalse:
410          [`conditions: (
411             [node == nodes ImplicitArgument /\ [countedImplicit isNil]]
412               -> [countedImplicit := node. valuesIn next].
413             [node == nodes Placeholder]
414               -> [valuesIn next]
415           ) otherwise: [node]]]
418 pattern@(nodes Pattern traits) deepCopy: scope
420   pattern for: (pattern message deepCopy: scope)
423 pattern@(nodes Pattern traits) evaluateIn: namespace &optionals: opts
424 "Patterns are auto-quasiquoting, in that their arguments get evaluated,
425 but the message is not sent."
427   pattern for: pattern message clone `>>
428     [arguments := pattern message arguments collect: #(evaluateIn: namespace) `er. ]
431 nodes define: #Literal &parents: {nodes Node} &slots: {#value}.
432 "The syntax for a literal Slate object, i.e. something the Lexer can create
433 directly."
435 nodes Literal traits define: #ReusableValues &builder: [Dictionary new].
436 nodes Literal traits define: #Nil &builder: [nodes Literal clone].
438 l@(nodes Literal traits) noteReusable: obj
439 [l ReusableValues at: obj ifAbsentPut:
440   [l new `setting: #{#value} to: {obj}]].
442 [| :each | nodes Literal noteReusable: each] for:
443   {Array new. ByteArray new. #''. ''}.
445 node@(nodes Literal traits) for: obj
446 [node ReusableValues at: obj ifAbsent: [node new `setting: #{#value} to: {obj}]].
448 node@(nodes Literal traits) for: _@Nil [node Nil].
450 x@(nodes Literal traits) = y@(nodes Literal traits)
451 [x value = y value].
453 node@(nodes Literal traits) evaluateIn: namespace
454 "A literal just evaluates to its expression-value."
455 [node value].
457 b@(nodes Node traits) allLiterals
458 "Answer an Array of all literal values from the source."
460   [| :result |
461    b walk: [| :node | (node is: nodes Literal) ifTrue:
462      [result nextPut: node value]]] writingAs: #{}
465 nodes define: #CompoundStatement &parents: {nodes Node}
466   &slots: {#statements -> #{}}.
468 array@(Sequence traits) as: group@(nodes CompoundStatement traits)
469 [group new `setting: #{#statements} to: {array as: group statements}].
471 group@(nodes CompoundStatement traits) size
472 "The number of statements/elements in the expression."
473 [group statements size].
475 node1@(nodes CompoundStatement traits) = node2@(nodes CompoundStatement traits)
476 [(node1 isSameAs: node2) /\ [node1 statements = node2 statements]].
478 group@(nodes CompoundStatement traits) walk: block
480   resend.
481   group statements do: #(_ walk: block) `er
484 group@(nodes CompoundStatement traits) transformChildren: block
486   group statements infect: #(_ transformBy: block) `er.
487   group
490 group@(nodes CompoundStatement traits) deepCopy: scope
492   (group statements collect:
493     #(_ deepCopy: scope) `er) as: group
496 nodes define: #Array &parents: {nodes CompoundStatement}.
498 group@(nodes Array traits) evaluateIn: namespace
500   group statements collect: #(evaluateIn: namespace) `er
503 nodes define: #Parenthesis &parents: {nodes CompoundStatement}.
505 group@(nodes Parenthesis traits) evaluateIn: namespace
507   group statements isEmpty
508     ifTrue: [Nil]
509     ifFalse:
510       [group statements allButLastDo: #(_ evaluateIn: namespace) `er.
511        group statements last evaluateIn: namespace]
514 group@(nodes Parenthesis traits) parenthesize
516   group
519 node@(nodes Node traits) parenthesize
521   {node} parenthesize
524 seq@(Sequence traits) parenthesize
526   seq size = 1 ifTrue: [seq first] ifFalse: [seq as: nodes Parenthesis]
529 nodes define: #Namespace &parents: {nodes Node} &slots: {#namespace -> lobby}.
531 node@(nodes Namespace traits) for: namespace
532 [node new `setting: #{#namespace} to: {namespace}].
534 node1@(nodes Namespace traits) = node2@(nodes Namespace traits)
535 [node1 namespace = node2 namespace].
537 _@(nodes Namespace traits) evaluateIn: namespace
538 [shouldNotImplement].
540 _@(nodes Namespace traits) parentScope
542   error: 'The top-level namespace has no parent scope.'
545 node@(nodes Namespace traits) topLevel
547   node
550 _@(nodes Namespace traits) findVariable: _
551 "Present for compatibility with Block findVariable:."
552 [Nil].
554 namespace@(nodes Namespace traits) includesScope: scope
555 [namespace == scope].
557 nodes define: #Ground &builder: [nodes Namespace for: lobby].
559 nodes define: #Block &parents: {nodes CompoundStatement} &slots:
560 {#parentScope -> nodes Ground.
561  #inputVariables -> #{}.
562 "Holds Variable nodes representing the block's inputs in order."
563  #restVariable -> Nil.
564 "Holds a Variable node representing the block's rest parameter if it
565 accepts one."
566  #optionalKeywords -> #{}.
567  #optionalVariables -> #{}.
568 "Holds Variable nodes representing the block's optional local slots."
569  #localVariables -> #{}
570 "Holds Variable nodes representing the block's local slots (including
571 inputs in order and optionals)."}.
573 node1@(nodes Block traits) = node2@(nodes Block traits)
574 "TODO: ensure this is correct and that local variable order is ignored."
576   resend
577    /\ [node1 inputVariables = node2 inputVariables]
578    /\ [node1 parentScope = node2 parentScope]
579    /\ [node1 localVariables = node2 localVariables]
582 block@(nodes Block traits) compile
583 "Invoke the VM ByteCompiler."
585   VM SSACompiler new generate: block result: Nil
588 block@(nodes Block traits) compileAndRun
589 "Compile the block using the VM ByteCompiler and then run it."
591   block compile do
594 block@(nodes Block traits) evaluateIn: namespace
595 "Compile the block and return it."
596 [block compile].
598 b@(nodes Block traits) new
600   resend `>>
601    [inputVariables := b inputVariables new.
602     localVariables := b localVariables new.
603     optionalKeywords := b optionalKeywords new.
604     optionalVariables := b optionalVariables new.
605     restVariable := Nil. ]
608 b@(nodes Block traits) body: body@(nodes Node traits)
609 "Makes a given Node the body."
610 [b statements := {body}].
612 b@(nodes Block traits) body: body@(nodes Parenthesis traits)
613 "Takes the statements as the body of the block."
614 [b statements := body statements].
616 b@(nodes Block traits) newFor: body@(nodes Node traits)
617 "Creates a new Block with the given node as the body."
618 [b new `>> [body := body. ]].
620 block@(nodes Block traits) addVariable: var
621 "Adds the Variable node to the block's locals and sets it as the
622 variable's scope (used to compile closures properly), and answers it."
624   (block localVariables anySatisfy: [| :other | other name = var name])
625     ifTrue:
626       [var name := block uniqueVariableName].
627   var scope := block.
628   block localVariables := block localVariables copyWith: var.
629   var
632 block@(nodes Block traits) addVariableNamed: name &varType: varType
633 "Creates a new Variable with the given name and adds it as a local,
634 then returning it."
636   varType `defaultsTo: nodes Variable.
637   block localVariables
638     detect: [| :var | var name = name /\ [var isSameAs: varType]]
639     ifNone: [block addVariable: (varType named: name)]
642 block@(nodes Block traits) uniqueVariableName &prefix: prefix
643 [| nameIndex |
644   prefix `defaultsTo: '_'.
645   nameIndex := 0.
646   [nameIndex < 100 /\
647      [(block findVariable: (prefix ; nameIndex printString) intern) isNotNil]]
648     whileTrue:
649       [nameIndex += 1].
650   nameIndex < 100
651     ifFalse:
652       [error: 'Could not generate a unique variable name.'].
653   (prefix ; nameIndex printString) intern
656 block@(nodes Block traits) addVariable &name: name &prefix: prefix
657 "Calls addVariable: with a name guaranteed not to clash with other such names."
659   name `defaultsTo: (block uniqueVariableName &prefix: prefix).
660   block addVariableNamed: name
663 block@(nodes Block traits) addInputVariableNamed: name
664 "Creates a new Variable with the given name and adds it as an input,
665 then returning it."
666 [| var |
667   var := block addVariableNamed: name.
668   block inputVariables := block inputVariables copyWith: var.
669   var
672 block@(nodes Block traits) addInputVariable &name: name &prefix: prefix
673 "Calls addInputVariable: with a name guaranteed not to clash with other such
674 names."
676   name `defaultsTo: (block uniqueVariableName &prefix: prefix).
677   block addInputVariableNamed: name
680 block@(nodes Block traits) addOptionalKeyword: key named: name
681 "Creates a new Variable with the given name and adds it as an optional,
682 then returning it."
683 [| var |
684   var := block addVariableNamed: name.
685   block optionalKeywords := block optionalKeywords copyWith: key intern.
686   block optionalVariables := block optionalVariables copyWith: var.
687   var
690 block@(nodes Block traits) topLevel
691 "Recurses up the scope to find the top-level scope."
693   block parentScope topLevel
696 block@(nodes Block traits) outermostBlock
697 "Answers the outermost scope that is still a Block or MethodDefinition and not
698 a Namespace."
699 [| scope |
700   scope := block.
701   [scope parentScope isSameAs: nodes Namespace]
702     whileFalse: [scope := scope parentScope].
703   scope
706 block@(nodes Block traits) hasVariableNamed: name
708   block localVariables anySatisfy: [| :var | name =~ var name]
711 block@(nodes Block traits) outermostScopeNotBinding: name
712 "Answers the outermost scope that does not have a given binding or slot."
713 [| scope |
714   (block hasVariableNamed: name) ifFalse:
715     [scope := block.
716      [(scope hasVariableNamed: name) \/ [scope parentScope isSameAs: nodes Namespace]]
717        whileFalse: [scope := scope parentScope]].
718   scope
721 block@(nodes Block traits) findVariable: name
722 "Searches through the current scope, and then upward, for the entry
723 corresponding to the given name, and answers what it can find, or Nil if none."
725   block localVariables
726     detect: [| :var | name =~ var name]
727     ifNone: [block parentScope findVariable: name]
730 block@(nodes Block traits) includesScope: scope
731 [block == scope \/ [block parentScope includesScope: scope]].
733 block@(nodes Block traits) from: varNames to: codeBlock &locals: localNames &linkVariables: linkVariables
734 "Takes an Array of symbol names or Nil's for unnamed variables, and runs the
735 code block with corresponding VariableNodes as inputs. The code block is
736 expected to return the method body expression. The method then answers a new
737 Block with that method body and those input variables."
738 [| result |
739   result := block new.
740   varNames do: [| :var | result addInputVariable &name: var].
741   localNames ifNotNil: [localNames do: [| :var | result addVariable &name: var]].
742   "ASSUME: newFor: does not clear inputs."
743   result body := codeBlock applyTo: result localVariables.
744   linkVariables ifNotNil: [result linkVariables].
745   result
748 b@(nodes Block traits) deepCopy: scope &into: target
749 "Copies up to the level of the given scope, and sets the scope to that one."
751   (target ifNil: [b]) clone `>>
752    [| :newBlock |
753     parentScope := scope.
754     localVariables :=
755       b localVariables collect:
756         [| :var newVar | var clone `>> [scope := newBlock. ]].
757     inputVariables :=
758       b inputVariables collect: [| :var | newBlock findVariable: var name].
759     optionalVariables :=
760       b optionalVariables collect: [| :var | newBlock findVariable: var name].
761     restVariable :=
762       b restVariable ifNotNil: [newBlock findVariable: b restVariable name].
763     statements :=
764       b statements collect: #(deepCopy: newBlock) `er.
765   ]
768 block@(nodes Block traits) deepCopy &into: target
769 "Copies the entire syntax tree with the (default) scope being the block's parent."
771   block deepCopy: block parentScope
774 block@(nodes Block traits) as: target@(nodes Block traits)
775 "This should allow Block and MethodDefinition objects to be converted (with
776 loss of Signature information, of course."
777 [block deepCopy &into: target].
779 block@(nodes Block traits) arity
780 [block inputVariables size].
782 dst@(nodes Block traits) addVariablesFrom: src@(nodes Block traits)
783 "Copies over the local variable entries from the source block to the
784 destination. Answers the locals found."
786   src localVariables do: #(dst addVariable: _) `er
789 b@(nodes Block traits) modifiesOwnVariables
790 "Answers whether there are any direct variable stores."
791 "TODO: Avoid re-implementing detect:!"
793   b walk: [| :node | (node is: nodes StoreVariable) ifTrue: [^ True]].
794   False
797 b@(nodes Block traits) modifiesInputVariables
798 "Answers whether there are any direct variable stores to inputs."
800   b walk: [| :node | (node is: nodes StoreVariable) /\
801              [b inputVariables includes: node variable] ifTrue: [^ True]].
802   False
805 b@(nodes Block traits) allSelectorsSent
807   [| :result |
808    b walk:
809      [| :node |
810       (node isSameAs: nodes LoadVariable) \/
811         [node isSameAs: nodes StoreVariable]
812       ifTrue: [result nextPut: node variable name]
813       ifFalse: [(node is: nodes Message)
814                 ifTrue: [result nextPut: node selector]]].
815    ] writingAs: Set
818 b@(nodes Block traits) allSelectorsSentToVar: var
819 "Answers the Set of all selectors called in this method on the Variable object."
820 [| loadExpr |
821   loadExpr := var load.
822   [| :result |
823    b statements walk:
824      [| :expr | (expr is: nodes Message)
825         /\ [expr arguments includes: loadExpr]
826         ifTrue: [result nextPut: expr selector]]
827    ] writingAs: Set
830 b@(nodes Block traits) allSelectorsSentToInputAt: argIndex
831 "Answers the Set of all selectors called in this method on the argument object."
833   (b inputVariables acceptsKey: argIndex)
834     ifTrue: [b allSelectorsSentToVar: (b inputVariables at: argIndex)]
835     ifFalse: [error: 'No such input argument.']
838 b@(nodes Block traits) allSelectorsSentToInputs
840   [| :result |
841    b inputVariables keysDo:
842      [| :index | result ; (b allSelectorsSentToInputAt: index)].
843    ] writingAs: Set
846 b@(nodes Block traits) allSelectorsSentImplicitly
848   [| :result |
849    b statements walk:
850      [| :node | (node is: nodes Message)
851                 ifTrue: [node arguments do:
852                   [| :arg | (arg is: nodes LoadVariable) /\
853                      [arg variable = nodes ImplicitArgument]
854                             ifTrue: [result nextPut: node selector]]]].
855    ] writingAs: Set
858 nodes define: #MethodDefinition &parents: {nodes Block}
859   &slots: {#selector. #roles -> #{}}.
860 "The object representing the definition of a Method."
862 method@(nodes MethodDefinition traits) new
863 [resend `>> [selector := Nil. roles := method roles new. ]].
865 method@(nodes MethodDefinition traits) of: selector on: roles
866   from: varNames to: codeBlock &locals: localNames &linkVariables: linkVariables
868   (method from: varNames to: codeBlock &locals: localNames &linkVariables: linkVariables) `>>
869     [selector := selector. roles := roles. ]
872 node1@(nodes MethodDefinition traits) = node2@(nodes MethodDefinition traits)
873 [resend /\ [node1 selector = node2 selector] /\ [node1 roles = node2 roles]].
875 method@(nodes MethodDefinition traits) walk: block
877   resend.
878   method roles do: [| :role | role ifNotNil: [role walk: block]]
881 method@(nodes MethodDefinition traits) transformChildren: block
883   method roles infect: [| :role | role ifNotNil: [role transformBy: block]].
884   resend
887 method@(nodes MethodDefinition traits) deepCopy: scope &into: target
889   resend `>>
890     [roles := method roles
891        collect: [| :role | role ifNotNil: [role deepCopy: scope]]. ]
894 method@(nodes MethodDefinition traits) evaluateIn: namespace
896   resend
897     asMethod: method selector
898     on: (method roles collect: #(evaluateIn: namespace) `er)
901 nodes define: #Signature &parents: {nodes Node} &slots: {
902   #selector.
903   #roles -> #{}.
904   #inputVariables -> #{}.
905   #restVariable -> Nil.
906   #optionalKeywords -> #{}.
907   #optionalVariables -> #{}
909 "The object representing the definition of a Method without the body."
911 sig@(nodes Signature traits) new
913   resend `>>
914     [selector := Nil.
915      roles := sig roles new.
916      inputVariables := sig inputVariables new.
917      restVariable := Nil.
918      optionalKeywords := sig optionalKeywords new.
919      optionalVariables := sig optionalVariables new. ]
922 method@(nodes MethodDefinition traits) as: sig@(nodes Signature traits)
924   sig new `>>
925     [selector := method selector.
926      roles := method roles.
927      inputVariables := method inputVariables.
928      inputVariables do: [| :var | var scope := Nil].
929      restVariable := method restVariable.
930      optionalKeywords := method optionalKeywords.
931      optionalVariables := method optionalVariables. ]
934 sig@(nodes Signature traits) as: method@(nodes MethodDefinition traits)
936   method new `>>
937     [| :result |
938      selector := sig selector.
939      roles := sig roles.
940      inputVariables := sig inputVariables copy.
941      inputVariables do: [| :var | var scope := result].
942      localVariables := result inputVariables copy.
943      restVariable := sig restVariable.
944      optionalKeywords := sig optionalKeywords.
945      optionalVariables := sig optionalVariables. ]
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 n@(nodes Node traits) allSelectorsSent
1129 "Answer a Set of selectors for the messages sent in this parse tree."
1131   [| :calls |
1132    n walk: [| :node | (node is: nodes Message)
1133                         ifTrue: [calls nextPut: node selector]]]
1134     writingAs: (IdentitySet new &capacity: 100)
1137 n@(nodes Node traits) allMacroSelectorsSent
1138 "Answer a Set of selectors for the macro-messages sent in this parse tree."
1140   [| :calls |
1141    n walk: [| :node | (node is: nodes Macro)
1142                         ifTrue: [calls nextPut: node selector]]]
1143     writingAs: (IdentitySet new &capacity: 100)
1146 n@(nodes Node traits) nodeCount
1147 "Answer the number of nodes in this tree, analogous to the size of the tree."
1148 [| count |
1149   count := 0.
1150   n walk: [| :_ | count += 1].
1151   count
1154 n@(nodes Node traits) hasExplicitReturn
1155 "Answer whether there is an explicit/early return call."
1157   n walk: [| :node | (node is: nodes Return) ifTrue: [^ True]].
1158   False