Renamed "Partial" to "Pattern" in Syntax code.
[cslatevm.git] / src / syntax / node.slate
blobba95d45d9a76f6381551f180a5f99c354262cc31
1 ensureNamespace: #nodes &delegate: True.
3 (Syntax addDelegateNamed: #nodes valued: nodes) `bootstrapping.
5 nodes define: #Node &parents: {Cloneable} &slots:
6 {#type -> Types Any. "The annotated type, by the inferencer or manually."
7  #source -> Nil. "The source of the lexer stream"
8  #lineNumber -> Nil "The line number in the source code at which the node was read."}.
9 "The general syntax object for expressions."
11 node@(nodes Node traits) new
12 [resend `setting: #{#type. #lineNumber} to: {Types Any. Nil}].
14 node@(nodes Node traits) evaluate
15 [node evaluateIn: lobby].
17 node@(nodes Node traits) evaluateIn: namespace
18 [overrideThis].
20 node@(nodes Node traits) walk: block
21 "A depth-first do:-style iteration through Nodes; a code/tree-walker."
23   block applyWith: node.
26 node@(nodes Node traits) transformBy: block
27 "Transforms the tree's nodes in-place by the block closure.
28 Only transformChildren: needs to be overridden."
30   (block applyWith: node) transformChildren: block
33 node@(nodes Node traits) transformChildren: block
34 "Act on each of a node's children in-place.
35 This gets overridden for the various compound node types."
37   node
40 node@(nodes Node traits) deepCopy: scope
41 "Copies the entire syntax tree, with the given scope as the lexical reference.
42 This gets overridden for each type that is compound or relates to the scope."
44   node
47 node@(nodes Node traits) deepCopy
48 "Copies the entire syntax tree with the (default) scope being the lobby."
50   node deepCopy: nodes Ground
53 node@(nodes Node traits) definitionLocation
55   (node source hasSlotNamed: #resource)
56     ifTrue: [node source resource locator
57                ifNil: ['stdin:' ; (node lineNumber - 2) printString]
58                ifNotNilDo: [| :loc | (loc as: String) ; ':' ; node lineNumber printString]]
59     ifFalse: [node source
60                 ifNil: ['Nil']
61                 ifNotNil: [node source printString ; ':' ; node lineNumber printString]]
64 nodes define: #Annotation &parents: {nodes Node}
65   &slots: {#value "The annotated node."}.
66 "A wrapper for other Nodes that adds an annotative object."
68 x@(nodes Annotation traits) = y@(nodes Annotation traits)
69 [x value = y value].
71 ann@(nodes Annotation traits) walk: block
73   block applyWith: ann.
74   ann value walk: block
77 ann@(nodes Annotation traits) transformChildren: block
79   ann value: (ann value transformBy: block).
80   ann
83 ann@(nodes Annotation traits) deepCopy: scope
84 [ann clone `setting: #{#value} to: {ann value deepCopy: scope}].
86 ann@(nodes Annotation traits) evaluateIn: namespace
87 [ann value evaluateIn: namespace].
89 nodes define: #Comment &parents: {nodes Annotation}
90 &slots: {#comment -> '' "The comment object, an empty String by default."}.
91 "Comments are nodes that contain the expression that they annotate."
93 x@(nodes Comment traits) = y@(nodes Comment traits)
94 [x value = y value /\ [x comment = y comment]].
96 node@(nodes Node traits) comment: comment
97 "Returns a new Comment with the given comment wrapping the original
98 Node. Usable as a macro."
99 [nodes Comment clone `setting: #{#comment. #value} to: {comment evaluate. node}].
101 nodes define: #ImplicitArgument &parents: {nodes Node}.
102 "Implicit arguments include anything sent to the local context, as well as
103 the lobby."
105 node1@(nodes ImplicitArgument traits) = node2@(nodes ImplicitArgument traits)
106 [True].
108 node@(nodes ImplicitArgument traits) evaluateIn: namespace
109 "The default is to simply return the namespace as the result."
110 [namespace].
112 nodes define: #Message &parents: {nodes Node}
113   &slots: {#selector -> #'' . #arguments -> #{}}.
114 "Represents a message send."
116 m@(nodes Message traits) prototypeFor: selector
118   `conditions: (
119     [Syntax isUnarySelector: selector] -> [nodes UnaryMessage].
120     [Syntax isBinarySelector: selector] -> [nodes BinaryMessage]
121   ) otherwise: [nodes KeywordMessage]
124 message@(nodes Message traits) sending: selector to: arguments
125 [(message prototypeFor: selector) clone `setting: #{#selector. #arguments} to:
126   {selector intern. arguments}].
128 x@(nodes Message traits) as: y@(nodes Message traits)
129 [y sending: x selector to: x arguments].
131 node1@(nodes Message traits) = node2@(nodes Message traits)
133   node1 selector = node2 selector
134    /\ [node1 isSameAs: node2]
135    /\ [node1 arguments = node2 arguments]
138 message@(nodes Message traits) walk: block
140   resend.
141   message arguments do: #(_ walk: block) `er
144 message@(nodes Message traits) transformChildren: block
146   message arguments infect: #(_ transformBy: block) `er.
147   message
150 message@(nodes Message traits) deepCopy: scope
152   message clone `>> [arguments := message arguments collect: #(deepCopy: scope) `er. ]
155 message@(nodes Message traits) evaluateIn: namespace &optionals: opts
156 "Overridden to support the evaluateIn: for ImplicitArgument."
158   message selector sendTo:
159     (message arguments collect: #(evaluateIn: namespace) `er)
160     &optionals: opts
163 b@(nodes Node traits) allSelectorsSent
164 "Answer a Set of all selectors sent in the source."
166   [| :result |
167    b walk: [| :node | (node is: nodes Message) ifTrue:
168      [result nextPut: node selector.
169       ({#sendTo:. #sendTo:through:} includes: result selector)
170         /\ [node arguments first is: Symbol]
171         ifTrue: [result nextPut: node arguments first]]]]
172     writingAs: IdentitySet
175 nodes define: #UnaryMessage &parents: {nodes Message}.
177 message@(nodes UnaryMessage traits) sending: selector
178 "Send the selector to the implicit context."
179 [message sending: selector to: {nodes ImplicitArgument}].
181 node@(nodes UnaryMessage traits) argument
182 [node arguments first].
184 nodes define: #BinaryMessage &parents: {nodes Message}.
185 nodes define: #KeywordMessage &parents: {nodes Message}.
187 nodes define: #Macro &parents: {nodes Message}.
188 "Macro nodes are just like regular message-sends, except being applied at
189 compile-time to the Node trees for the expressions."
191 macro@(nodes Macro traits) evaluateIn: namespace &optionals: opts
192 "Evaluate the expansion. Should this be relied on? (I.e. should this throw a
193 condition which is resumable via macro-expansion?)"
195   (macro macroExpand &optionals:
196     (opts
197       ifNotNil:
198         [nodes OptionalKeywords new `>>
199            [message := macro.
200             keywords := opts atAll: (0 below: opts size by: 2).
201             arguments := opts atAll: (1 below: opts size by: 2). ]]))
202     evaluateIn: namespace
205 m@(nodes Macro traits) prototypeFor: selector
207   `conditions: (
208     [Syntax isUnarySelector: selector] -> [nodes UnaryMacro].
209     [Syntax isBinarySelector: selector] -> [nodes BinaryMacro]
210   ) otherwise: [nodes KeywordMacro]
213 nodes define: #UnaryMacro &parents: {nodes Macro}.
214 nodes define: #BinaryMacro &parents: {nodes Macro}.
215 nodes define: #KeywordMacro &parents: {nodes Macro}.
217 nodes define: #Deferred &parents: {nodes Message}.
218 "Deferred nodes are just like regular message-sends, except being applied
219 only when all argument promises are entirely resolved."
221 message@(nodes Message traits) deferred
222 [message as: nodes Deferred].
224 message@(nodes Deferred traits) evaluateIn: namespace &optionals: opts
226   (message arguments collect: #(evaluateIn: namespace) `er)
227     whenFulfilled: [| *args |
228       message selector sendTo: args &optionals: opts]
231 m@(nodes Deferred traits) prototypeFor: selector
233   `conditions: (
234     [Syntax isUnarySelector: selector] -> [nodes UnaryDeferred].
235     [Syntax isBinarySelector: selector] -> [nodes BinaryDeferred]
236   ) otherwise: [nodes KeywordDeferred]
239 nodes define: #UnaryDeferred &parents: {nodes Deferred}.
240 nodes define: #BinaryDeferred &parents: {nodes Deferred}.
241 nodes define: #KeywordDeferred &parents: {nodes Deferred}.
243 nodes define: #MessageWrapper &parents: {nodes Node}
244   &slots: {#message}.
246 w@(nodes MessageWrapper traits) for: message
247 [w new `setting: #{#message} to: {message}].
249 w@(nodes MessageWrapper traits) selector
250 [w message selector].
252 w@(nodes MessageWrapper traits) transformChildren: block
254   w message := w message transformBy: block.
255   w
258 w@(nodes MessageWrapper traits) walk: block
260   block applyWith: w.
261   w message walk: block.
264 w@(nodes MessageWrapper traits) deepCopy: scope
266   w clone `>> [message := w message deepCopy: scope. ]
269 nodes define: #OptionalKeywords &parents: {nodes MessageWrapper}
270   &slots: {#keywords -> {}. #arguments -> {}}.
271 "Annotates a Message with optional keywords and values given."
273 x@(nodes OptionalKeywords traits) = y@(nodes OptionalKeywords traits)
274 [x message = y message /\ [x keywords = y keywords] /\ [x arguments = y arguments]].
276 opts@(nodes OptionalKeywords traits) new
277 [resend clone `setting: #{#keywords. #arguments} to: #{{}. {}}].
279 opts@(nodes OptionalKeywords traits) walk: block
281   resend.
282   opts arguments
283     do: #(walk: block) `er
286 opts@(nodes OptionalKeywords traits) transformChildren: block
288   resend.
289   opts arguments infect: #(_ transformBy: block) `er.
290   opts
293 opts@(nodes OptionalKeywords traits) deepCopy: scope
295   resend `>> [arguments := opts arguments collect: #(deepCopy: scope) `er. ]
298 opts@(nodes OptionalKeywords traits) evaluateIn: namespace
300   opts message evaluateIn: namespace &optionals:
301     ([| :result |
302        opts keywords with: opts arguments
303          do: [| :key :arg | result nextPutAll: {key intern. arg evaluateIn: namespace}]
304      ] writingAs: #{})
307 nodes define: #RestArguments &parents: {nodes MessageWrapper}
308   &slots: {#arguments}.
310 x@(nodes RestArguments traits) = y@(nodes RestArguments traits)
311 [x message = y message /\ [x arguments = y arguments]].
313 rest@(nodes RestArguments traits) new
314 [resend clone `setting: #{#arguments} to: #{{}}].
316 rest@(nodes RestArguments traits) walk: block
318   resend.
319   rest arguments do: #(_ walk: block) `er
322 rest@(nodes RestArguments traits) transformChildren: block
324   resend.
325   rest arguments infect: #(_ transformBy: block) `er.
326   rest
329 rest@(nodes RestArguments traits) deepCopy: scope
331   resend `>> [arguments := rest arguments collect: #(deepCopy: scope) `er. ]
334 rest@(nodes RestArguments traits) allArguments
336   rest message arguments ; rest arguments
339 rest@(nodes RestArguments traits) evaluateIn: namespace &optionals: opts
341   rest selector sendTo:
342     (rest allArguments collect: #(evaluateIn: namespace) `er)
343     &optionals: opts
346 nodes define: #Placeholder &parents: {nodes Node}.
348 node@(nodes Node traits) as: _@(nodes Placeholder traits)
350   node
353 node@(nodes UnaryMessage traits) as: ph@(nodes Placeholder traits)
355   node selector = #_ /\ [node arguments first == nodes ImplicitArgument]
356     ifTrue: [ph] ifFalse: [node]
359 ph@(nodes Placeholder traits) evaluateIn: namespace &optionals: opts
361   ph
364 nodes define: #Pattern &parents: {nodes MessageWrapper}.
365 "Pattern nodes are just like regular message-sends, except having only
366 some arguments filled initially at parse-time. They may be treated as
367 records or curry-able message-sends."
369 w@(nodes Pattern traits) keywords
370 [w selector keywords].
372 w@(nodes Pattern traits) values
373 [w message arguments].
375 nodes Pattern traits define: #BlankTokens &builder:
376   [{nodes Placeholder. nodes ImplicitArgument}].
378 w@(nodes Pattern traits) isPlaceholder: node
380   w BlankTokens includes: node
383 w@(nodes Pattern traits) arity
384 [| count countedImplicit |
385   count := 0.
386   w walk:
387     [| :node |
388      `conditions: (
389         [node == nodes Placeholder]
390           -> [count += 1].
391         [node == nodes ImplicitArgument /\ [countedImplicit isNil]]
392           -> [countedImplicit := node. count += 1]
393     )].
394   count
397 w@(nodes Pattern traits) isComplete
398 "Answers whether it can be evaluated successfully."
400   w walk: [| :node | node == nodes Placeholder ifTrue: [^ False]].
401   True
404 w@(nodes Pattern traits) completeWith: values
405 [| valuesIn countedImplicit |
406   valuesIn := values reader.
407   w transformBy:
408     [| :node |
409      valuesIn isAtEnd
410        ifTrue: [node]
411        ifFalse:
412          [`conditions: (
413             [node == nodes ImplicitArgument /\ [countedImplicit isNil]]
414               -> [countedImplicit := node. valuesIn next].
415             [node == nodes Placeholder]
416               -> [valuesIn next]
417           ) otherwise: [node]]]
420 w@(nodes Pattern traits) evaluateIn: namespace &optionals: opts
422   w isComplete
423     ifTrue: [w message evaluateIn: namespace &optionals: opts]
424     ifFalse: [w]
427 nodes define: #Literal &parents: {nodes Node} &slots: {#value}.
428 "The syntax for a literal Slate object, i.e. something the Lexer can create
429 directly."
431 nodes Literal traits define: #ReusableValues &builder: [Dictionary new].
432 nodes Literal traits define: #Nil &builder: [nodes Literal clone].
434 l@(nodes Literal traits) noteReusable: obj
435 [l ReusableValues at: obj ifAbsentPut:
436   [l new `setting: #{#value} to: {obj}]].
438 [| :each | nodes Literal noteReusable: each] for:
439   {Array new. ByteArray new. #''. ''}.
441 node@(nodes Literal traits) for: obj
442 [node ReusableValues at: obj ifAbsent: [node new `setting: #{#value} to: {obj}]].
444 node@(nodes Literal traits) for: _@Nil [node Nil].
446 x@(nodes Literal traits) = y@(nodes Literal traits)
447 [x value = y value].
449 node@(nodes Literal traits) evaluateIn: namespace
450 "A literal just evaluates to its expression-value."
451 [node value].
453 b@(nodes Node traits) allLiterals
454 "Answer an Array of all literal values from the source."
456   [| :result |
457    b walk: [| :node | (node is: nodes Literal) ifTrue:
458      [result nextPut: node value]]] writingAs: #{}
461 nodes define: #CompoundStatement &parents: {nodes Node}
462   &slots: {#statements -> #{}}.
464 array@(Sequence traits) as: group@(nodes CompoundStatement traits)
465 [group new `setting: #{#statements} to: {array as: group statements}].
467 group@(nodes CompoundStatement traits) size
468 "The number of statements/elements in the expression."
469 [group statements size].
471 node1@(nodes CompoundStatement traits) = node2@(nodes CompoundStatement traits)
472 [(node1 isSameAs: node2) /\ [node1 statements = node2 statements]].
474 group@(nodes CompoundStatement traits) walk: block
476   resend.
477   group statements do: #(_ walk: block) `er
480 group@(nodes CompoundStatement traits) transformChildren: block
482   group statements infect: #(_ transformBy: block) `er.
483   group
486 group@(nodes CompoundStatement traits) deepCopy: scope
488   (group statements collect:
489     #(_ deepCopy: scope) `er) as: group
492 nodes define: #Array &parents: {nodes CompoundStatement}.
494 group@(nodes Array traits) evaluateIn: namespace
496   group statements collect: #(evaluateIn: namespace) `er
499 nodes define: #Parenthesis &parents: {nodes CompoundStatement}.
501 group@(nodes Parenthesis traits) evaluateIn: namespace
503   group statements isEmpty
504     ifTrue: [Nil]
505     ifFalse:
506       [group statements allButLastDo: #(_ evaluateIn: namespace) `er.
507        group statements last evaluateIn: namespace]
510 group@(nodes Parenthesis traits) parenthesize
512   group
515 node@(nodes Node traits) parenthesize
517   {node} parenthesize
520 seq@(Sequence traits) parenthesize
522   seq size = 1 ifTrue: [seq first] ifFalse: [seq as: nodes Parenthesis]
525 nodes define: #Namespace &parents: {nodes Node} &slots: {#namespace -> lobby}.
527 node@(nodes Namespace traits) for: namespace
528 [node new `setting: #{#namespace} to: {namespace}].
530 node1@(nodes Namespace traits) = node2@(nodes Namespace traits)
531 [node1 namespace = node2 namespace].
533 _@(nodes Namespace traits) evaluateIn: namespace
534 [shouldNotImplement].
536 _@(nodes Namespace traits) parentScope
538   error: 'The top-level namespace has no parent scope.'
541 node@(nodes Namespace traits) topLevel
543   node
546 _@(nodes Namespace traits) findVariable: _
547 "Present for compatibility with Block findVariable:."
548 [Nil].
550 namespace@(nodes Namespace traits) includesScope: scope
551 [namespace == scope].
553 nodes define: #Ground &builder: [nodes Namespace for: lobby].
555 nodes define: #Block &parents: {nodes CompoundStatement} &slots:
556 {#parentScope -> nodes Ground.
557  #inputVariables -> #{}.
558 "Holds Variable nodes representing the block's inputs in order."
559  #restVariable -> Nil.
560 "Holds a Variable node representing the block's rest parameter if it
561 accepts one."
562  #optionalKeywords -> #{}.
563  #optionalVariables -> #{}.
564 "Holds Variable nodes representing the block's optional local slots."
565  #localVariables -> #{}
566 "Holds Variable nodes representing the block's local slots (including
567 inputs in order and optionals)."}.
569 node1@(nodes Block traits) = node2@(nodes Block traits)
570 "TODO: ensure this is correct and that local variable order is ignored."
572   resend
573    /\ [node1 inputVariables = node2 inputVariables]
574    /\ [node1 parentScope = node2 parentScope]
575    /\ [node1 localVariables = node2 localVariables]
578 block@(nodes Block traits) compile
579 "Invoke the VM ByteCompiler."
581   VM SSACompiler new generate: block result: Nil
584 block@(nodes Block traits) compileAndRun
585 "Compile the block using the VM ByteCompiler and then run it."
587   block compile do
590 block@(nodes Block traits) evaluateIn: namespace
591 "Compile the block and return it."
592 [block compile].
594 b@(nodes Block traits) new
596   resend `>>
597    [inputVariables := b inputVariables new.
598     localVariables := b localVariables new.
599     optionalKeywords := b optionalKeywords new.
600     optionalVariables := b optionalVariables new.
601     restVariable := Nil. ]
604 b@(nodes Block traits) body: body@(nodes Node traits)
605 "Makes a given Node the body."
606 [b statements := {body}].
608 b@(nodes Block traits) body: body@(nodes Parenthesis traits)
609 "Takes the statements as the body of the block."
610 [b statements := body statements].
612 b@(nodes Block traits) newFor: body@(nodes Node traits)
613 "Creates a new Block with the given node as the body."
614 [b new `>> [body := body. ]].
616 block@(nodes Block traits) addVariable: var
617 "Adds the Variable node to the block's locals and sets it as the
618 variable's scope (used to compile closures properly), and answers it."
620   (block localVariables anySatisfy: [| :other | other name = var name])
621     ifTrue:
622       [var name := block uniqueVariableName].
623   var scope := block.
624   block localVariables := block localVariables ; { var }.
625   var
628 block@(nodes Block traits) addVariableNamed: name
629 "Creates a new Variable with the given name and adds it as a local,
630 then returning it."
631 [block addVariable: (nodes Variable clone `setting: #{#name} to: {name})].
633 block@(nodes Block traits) uniqueVariableName &prefix: prefix
634 [| nameIndex |
635   prefix `defaultsTo: '_'.
636   nameIndex := 0.
637   [nameIndex < 100 /\
638      [(block findVariable: (prefix ; nameIndex printString) intern) isNotNil]]
639     whileTrue:
640       [nameIndex += 1].
641   nameIndex < 100
642     ifFalse:
643       [error: 'Could not generate a unique variable name.'].
644   (prefix ; nameIndex printString) intern
647 block@(nodes Block traits) addVariable &name: name &prefix: prefix
648 "Calls addVariable: with a name guaranteed not to clash with other such names."
650   name `defaultsTo: (block uniqueVariableName &prefix: prefix).
651   block addVariableNamed: name
654 block@(nodes Block traits) addInputVariableNamed: name
655 "Creates a new Variable with the given name and adds it as an input,
656 then returning it."
657 [| var |
658   var := block addVariableNamed: name.
659   block inputVariables := block inputVariables ; { var }.
660   var
663 block@(nodes Block traits) addInputVariable &name: name &prefix: prefix
664 "Calls addInputVariable: with a name guaranteed not to clash with other such
665 names."
667   name `defaultsTo: (block uniqueVariableName &prefix: prefix).
668   block addInputVariableNamed: name
671 block@(nodes Block traits) addOptionalKeyword: key named: name
672 "Creates a new Variable with the given name and adds it as an optional,
673 then returning it."
674 [| var |
675   var := block addVariableNamed: name.
676   block optionalKeywords := block optionalKeywords ; { key intern }.
677   block optionalVariables := block optionalVariables ; { var }.
678   var
681 block@(nodes Block traits) topLevel
682 "Recurses up the scope to find the top-level scope."
684   block parentScope topLevel
687 block@(nodes Block traits) outermostBlock
688 "Answers the outermost scope that is still a Block or MethodDefinition and not
689 a Namespace."
690 [| scope |
691   scope := block.
692   [scope parentScope isSameAs: nodes Namespace]
693     whileFalse: [scope := scope parentScope].
694   scope
697 block@(nodes Block traits) findVariable: name
698 "Searches through the current scope, and then upward, for the entry
699 corresponding to the given name, and answers what it can find, or Nil if none."
701   block localVariables
702     detect: [| :var | name =~ var name]
703     ifNone: [block parentScope findVariable: name]
706 block@(nodes Block traits) includesScope: scope
707 [block == scope \/ [block parentScope includesScope: scope]].
709 block@(nodes Block traits) from: varNames to: codeBlock &locals: localNames &linkVariables: linkVariables
710 "Takes an Array of symbol names or Nil's for unnamed variables, and runs the
711 code block with corresponding VariableNodes as inputs. The code block is
712 expected to return the method body expression. The method then answers a new
713 Block with that method body and those input variables."
714 [| result |
715   result := block new.
716   varNames do: [| :var | result addInputVariable &name: var].
717   localNames ifNotNil: [localNames do: [| :var | result addVariable &name: var]].
718   "ASSUME: newFor: does not clear inputs."
719   result body := codeBlock applyTo: result localVariables.
720   linkVariables ifNotNil: [result linkVariables].
721   result
724 b@(nodes Block traits) deepCopy: scope &into: target
725 "Copies up to the level of the given scope, and sets the scope to that one."
727   (target ifNil: [b]) clone `>>
728    [| :newBlock |
729     parentScope := scope.
730     localVariables :=
731       b localVariables collect:
732         [| :var newVar | var clone `>> [scope := newBlock. ]].
733     inputVariables :=
734       b inputVariables collect: [| :var | newBlock findVariable: var name].
735     optionalVariables :=
736       b optionalVariables collect: [| :var | newBlock findVariable: var name].
737     restVariable :=
738       b restVariable ifNotNil: [newBlock findVariable: b restVariable name].
739     statements :=
740       b statements collect: #(deepCopy: newBlock) `er.
741   ]
744 block@(nodes Block traits) deepCopy &into: target
745 "Copies the entire syntax tree with the (default) scope being the block's parent."
747   block deepCopy: block parentScope
750 block@(nodes Block traits) as: target@(nodes Block traits)
751 "This should allow Block and MethodDefinition objects to be converted (with
752 loss of Signature information, of course."
753 [block deepCopy &into: target].
755 block@(nodes Block traits) arity
756 [block inputVariables size].
758 dst@(nodes Block traits) addVariablesFrom: src@(nodes Block traits)
759 "Copies over the local variable entries from the source block to the
760 destination. Answers the locals found."
762   src localVariables do: #(dst addVariable: _) `er
765 b@(nodes Block traits) modifiesOwnVariables
766 "Answers whether there are any direct variable stores."
767 "TODO: Avoid re-implementing detect:!"
769   b walk: [| :node | (node is: nodes StoreVariable) ifTrue: [^ True]].
770   False
773 b@(nodes Block traits) modifiesInputVariables
774 "Answers whether there are any direct variable stores to inputs."
776   b walk: [| :node | (node is: nodes StoreVariable) /\
777              [b inputVariables includes: node variable] ifTrue: [^ True]].
778   False
781 b@(nodes Block traits) allSelectorsSent
783   [| :result |
784    b walk:
785      [| :node |
786       (node isSameAs: nodes LoadVariable) \/
787         [node isSameAs: nodes StoreVariable]
788       ifTrue: [result nextPut: node variable name]
789       ifFalse: [(node is: nodes Message)
790                 ifTrue: [result nextPut: node selector]]].
791    ] writingAs: Set
794 b@(nodes Block traits) allSelectorsSentToVar: var
795 "Answers the Set of all selectors called in this method on the Variable object."
796 [| loadExpr |
797   loadExpr := var load.
798   [| :result |
799    b statements walk:
800      [| :expr | (expr is: nodes Message)
801         /\ [expr arguments includes: loadExpr]
802         ifTrue: [result nextPut: expr selector]]
803    ] writingAs: Set
806 b@(nodes Block traits) allSelectorsSentToInputAt: argIndex
807 "Answers the Set of all selectors called in this method on the argument object."
809   (b inputVariables acceptsKey: argIndex)
810     ifTrue: [b allSelectorsSentToVar: (b inputVariables at: argIndex)]
811     ifFalse: [error: 'No such input argument.']
814 b@(nodes Block traits) allSelectorsSentToInputs
816   [| :result |
817    b inputVariables keysDo:
818      [| :index | result ; (b allSelectorsSentToInputAt: index)].
819    ] writingAs: Set
822 b@(nodes Block traits) allSelectorsSentImplicitly
824   [| :result |
825    b statements walk:
826      [| :node | (node is: nodes Message)
827                 ifTrue: [node arguments do:
828                   [| :arg | (arg is: nodes LoadVariable) /\
829                      [arg variable = nodes ImplicitArgument]
830                             ifTrue: [result nextPut: node selector]]]].
831    ] writingAs: Set
834 nodes define: #MethodDefinition &parents: {nodes Block}
835   &slots: {#selector. #roles -> #{}}.
836 "The object representing the definition of a Method."
838 method@(nodes MethodDefinition traits) new
839 [resend `>> [selector := Nil. roles := method roles new. ]].
841 method@(nodes MethodDefinition traits) of: selector on: roles
842   from: varNames to: codeBlock &locals: localNames &linkVariables: linkVariables
844   (method from: varNames to: codeBlock &locals: localNames &linkVariables: linkVariables) `>>
845     [selector := selector. roles := roles. ]
848 node1@(nodes MethodDefinition traits) = node2@(nodes MethodDefinition traits)
849 [resend /\ [node1 selector = node2 selector] /\ [node1 roles = node2 roles]].
851 method@(nodes MethodDefinition traits) walk: block
853   resend.
854   method roles do: [| :role | role ifNotNil: [role walk: block]]
857 method@(nodes MethodDefinition traits) transformChildren: block
859   method roles infect: [| :role | role ifNotNil: [role transformBy: block]].
860   resend
863 method@(nodes MethodDefinition traits) deepCopy: scope &into: target
865   resend `>>
866     [roles := method roles
867        collect: [| :role | role ifNotNil: [role deepCopy: scope]]. ]
870 method@(nodes MethodDefinition traits) evaluateIn: namespace
872   resend
873     asMethod: method selector
874     on: (method roles collect: #(evaluateIn: namespace) `er)
877 nodes define: #Signature &parents: {nodes Node} &slots: {
878   #selector.
879   #roles -> #{}.
880   #inputVariables -> #{}.
881   #restVariable -> Nil.
882   #optionalKeywords -> #{}.
883   #optionalVariables -> #{}
885 "The object representing the definition of a Method without the body."
887 sig@(nodes Signature traits) new
889   resend `>>
890     [selector := Nil.
891      roles := sig roles new.
892      inputVariables := sig inputVariables new.
893      restVariable := Nil.
894      optionalKeywords := sig optionalKeywords new.
895      optionalVariables := sig optionalVariables new. ]
898 method@(nodes MethodDefinition traits) as: sig@(nodes Signature traits)
900   sig new `>>
901     [selector := method selector.
902      roles := method roles.
903      inputVariables := method inputVariables.
904      inputVariables do: [| :var | var scope := Nil].
905      restVariable := method restVariable.
906      optionalKeywords := method optionalKeywords.
907      optionalVariables := method optionalVariables. ]
910 sig@(nodes Signature traits) as: method@(nodes MethodDefinition traits)
912   method new `>>
913     [| :result |
914      selector := sig selector.
915      roles := sig roles.
916      inputVariables := sig inputVariables copy.
917      inputVariables do: [| :var | var scope := result].
918      localVariables := result inputVariables copy.
919      restVariable := sig restVariable.
920      optionalKeywords := sig optionalKeywords.
921      optionalVariables := sig optionalVariables. ]
924 node1@(nodes Signature traits) = node2@(nodes Signature traits)
925 [node1 selector = node2 selector /\ [node1 roles = node2 roles]].
927 sig@(nodes Signature traits) walk: block
929   sig roles do: [| :role | role ifNotNil: [role walk: block]]
932 sig@(nodes Signature traits) transformChildren: block
934   sig roles infect: [| :role | role ifNotNil: [role transformBy: block]].
937 sig@(nodes Signature traits) deepCopy: scope &into: target
939   resend `>>
940     [roles := sig roles
941        collect: [| :role | role ifNotNil: [role deepCopy: scope]]. ]
944 sig@(nodes Signature traits) evaluateIn: namespace
946   sig
949 nodes define: #Variable &parents: {nodes Node} &slots: {
950   #name -> #''.
951   #scope -> nodes Ground
954 node1@(nodes Variable traits) = node2@(nodes Variable traits)
955 [node1 name = node2 name /\ [node1 scope = node2 scope]].
957 var@(nodes Variable traits) deepCopy: scope
959   scope findVariable: var name
962 nodes define: #RestVariable &parents: {nodes Variable}.
964 nodes define: #VariableOperation &parents: {nodes Node} &slots: {#variable}.
966 nodes define: #LoadVariable &parents: {nodes VariableOperation} &slots: {}.
968 load@(nodes LoadVariable traits) from: variable
969 [load new `setting: #{#variable} to: {variable}].
971 var@(nodes Variable traits) load
972 [nodes LoadVariable from: var].
974 node1@(nodes LoadVariable traits) = node2@(nodes LoadVariable traits)
975 [node1 variable = node2 variable].
977 load@(nodes LoadVariable traits) deepCopy: scope
979   (scope findVariable: load variable name)
980     ifNil: [nodes UnaryMessage
981               sending: load variable name
982               to: {nodes ImplicitArgument}]
983     ifNotNilDo: #(load from: _) `er
986 load@(nodes LoadVariable traits) evaluateIn: namespace &optionals: opts
988   load variable name sendTo: {namespace} &optionals: opts
991 nodes define: #LoadRestVariable &parents: {nodes LoadVariable}.
993 nodes define: #StoreVariable &parents: {nodes VariableOperation}
994   &slots: {#value}.
996 store@(nodes StoreVariable traits) of: value into: variable
997 [store new `setting: #{#value. #variable} to: {value. variable}].
999 var@(nodes Variable traits) store: value
1000 [nodes StoreVariable of: value into: var].
1002 load@(nodes LoadVariable traits) store: value
1003 [load variable store: value].
1005 store@(nodes StoreVariable traits) load
1006 [store variable load].
1008 node1@(nodes StoreVariable traits) = node2@(nodes StoreVariable traits)
1009 [node1 variable = node2 variable /\ [node1 value = node2 value]].
1011 store@(nodes StoreVariable traits) walk: block
1013   resend.
1014   store value walk: block
1017 store@(nodes StoreVariable traits) transformChildren: block
1019   store value := store value transformBy: block.
1020   store
1023 store@(nodes StoreVariable traits) deepCopy: scope
1025   (scope findVariable: store variable name)
1026     ifNil:
1027       [nodes KeywordMessage
1028         sending: store variable name name ; ':'
1029         to: {nodes ImplicitArgument. store value deepCopy: scope}]
1030     ifNotNilDo:
1031       [| :var | store of: (store value deepCopy: scope) into: var]
1034 store@(nodes StoreVariable traits) evaluateIn: namespace &optionals: opts
1036   (store variable name name ; ':') intern
1037     sendTo: {namespace. store value evaluateIn: namespace}
1038     &optionals: opts
1041 nodes define: #Return &parents: {nodes Node} &slots: {#value}.
1043 ret@(nodes Return traits) of: value
1044 [ret new `setting: #{#value} to: {value}].
1046 node1@(nodes Return traits) = node2@(nodes Return traits)
1047 [node1 value = node2 value /\ [node1 isSameAs: node2]].
1049 ret@(nodes Return traits) walk: block
1051   resend.
1052   ret value walk: block
1055 ret@(nodes Return traits) deepCopy: scope
1057   ret of: (ret value deepCopy: scope)
1060 ret@(nodes Return traits) transformChildren: block
1062   ret value := ret value transformBy: block.
1063   ret
1066 nodes define: #ReturnClose &parents: {nodes Return}.
1068 ret@(nodes ReturnClose traits) selector [#^].
1070 nodes define: #ReturnFar &parents: {nodes Return}.
1072 ret@(nodes ReturnFar traits) selector [#^^].
1074 nodes define: #ReturnLevel &parents: {nodes Return} &slots: {#level -> 1}.
1076 ret@(nodes ReturnLevel traits) selector [('^' ; ret level printString) intern].
1078 ret@(nodes ReturnLevel traits) by: offset
1079 [ret new `setting: #{#level} to: {offset}].
1081 nodes define: #Resend &parents: {nodes Node}.
1083 _@(nodes Resend traits) selector [ #resend ].
1085 node1@(nodes Resend traits) = node2@(nodes Resend traits)
1086 [True].
1088 "Non-core utilities follow."
1090 n@(nodes Node traits) allSelectorsSent
1091 "Answer a Set of selectors for the messages sent in this parse tree."
1093   [| :calls |
1094    n walk: [| :node | (node is: nodes Message)
1095                         ifTrue: [calls nextPut: node selector]]]
1096     writingAs: (IdentitySet new &capacity: 100)
1099 n@(nodes Node traits) allMacroSelectorsSent
1100 "Answer a Set of selectors for the macro-messages sent in this parse tree."
1102   [| :calls |
1103    n walk: [| :node | (node is: nodes Macro)
1104                         ifTrue: [calls nextPut: node selector]]]
1105     writingAs: (IdentitySet new &capacity: 100)
1108 n@(nodes Node traits) nodeCount
1109 "Answer the number of nodes in this tree, analogous to the size of the tree."
1110 [| count |
1111   count := 0.
1112   n walk: [| :_ | count += 1].
1113   count
1116 n@(nodes Node traits) hasExplicitReturn
1117 "Answer whether there is an explicit/early return call."
1119   n walk: [| :node | (node is: nodes Return) ifTrue: [^ True]].
1120   False