Compiler-Interpreter.st 17 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864
  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. evaluateNode: aNode
  146. ^ ASTInterpreter new
  147. context: self;
  148. node: aNode nextChild;
  149. proceed;
  150. result
  151. ! !
  152. !AIContext methodsFor: 'factory'!
  153. newBlockContext
  154. ^ self class new
  155. outerContext: self;
  156. yourself
  157. ! !
  158. !AIContext methodsFor: 'initialization'!
  159. initializeAST
  160. ast := self method ast.
  161. (SemanticAnalyzer on: self method methodClass)
  162. visit: ast
  163. !
  164. initializeFromMethodContext: aMethodContext
  165. self
  166. evaluatedSelector: aMethodContext evaluatedSelector;
  167. index: aMethodContext index;
  168. sendIndexes: aMethodContext sendIndexes;
  169. receiver: aMethodContext receiver;
  170. selector: aMethodContext selector.
  171. aMethodContext outerContext ifNotNil: [ :outer |
  172. "If the method context is nil, the block was defined in JS, so ignore it"
  173. outer methodContext ifNotNil: [
  174. self outerContext: (self class fromMethodContext: aMethodContext outerContext) ].
  175. aMethodContext locals keysAndValuesDo: [ :key :value |
  176. self locals at: key put: value ] ]
  177. !
  178. initializeInterpreter
  179. interpreter := ASTInterpreter new
  180. context: self;
  181. yourself.
  182. self innerContext ifNotNil: [
  183. self setupInterpreter: interpreter ]
  184. !
  185. initializeLocals
  186. locals := Dictionary new.
  187. locals at: 'thisContext' put: self.
  188. ! !
  189. !AIContext methodsFor: 'interpreting'!
  190. arguments
  191. ^ self ast arguments collect: [ :each |
  192. self localAt: each ifAbsent: [ self error: 'Argument not in context' ] ]
  193. !
  194. ast
  195. self isBlockContext ifTrue: [
  196. ^ self outerContext ifNotNil: [ :context | context ast ] ].
  197. ast ifNil: [ self initializeAST ].
  198. ^ ast
  199. !
  200. interpreter
  201. interpreter ifNil: [ self initializeInterpreter ].
  202. ^ interpreter
  203. !
  204. interpreter: anInterpreter
  205. interpreter := anInterpreter
  206. !
  207. receiver
  208. ^ self localAt: 'self'
  209. !
  210. receiver: anObject
  211. self localAt: 'self' put: anObject
  212. !
  213. setupInterpreter: anInterpreter
  214. | currentNode |
  215. "Retrieve the current node"
  216. currentNode := ASTPCNodeVisitor new
  217. selector: self evaluatedSelector;
  218. context: self;
  219. visit: self ast;
  220. currentNode.
  221. anInterpreter node: currentNode.
  222. "Push the send args and receiver to the interpreter stack"
  223. self innerContext arguments reversed do: [ :each |
  224. anInterpreter push: each ].
  225. anInterpreter push: (self innerContext receiver)
  226. ! !
  227. !AIContext class methodsFor: 'instance creation'!
  228. fromMethodContext: aMethodContext
  229. ^ self new
  230. initializeFromMethodContext: aMethodContext;
  231. yourself
  232. ! !
  233. SemanticAnalyzer subclass: #AISemanticAnalyzer
  234. instanceVariableNames: 'context'
  235. package: 'Compiler-Interpreter'!
  236. !AISemanticAnalyzer commentStamp!
  237. I perform the same semantic analysis than `SemanticAnalyzer`, with the difference that provided an `AIContext` context, variables are bound with the context variables.!
  238. !AISemanticAnalyzer methodsFor: 'accessing'!
  239. context
  240. ^ context
  241. !
  242. context: anAIContext
  243. context := anAIContext
  244. ! !
  245. !AISemanticAnalyzer methodsFor: 'visiting'!
  246. visitVariableNode: aNode
  247. self context
  248. localAt: aNode value
  249. ifAbsent: [ ^ super visitVariableNode: aNode ].
  250. aNode binding: ASTContextVar new
  251. ! !
  252. ScopeVar subclass: #ASTContextVar
  253. instanceVariableNames: 'context'
  254. package: 'Compiler-Interpreter'!
  255. !ASTContextVar commentStamp!
  256. I am a variable defined in a `context`.!
  257. !ASTContextVar methodsFor: 'accessing'!
  258. context
  259. ^ context
  260. !
  261. context: anObject
  262. context := anObject
  263. ! !
  264. Object subclass: #ASTDebugger
  265. instanceVariableNames: 'interpreter context'
  266. package: 'Compiler-Interpreter'!
  267. !ASTDebugger commentStamp!
  268. I am a stepping debugger interface for Amber code.
  269. I internally use an instance of `ASTInterpreter` to actually step through node and interpret them.
  270. My instances are created from an `AIContext` with `ASTDebugger class >> context:`.
  271. They hold an `AIContext` instance internally, recursive copy of the `MethodContext`.
  272. ## API
  273. Use the methods of the `'stepping'` protocol to do stepping.!
  274. !ASTDebugger methodsFor: 'accessing'!
  275. context
  276. ^ context
  277. !
  278. context: aContext
  279. context := aContext
  280. !
  281. interpreter
  282. ^ self context interpreter
  283. !
  284. method
  285. ^ self context method
  286. !
  287. nextNode
  288. ^ self interpreter nextNode
  289. ! !
  290. !ASTDebugger methodsFor: 'private'!
  291. flushInnerContexts
  292. "When stepping, the inner contexts are not relevent anymore,
  293. and can be flushed"
  294. self context innerContext: nil
  295. !
  296. onStep
  297. "After each step, check if the interpreter is at the end,
  298. and if it is move to its outer context if any, skipping its
  299. current node (which was just evaluated by the current
  300. interpreter).
  301. After each step we also flush inner contexts."
  302. self interpreter atEnd ifTrue: [
  303. self context: self context outerContext.
  304. self context ifNotNil: [ self skip ] ].
  305. self flushInnerContexts
  306. ! !
  307. !ASTDebugger methodsFor: 'stepping'!
  308. proceed
  309. self shouldBeImplemented
  310. !
  311. restart
  312. self interpreter restart.
  313. self flushInnerContexts
  314. !
  315. skip
  316. self interpreter skip.
  317. self onStep
  318. !
  319. stepInto
  320. self shouldBeImplemented
  321. !
  322. stepOver
  323. self interpreter stepOver.
  324. self onStep
  325. ! !
  326. !ASTDebugger methodsFor: 'testing'!
  327. atEnd
  328. ^ self interpreter atEnd and: [
  329. self context outerContext isNil ]
  330. ! !
  331. !ASTDebugger class methodsFor: 'instance creation'!
  332. context: aContext
  333. ^ self new
  334. context: aContext;
  335. yourself
  336. ! !
  337. NodeVisitor subclass: #ASTInterpreter
  338. instanceVariableNames: 'node context stack returnValue returned'
  339. package: 'Compiler-Interpreter'!
  340. !ASTInterpreter commentStamp!
  341. I visit an AST, interpreting (evaluating) nodes one after the other, using a small stack machine.
  342. ## API
  343. While my instances should be used from within an `ASTDebugger`, which provides a more high level interface,
  344. you can use methods from the `interpreting` protocol:
  345. - `#step` evaluates the current `node` only
  346. - `#stepOver` evaluates the AST from the current `node` up to the next stepping node (most likely the next send node)
  347. - `#proceed` evaluates eagerly the AST
  348. - `#restart` select the first node of the AST
  349. - `#skip` skips the current node, moving to the next one if any!
  350. !ASTInterpreter methodsFor: 'accessing'!
  351. context
  352. ^ context
  353. !
  354. context: aContext
  355. context := aContext
  356. !
  357. node
  358. "Answer the next node, ie the node to be evaluated in the next step"
  359. ^ node
  360. !
  361. node: aNode
  362. node := aNode
  363. !
  364. result
  365. ^ self hasReturned
  366. ifTrue: [ self returnValue ]
  367. ifFalse: [ self context receiver ]
  368. !
  369. returnValue
  370. ^ returnValue
  371. !
  372. returnValue: anObject
  373. returnValue := anObject
  374. !
  375. stack
  376. ^ stack ifNil: [ stack := OrderedCollection new ]
  377. ! !
  378. !ASTInterpreter methodsFor: 'interpreting'!
  379. interpret
  380. "Interpret the next node to be evaluated"
  381. self visit: self node
  382. !
  383. interpret: aNode
  384. self node: aNode.
  385. self interpret
  386. !
  387. next
  388. self node: self node nextNode
  389. !
  390. proceed
  391. "Eagerly evaluate the ast"
  392. [ self atEnd ]
  393. whileFalse: [ self step ]
  394. !
  395. restart
  396. self node: self context ast nextChild
  397. !
  398. setNonLocalReturnFromContext: aContext
  399. aContext interpreter hasReturned ifTrue: [
  400. returned := true.
  401. self returnValue: aContext interpreter returnValue ]
  402. !
  403. skip
  404. self next
  405. !
  406. step
  407. self
  408. interpret;
  409. next
  410. !
  411. stepOver
  412. self step.
  413. [ self node isSteppingNode ] whileFalse: [
  414. self step ]
  415. ! !
  416. !ASTInterpreter methodsFor: 'private'!
  417. assign: aNode to: anObject
  418. aNode binding isInstanceVar
  419. ifTrue: [ self context receiver instVarAt: aNode value put: anObject ]
  420. ifFalse: [ self context localAt: aNode value put: anObject ]
  421. !
  422. eval: aString
  423. "Evaluate aString as JS source inside an JS function.
  424. aString is not sandboxed."
  425. | source function |
  426. source := String streamContents: [ :str |
  427. str nextPutAll: '(function('.
  428. self context locals keys
  429. do: [ :each | str nextPutAll: each ]
  430. separatedBy: [ str nextPutAll: ',' ].
  431. str
  432. nextPutAll: '){ return (function() {';
  433. nextPutAll: aString;
  434. nextPutAll: '})() })' ].
  435. function := Compiler new eval: source.
  436. ^ function valueWithPossibleArguments: self context locals values
  437. !
  438. messageFromSendNode: aSendNode arguments: aCollection
  439. ^ Message new
  440. selector: aSendNode selector;
  441. arguments: aCollection;
  442. yourself
  443. !
  444. messageNotUnderstood: aMessage receiver: anObject
  445. MessageNotUnderstood new
  446. meesage: aMessage;
  447. receiver: anObject;
  448. signal
  449. !
  450. sendMessage: aMessage to: anObject superSend: aBoolean
  451. | method |
  452. aBoolean ifFalse: [ ^ aMessage sendTo: anObject ].
  453. anObject class superclass ifNil: [ ^ self messageNotUnderstood: aMessage receiver: anObject ].
  454. method := anObject class superclass methodDictionary
  455. at: aMessage selector
  456. ifAbsent: [ ^ self messageNotUnderstood: aMessage receiver: anObject ].
  457. ^ method sendTo: anObject arguments: aMessage arguments
  458. ! !
  459. !ASTInterpreter methodsFor: 'stack'!
  460. peek
  461. "Peek the top object of the context stack"
  462. self stack ifEmpty: [ ^ nil ].
  463. ^ self stack last
  464. !
  465. pop
  466. "Pop an object from the context stack"
  467. | peekedValue |
  468. peekedValue := self peek.
  469. self stack removeLast.
  470. ^ peekedValue
  471. !
  472. push: anObject
  473. "Push an object to the context stack"
  474. ^ self stack add: anObject
  475. ! !
  476. !ASTInterpreter methodsFor: 'testing'!
  477. atEnd
  478. ^ self hasReturned or: [ self node isNil ]
  479. !
  480. hasReturned
  481. ^ returned ifNil: [ false ]
  482. ! !
  483. !ASTInterpreter methodsFor: 'visiting'!
  484. visit: aNode
  485. self hasReturned ifFalse: [ super visit: aNode ]
  486. !
  487. visitAssignmentNode: aNode
  488. | poppedValue |
  489. poppedValue := self pop.
  490. "Pop the left side of the assignment.
  491. It already has been visited, and we don't need its value."
  492. self pop.
  493. self push: poppedValue.
  494. self assign: aNode left to: poppedValue
  495. !
  496. visitBlockNode: aNode
  497. "Do not evaluate the block node.
  498. Instead, put all instructions into a block that we push to the stack for later evaluation"
  499. | block |
  500. block := AIBlockClosure forContext: self context node: aNode.
  501. self push: block
  502. !
  503. visitDynamicArrayNode: aNode
  504. | array |
  505. array := #().
  506. aNode nodes do: [ :each |
  507. array addFirst: self pop ].
  508. self push: array
  509. !
  510. visitDynamicDictionaryNode: aNode
  511. | keyValueList |
  512. keyValueList := OrderedCollection new.
  513. aNode nodes do: [ :each |
  514. keyValueList add: self pop ].
  515. self push: (HashedCollection newFromPairs: keyValueList reversed)
  516. !
  517. visitJSStatementNode: aNode
  518. returned := true.
  519. self returnValue: (self eval: aNode source)
  520. !
  521. visitNode: aNode
  522. "Do nothing by default. Especially, do not visit children recursively."
  523. !
  524. visitReturnNode: aNode
  525. returned := true.
  526. self returnValue: self pop
  527. !
  528. visitSendNode: aNode
  529. | receiver args message result |
  530. args := aNode arguments collect: [ :each | self pop ].
  531. receiver := self pop.
  532. message := self
  533. messageFromSendNode: aNode
  534. arguments: args reversed.
  535. result := self sendMessage: message to: receiver superSend: aNode superSend.
  536. "For cascade sends, push the reciever if the send is not the last one"
  537. (aNode isCascadeSendNode and: [ aNode isLastChild not ])
  538. ifTrue: [ self push: receiver ]
  539. ifFalse: [ self push: result ]
  540. !
  541. visitValueNode: aNode
  542. self push: aNode value
  543. !
  544. visitVariableNode: aNode
  545. aNode binding isUnknownVar ifTrue: [
  546. ^ self push: (PlatformInterface globals at: aNode value ifAbsent: [ self error: 'Unknown variable' ]) ].
  547. self push: (aNode binding isInstanceVar
  548. ifTrue: [ self context receiver instVarAt: aNode value ]
  549. ifFalse: [ self context
  550. localAt: aNode value
  551. ifAbsent: [
  552. aNode value isCapitalized
  553. ifTrue: [
  554. Smalltalk globals
  555. at: aNode value
  556. ifAbsent: [ PlatformInterface globals at: aNode value ] ] ] ])
  557. ! !
  558. Error subclass: #ASTInterpreterError
  559. instanceVariableNames: ''
  560. package: 'Compiler-Interpreter'!
  561. !ASTInterpreterError commentStamp!
  562. I get signaled when an AST interpreter is unable to interpret a node.!
  563. NodeVisitor subclass: #ASTPCNodeVisitor
  564. instanceVariableNames: 'context index selector currentNode'
  565. package: 'Compiler-Interpreter'!
  566. !ASTPCNodeVisitor commentStamp!
  567. I visit an AST until I get to the current node for the `context` and answer it.
  568. ## API
  569. My instances must be filled with a context object using `#context:`.
  570. After visiting the AST the current node is answered by `#currentNode`!
  571. !ASTPCNodeVisitor methodsFor: 'accessing'!
  572. context
  573. ^ context
  574. !
  575. context: aContext
  576. context := aContext
  577. !
  578. currentNode
  579. ^ currentNode
  580. !
  581. increaseIndex
  582. index := self index + 1
  583. !
  584. index
  585. ^ index ifNil: [ index := 0 ]
  586. !
  587. selector
  588. ^ selector
  589. !
  590. selector: aString
  591. selector := aString
  592. ! !
  593. !ASTPCNodeVisitor methodsFor: 'visiting'!
  594. visitJSStatementNode: aNode
  595. "If a JSStatementNode is encountered, it always is the current node.
  596. Stop visiting the AST there"
  597. currentNode := aNode
  598. !
  599. visitSendNode: aNode
  600. | sendIndex |
  601. sendIndex := self context sendIndexAt: self selector.
  602. super visitSendNode: aNode.
  603. self selector = aNode selector ifTrue: [
  604. self index < sendIndex ifFalse: [
  605. self index > sendIndex ifFalse: [ currentNode := aNode ] ].
  606. self increaseIndex ]
  607. ! !
  608. !AssignmentNode methodsFor: '*Compiler-Interpreter'!
  609. isSteppingNode
  610. ^ true
  611. ! !
  612. !BlockNode methodsFor: '*Compiler-Interpreter'!
  613. isSteppingNode
  614. ^ true
  615. ! !
  616. !DynamicArrayNode methodsFor: '*Compiler-Interpreter'!
  617. isSteppingNode
  618. ^ true
  619. ! !
  620. !DynamicDictionaryNode methodsFor: '*Compiler-Interpreter'!
  621. isSteppingNode
  622. ^ true
  623. ! !
  624. !JSStatementNode methodsFor: '*Compiler-Interpreter'!
  625. isSteppingNode
  626. ^ true
  627. ! !
  628. !Node methodsFor: '*Compiler-Interpreter'!
  629. isSteppingNode
  630. ^ false
  631. ! !
  632. !SendNode methodsFor: '*Compiler-Interpreter'!
  633. isSteppingNode
  634. ^ true
  635. ! !