Compiler-Interpreter.st 18 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909
  1. Smalltalk createPackage: 'Compiler-Interpreter'!
  2. BlockClosure subclass: #AIBlockClosure
  3. instanceVariableNames: 'node outerContext'
  4. package: 'Compiler-Interpreter'!
  5. !AIBlockClosure commentStamp!
  6. I am a special `BlockClosure` subclass used by an interpreter to interpret a block node.
  7. While I am polymorphic with `BlockClosure`, some methods such as `#new` will raise interpretation errors. Unlike a `BlockClosure`, my instance are not JavaScript functions.
  8. Evaluating an instance will result in interpreting the `node` instance variable (instance of `BlockNode`).!
  9. !AIBlockClosure methodsFor: 'accessing'!
  10. compiledSource
  11. "Unlike blocks, the receiver doesn't represent a JS function"
  12. ^ '[ AST Block closure ]'
  13. !
  14. numArgs
  15. ^ node temps size
  16. ! !
  17. !AIBlockClosure methodsFor: 'converting'!
  18. currySelf
  19. self interpreterError
  20. ! !
  21. !AIBlockClosure methodsFor: 'error handling'!
  22. interpreterError
  23. ASTInterpreterError signal: 'Method cannot be interpreted by the interpreter.'
  24. ! !
  25. !AIBlockClosure methodsFor: 'evaluating'!
  26. applyTo: anObject arguments: aCollection
  27. self interpreterError
  28. !
  29. value
  30. ^ self valueWithPossibleArguments: #()
  31. !
  32. value: anArgument
  33. ^ self valueWithPossibleArguments: {anArgument}
  34. !
  35. value: firstArgument value: secondArgument
  36. ^ self valueWithPossibleArguments: {firstArgument . secondArgument}
  37. !
  38. value: firstArgument value: secondArgument value: thirdArgument
  39. ^ self valueWithPossibleArguments: {firstArgument . secondArgument . thirdArgument}
  40. !
  41. valueWithPossibleArguments: aCollection
  42. | context sequenceNode |
  43. context := outerContext newBlockContext.
  44. "Interpret a copy of the sequence node to avoid creating a new AIBlockClosure"
  45. sequenceNode := node nodes first copy
  46. parent: nil;
  47. yourself.
  48. "Populate the arguments into the context locals"
  49. node parameters withIndexDo: [ :each :index |
  50. context localAt: each put: (aCollection at: index ifAbsent: [ nil ]) ].
  51. "Interpret the first node of the BlockSequenceNode"
  52. context interpreter
  53. node: sequenceNode nextChild;
  54. proceed.
  55. outerContext interpreter
  56. setNonLocalReturnFromContext: context.
  57. ^ context interpreter pop
  58. ! !
  59. !AIBlockClosure methodsFor: 'initialization'!
  60. initializeWithContext: aContext node: aNode
  61. node := aNode.
  62. outerContext := aContext
  63. ! !
  64. !AIBlockClosure class methodsFor: 'instance creation'!
  65. forContext: aContext node: aNode
  66. ^ self new
  67. initializeWithContext: aContext node: aNode;
  68. yourself
  69. ! !
  70. MethodContext subclass: #AIContext
  71. instanceVariableNames: 'outerContext innerContext pc locals selector index sendIndexes evaluatedSelector ast interpreter'
  72. package: 'Compiler-Interpreter'!
  73. !AIContext commentStamp!
  74. I am like a `MethodContext`, used by the `ASTInterpreter`.
  75. Unlike a `MethodContext`, my instances are not read-only.
  76. When debugging, my instances are created by copying the current `MethodContext` (thisContext)!
  77. !AIContext methodsFor: 'accessing'!
  78. evaluatedSelector
  79. ^ evaluatedSelector
  80. !
  81. evaluatedSelector: aString
  82. evaluatedSelector := aString
  83. !
  84. index
  85. ^ index ifNil: [ 0 ]
  86. !
  87. index: anInteger
  88. index := anInteger
  89. !
  90. innerContext
  91. ^ innerContext
  92. !
  93. innerContext: anAIContext
  94. innerContext := anAIContext
  95. !
  96. localAt: aString
  97. "Lookup the local value up to the method context"
  98. ^ self locals at: aString ifAbsent: [
  99. self outerContext ifNotNil: [ :context |
  100. context localAt: aString ifAbsent: [
  101. self error: 'Variable missing' ] ] ]
  102. !
  103. localAt: aString ifAbsent: aBlock
  104. "Lookup the local value up to the method context"
  105. ^ self locals at: aString ifAbsent: [
  106. self outerContext
  107. ifNotNil: [ :context | context localAt: aString ifAbsent: aBlock ]
  108. ifNil: [ aBlock value ] ]
  109. !
  110. localAt: aString put: anObject
  111. self locals at: aString put: anObject
  112. !
  113. locals
  114. locals ifNil: [ self initializeLocals ].
  115. ^ locals
  116. !
  117. method
  118. ^ self methodContext ifNotNil: [
  119. self methodContext receiver class lookupSelector: self methodContext selector ]
  120. !
  121. outerContext
  122. ^ outerContext
  123. !
  124. outerContext: anAIContext
  125. outerContext := anAIContext.
  126. outerContext ifNotNil: [ :context |
  127. context innerContext: self ]
  128. !
  129. selector
  130. ^ selector
  131. !
  132. selector: aString
  133. selector := aString
  134. !
  135. sendIndexAt: aString
  136. ^ self sendIndexes at: aString ifAbsent: [ 0 ]
  137. !
  138. sendIndexes
  139. ^ sendIndexes ifNil: [ Dictionary new ]
  140. !
  141. sendIndexes: aDictionary
  142. sendIndexes := aDictionary
  143. ! !
  144. !AIContext methodsFor: 'evaluating'!
  145. evaluate: aString on: anEvaluator
  146. ^ anEvaluator evaluate: aString context: self
  147. !
  148. evaluateNode: aNode
  149. ^ ASTInterpreter new
  150. context: self;
  151. node: aNode nextChild;
  152. proceed;
  153. result
  154. ! !
  155. !AIContext methodsFor: 'factory'!
  156. newBlockContext
  157. ^ self class new
  158. outerContext: self;
  159. yourself
  160. ! !
  161. !AIContext methodsFor: 'initialization'!
  162. initializeAST
  163. ast := self method ast.
  164. (SemanticAnalyzer on: self method methodClass)
  165. visit: ast
  166. !
  167. initializeFromMethodContext: aMethodContext
  168. self
  169. evaluatedSelector: aMethodContext evaluatedSelector;
  170. index: aMethodContext index;
  171. sendIndexes: aMethodContext sendIndexes;
  172. receiver: aMethodContext receiver;
  173. selector: aMethodContext selector.
  174. aMethodContext outerContext ifNotNil: [ :outer |
  175. "If the method context is nil, the block was defined in JS, so ignore it"
  176. outer methodContext ifNotNil: [
  177. self outerContext: (self class fromMethodContext: aMethodContext outerContext) ].
  178. aMethodContext locals keysAndValuesDo: [ :key :value |
  179. self locals at: key put: value ] ]
  180. !
  181. initializeInterpreter
  182. interpreter := ASTInterpreter new
  183. context: self;
  184. yourself.
  185. self innerContext ifNotNil: [
  186. self setupInterpreter: interpreter ]
  187. !
  188. initializeLocals
  189. locals := Dictionary new.
  190. locals at: 'thisContext' put: self.
  191. ! !
  192. !AIContext methodsFor: 'interpreting'!
  193. arguments
  194. ^ self ast arguments collect: [ :each |
  195. self localAt: each ifAbsent: [ self error: 'Argument not in context' ] ]
  196. !
  197. ast
  198. self isBlockContext ifTrue: [
  199. ^ self outerContext ifNotNil: [ :context | context ast ] ].
  200. ast ifNil: [ self initializeAST ].
  201. ^ ast
  202. !
  203. basicReceiver
  204. ^ self localAt: 'self'
  205. !
  206. interpreter
  207. interpreter ifNil: [ self initializeInterpreter ].
  208. ^ interpreter
  209. !
  210. interpreter: anInterpreter
  211. interpreter := anInterpreter
  212. !
  213. receiver: anObject
  214. self localAt: 'self' put: anObject
  215. !
  216. setupInterpreter: anInterpreter
  217. | currentNode |
  218. "Retrieve the current node"
  219. currentNode := ASTPCNodeVisitor new
  220. selector: self evaluatedSelector;
  221. context: self;
  222. visit: self ast;
  223. currentNode.
  224. anInterpreter node: currentNode.
  225. "Push the send args and receiver to the interpreter stack"
  226. self innerContext arguments reversed do: [ :each |
  227. anInterpreter push: each ].
  228. anInterpreter push: (self innerContext receiver)
  229. ! !
  230. !AIContext methodsFor: 'testing'!
  231. isTopContext
  232. ^ self innerContext isNil
  233. ! !
  234. !AIContext class methodsFor: 'instance creation'!
  235. fromMethodContext: aMethodContext
  236. ^ self new
  237. initializeFromMethodContext: aMethodContext;
  238. yourself
  239. ! !
  240. SemanticAnalyzer subclass: #AISemanticAnalyzer
  241. instanceVariableNames: 'context'
  242. package: 'Compiler-Interpreter'!
  243. !AISemanticAnalyzer commentStamp!
  244. I perform the same semantic analysis than `SemanticAnalyzer`, with the difference that provided an `AIContext` context, variables are bound with the context variables.!
  245. !AISemanticAnalyzer methodsFor: 'accessing'!
  246. context
  247. ^ context
  248. !
  249. context: anAIContext
  250. context := anAIContext
  251. ! !
  252. !AISemanticAnalyzer methodsFor: 'visiting'!
  253. visitVariableNode: aNode
  254. self context
  255. localAt: aNode value
  256. ifAbsent: [ ^ super visitVariableNode: aNode ].
  257. aNode binding: ASTContextVar new
  258. ! !
  259. ScopeVar subclass: #ASTContextVar
  260. instanceVariableNames: 'context'
  261. package: 'Compiler-Interpreter'!
  262. !ASTContextVar commentStamp!
  263. I am a variable defined in a `context`.!
  264. !ASTContextVar methodsFor: 'accessing'!
  265. context
  266. ^ context
  267. !
  268. context: anObject
  269. context := anObject
  270. ! !
  271. Object subclass: #ASTDebugger
  272. instanceVariableNames: 'interpreter context result'
  273. package: 'Compiler-Interpreter'!
  274. !ASTDebugger commentStamp!
  275. I am a stepping debugger interface for Amber code.
  276. I internally use an instance of `ASTInterpreter` to actually step through node and interpret them.
  277. My instances are created from an `AIContext` with `ASTDebugger class >> context:`.
  278. They hold an `AIContext` instance internally, recursive copy of the `MethodContext`.
  279. ## API
  280. Use the methods of the `'stepping'` protocol to do stepping.!
  281. !ASTDebugger methodsFor: 'accessing'!
  282. context
  283. ^ context
  284. !
  285. context: aContext
  286. context := aContext
  287. !
  288. interpreter
  289. ^ self context ifNotNil: [ :ctx |
  290. ctx interpreter ]
  291. !
  292. method
  293. ^ self context method
  294. !
  295. nextNode
  296. ^ self interpreter nextNode
  297. !
  298. node
  299. ^ self interpreter ifNotNil: [
  300. self interpreter node ]
  301. !
  302. result
  303. ^ result
  304. ! !
  305. !ASTDebugger methodsFor: 'actions'!
  306. flushInnerContexts
  307. "When stepping, the inner contexts are not relevent anymore,
  308. and can be flushed"
  309. self context ifNotNil: [ :cxt |
  310. cxt innerContext: nil ]
  311. ! !
  312. !ASTDebugger methodsFor: 'private'!
  313. onStep
  314. "After each step, check if the interpreter is at the end,
  315. and if it is move to its outer context if any, skipping its
  316. current node (which was just evaluated by the current
  317. interpreter).
  318. After each step we also flush inner contexts."
  319. result := self interpreter result.
  320. self interpreter atEnd ifTrue: [
  321. self context outerContext ifNotNil: [ :outerContext |
  322. self context: outerContext ].
  323. self interpreter atEnd ifFalse: [ self interpreter skip ] ].
  324. self flushInnerContexts
  325. ! !
  326. !ASTDebugger methodsFor: 'stepping'!
  327. proceed
  328. [ self atEnd ] whileFalse: [ self stepOver ]
  329. !
  330. restart
  331. self interpreter restart.
  332. self flushInnerContexts
  333. !
  334. stepInto
  335. self shouldBeImplemented
  336. !
  337. stepOver
  338. self context isTopContext
  339. ifFalse: [ self interpreter skip ]
  340. ifTrue: [ self interpreter stepOver ].
  341. self onStep
  342. ! !
  343. !ASTDebugger methodsFor: 'testing'!
  344. atEnd
  345. self context ifNil: [ ^ true ].
  346. ^ self interpreter atEnd and: [
  347. self context isTopContext ]
  348. ! !
  349. !ASTDebugger class methodsFor: 'instance creation'!
  350. context: aContext
  351. ^ self new
  352. context: aContext;
  353. yourself
  354. ! !
  355. NodeVisitor subclass: #ASTInterpreter
  356. instanceVariableNames: 'node context stack returnValue returned forceAtEnd'
  357. package: 'Compiler-Interpreter'!
  358. !ASTInterpreter commentStamp!
  359. I visit an AST, interpreting (evaluating) nodes one after the other, using a small stack machine.
  360. ## API
  361. While my instances should be used from within an `ASTDebugger`, which provides a more high level interface,
  362. you can use methods from the `interpreting` protocol:
  363. - `#step` evaluates the current `node` only
  364. - `#stepOver` evaluates the AST from the current `node` up to the next stepping node (most likely the next send node)
  365. - `#proceed` evaluates eagerly the AST
  366. - `#restart` select the first node of the AST
  367. - `#skip` skips the current node, moving to the next one if any!
  368. !ASTInterpreter methodsFor: 'accessing'!
  369. context
  370. ^ context
  371. !
  372. context: aContext
  373. context := aContext
  374. !
  375. node
  376. "Answer the next node, ie the node to be evaluated in the next step"
  377. ^ node
  378. !
  379. node: aNode
  380. node := aNode
  381. !
  382. result
  383. ^ self hasReturned
  384. ifTrue: [ self returnValue ]
  385. ifFalse: [ self context receiver ]
  386. !
  387. returnValue
  388. ^ returnValue
  389. !
  390. returnValue: anObject
  391. returnValue := anObject
  392. !
  393. stack
  394. ^ stack ifNil: [ stack := OrderedCollection new ]
  395. ! !
  396. !ASTInterpreter methodsFor: 'initialization'!
  397. initialize
  398. super initialize.
  399. forceAtEnd := false
  400. ! !
  401. !ASTInterpreter methodsFor: 'interpreting'!
  402. interpret
  403. "Interpret the next node to be evaluated"
  404. self visit: self node
  405. !
  406. interpret: aNode
  407. self node: aNode.
  408. self interpret
  409. !
  410. next
  411. self node: self node nextNode
  412. !
  413. proceed
  414. "Eagerly evaluate the ast"
  415. [ self atEnd ]
  416. whileFalse: [ self step ]
  417. !
  418. restart
  419. self node: self context ast nextChild
  420. !
  421. setNonLocalReturnFromContext: aContext
  422. aContext interpreter hasReturned ifTrue: [
  423. returned := true.
  424. self returnValue: aContext interpreter returnValue ]
  425. !
  426. skip
  427. self next
  428. !
  429. step
  430. self
  431. interpret;
  432. next
  433. !
  434. stepOver
  435. self step.
  436. [ self node isNil or: [ self node isSteppingNode ] ] whileFalse: [
  437. self step ]
  438. ! !
  439. !ASTInterpreter methodsFor: 'private'!
  440. assign: aNode to: anObject
  441. aNode binding isInstanceVar
  442. ifTrue: [ self context receiver instVarAt: aNode value put: anObject ]
  443. ifFalse: [ self context localAt: aNode value put: anObject ]
  444. !
  445. eval: aString
  446. "Evaluate aString as JS source inside an JS function.
  447. aString is not sandboxed."
  448. | source function |
  449. source := String streamContents: [ :str |
  450. str nextPutAll: '(function('.
  451. self context locals keys
  452. do: [ :each | str nextPutAll: each ]
  453. separatedBy: [ str nextPutAll: ',' ].
  454. str
  455. nextPutAll: '){ return (function() {';
  456. nextPutAll: aString;
  457. nextPutAll: '})() })' ].
  458. function := Compiler new eval: source.
  459. ^ function valueWithPossibleArguments: self context locals values
  460. !
  461. messageFromSendNode: aSendNode arguments: aCollection
  462. ^ Message new
  463. selector: aSendNode selector;
  464. arguments: aCollection;
  465. yourself
  466. !
  467. messageNotUnderstood: aMessage receiver: anObject
  468. MessageNotUnderstood new
  469. meesage: aMessage;
  470. receiver: anObject;
  471. signal
  472. !
  473. sendMessage: aMessage to: anObject superSend: aBoolean
  474. | method |
  475. aBoolean ifFalse: [ ^ aMessage sendTo: anObject ].
  476. anObject class superclass ifNil: [ ^ self messageNotUnderstood: aMessage receiver: anObject ].
  477. method := anObject class superclass methodDictionary
  478. at: aMessage selector
  479. ifAbsent: [ ^ self messageNotUnderstood: aMessage receiver: anObject ].
  480. ^ method sendTo: anObject arguments: aMessage arguments
  481. ! !
  482. !ASTInterpreter methodsFor: 'stack'!
  483. peek
  484. "Peek the top object of the context stack"
  485. self stack ifEmpty: [ ^ nil ].
  486. ^ self stack last
  487. !
  488. pop
  489. "Pop an object from the context stack"
  490. | peekedValue |
  491. peekedValue := self peek.
  492. self stack removeLast.
  493. ^ peekedValue
  494. !
  495. push: anObject
  496. "Push an object to the context stack"
  497. ^ self stack add: anObject
  498. ! !
  499. !ASTInterpreter methodsFor: 'testing'!
  500. atEnd
  501. forceAtEnd ifTrue: [ ^ true ].
  502. ^ self hasReturned or: [ self node isNil ]
  503. !
  504. hasReturned
  505. ^ returned ifNil: [ false ]
  506. ! !
  507. !ASTInterpreter methodsFor: 'visiting'!
  508. visit: aNode
  509. self hasReturned ifFalse: [ super visit: aNode ]
  510. !
  511. visitAssignmentNode: aNode
  512. | poppedValue |
  513. poppedValue := self pop.
  514. "Pop the left side of the assignment.
  515. It already has been visited, and we don't need its value."
  516. self pop.
  517. self push: poppedValue.
  518. self assign: aNode left to: poppedValue
  519. !
  520. visitBlockNode: aNode
  521. "Do not evaluate the block node.
  522. Instead, put all instructions into a block that we push to the stack for later evaluation"
  523. | block |
  524. block := AIBlockClosure forContext: self context node: aNode.
  525. self push: block
  526. !
  527. visitBlockSequenceNode: aNode
  528. "If the receiver is actually visiting a BlockSequenceNode,
  529. it means the the context is a block context. Evaluation should
  530. stop right after evaluating the block sequence and the outer
  531. context's interpreter should take over.
  532. Therefore we force #atEnd."
  533. super visitBlockSequenceNode: aNode.
  534. forceAtEnd := true
  535. !
  536. visitDynamicArrayNode: aNode
  537. | array |
  538. array := #().
  539. aNode nodes do: [ :each |
  540. array addFirst: self pop ].
  541. self push: array
  542. !
  543. visitDynamicDictionaryNode: aNode
  544. | keyValueList |
  545. keyValueList := OrderedCollection new.
  546. aNode nodes do: [ :each |
  547. keyValueList add: self pop ].
  548. self push: (HashedCollection newFromPairs: keyValueList reversed)
  549. !
  550. visitJSStatementNode: aNode
  551. returned := true.
  552. self returnValue: (self eval: aNode source)
  553. !
  554. visitNode: aNode
  555. "Do nothing by default. Especially, do not visit children recursively."
  556. !
  557. visitReturnNode: aNode
  558. returned := true.
  559. self returnValue: self pop
  560. !
  561. visitSendNode: aNode
  562. | receiver args message result |
  563. args := aNode arguments collect: [ :each | self pop ].
  564. receiver := self pop.
  565. message := self
  566. messageFromSendNode: aNode
  567. arguments: args reversed.
  568. result := self sendMessage: message to: receiver superSend: aNode superSend.
  569. "For cascade sends, push the reciever if the send is not the last one"
  570. (aNode isCascadeSendNode and: [ aNode isLastChild not ])
  571. ifTrue: [ self push: receiver ]
  572. ifFalse: [ self push: result ]
  573. !
  574. visitValueNode: aNode
  575. self push: aNode value
  576. !
  577. visitVariableNode: aNode
  578. aNode binding isUnknownVar ifTrue: [
  579. ^ self push: (PlatformInterface globals at: aNode value ifAbsent: [ self error: 'Unknown variable' ]) ].
  580. self push: (aNode binding isInstanceVar
  581. ifTrue: [ self context receiver instVarAt: aNode value ]
  582. ifFalse: [ self context
  583. localAt: aNode value
  584. ifAbsent: [
  585. aNode value isCapitalized
  586. ifTrue: [
  587. Smalltalk globals
  588. at: aNode value
  589. ifAbsent: [ PlatformInterface globals at: aNode value ] ] ] ])
  590. ! !
  591. Error subclass: #ASTInterpreterError
  592. instanceVariableNames: ''
  593. package: 'Compiler-Interpreter'!
  594. !ASTInterpreterError commentStamp!
  595. I get signaled when an AST interpreter is unable to interpret a node.!
  596. NodeVisitor subclass: #ASTPCNodeVisitor
  597. instanceVariableNames: 'context index selector currentNode'
  598. package: 'Compiler-Interpreter'!
  599. !ASTPCNodeVisitor commentStamp!
  600. I visit an AST until I get to the current node for the `context` and answer it.
  601. ## API
  602. My instances must be filled with a context object using `#context:`.
  603. After visiting the AST the current node is answered by `#currentNode`!
  604. !ASTPCNodeVisitor methodsFor: 'accessing'!
  605. context
  606. ^ context
  607. !
  608. context: aContext
  609. context := aContext
  610. !
  611. currentNode
  612. ^ currentNode
  613. !
  614. increaseIndex
  615. index := self index + 1
  616. !
  617. index
  618. ^ index ifNil: [ index := 0 ]
  619. !
  620. selector
  621. ^ selector
  622. !
  623. selector: aString
  624. selector := aString
  625. ! !
  626. !ASTPCNodeVisitor methodsFor: 'visiting'!
  627. visitJSStatementNode: aNode
  628. "If a JSStatementNode is encountered, it always is the current node.
  629. Stop visiting the AST there"
  630. currentNode := aNode
  631. !
  632. visitSendNode: aNode
  633. | sendIndex |
  634. sendIndex := self context sendIndexAt: self selector.
  635. super visitSendNode: aNode.
  636. self selector = aNode selector ifTrue: [
  637. self index = sendIndex ifTrue: [ currentNode := aNode ].
  638. self increaseIndex ]
  639. ! !
  640. !AssignmentNode methodsFor: '*Compiler-Interpreter'!
  641. isSteppingNode
  642. ^ true
  643. ! !
  644. !BlockNode methodsFor: '*Compiler-Interpreter'!
  645. isSteppingNode
  646. ^ true
  647. ! !
  648. !DynamicArrayNode methodsFor: '*Compiler-Interpreter'!
  649. isSteppingNode
  650. ^ true
  651. ! !
  652. !DynamicDictionaryNode methodsFor: '*Compiler-Interpreter'!
  653. isSteppingNode
  654. ^ true
  655. ! !
  656. !JSStatementNode methodsFor: '*Compiler-Interpreter'!
  657. isSteppingNode
  658. ^ true
  659. ! !
  660. !Node methodsFor: '*Compiler-Interpreter'!
  661. isSteppingNode
  662. ^ false
  663. ! !
  664. !SendNode methodsFor: '*Compiler-Interpreter'!
  665. isSteppingNode
  666. ^ true
  667. ! !