Compiler-Interpreter.st 20 KB

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